From git at git.haskell.org Tue Dec 1 02:07:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 1 Dec 2015 02:07:51 +0000 (UTC) Subject: [commit: ghc] master: MkId: Typos in comments (afb7213) Message-ID: <20151201020751.1FB643A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/afb721390cd506f09ce9f04aa3fb19324c2ae5a0/ghc >--------------------------------------------------------------- commit afb721390cd506f09ce9f04aa3fb19324c2ae5a0 Author: ?mer Sinan A?acan Date: Mon Nov 30 21:07:24 2015 -0500 MkId: Typos in comments >--------------------------------------------------------------- afb721390cd506f09ce9f04aa3fb19324c2ae5a0 compiler/basicTypes/MkId.hs | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/compiler/basicTypes/MkId.hs b/compiler/basicTypes/MkId.hs index 989d797..8223f33 100644 --- a/compiler/basicTypes/MkId.hs +++ b/compiler/basicTypes/MkId.hs @@ -106,7 +106,7 @@ There are several reasons why an Id might appear in the wiredInIds: result type. -- sof 1/99] (3) Other error functions (rUNTIME_ERROR_ID) are wired in (a) because - the desugarer generates code that mentiones them directly, and + the desugarer generates code that mentions them directly, and (b) for the same reason as eRROR_ID (4) lazyId is wired in because the wired-in version overrides the @@ -390,7 +390,7 @@ mkDataConWorkId wkr_name data_con -- even if the data constructor is declared strict -- e.g. data T = MkT !(Int,Int) -- Why? Because the *wrapper* is strict (and its unfolding has case - -- expresssions that do the evals) but the *worker* itself is not. + -- expressions that do the evals) but the *worker* itself is not. -- If we pretend it is strict then when we see -- case x of y -> $wMkT y -- the simplifier thinks that y is "sure to be evaluated" (because @@ -655,7 +655,7 @@ dataConSrcToImplBang dflags fam_envs arg_ty = HsStrict --- | Wrappers/Workser and representation following Unpack/Strictness +-- | Wrappers/Workers and representation following Unpack/Strictness -- decisions dataConArgRep :: Type @@ -820,7 +820,7 @@ Because then we'd get an infinite number of arguments. Here is a more complicated case: data S = MkS {-# UNPACK #-} !T Int data T = MkT {-# UNPACK #-} !S Int -Each of S and T must decide independendently whether to unpack +Each of S and T must decide independently whether to unpack and they had better not both say yes. So they must both say no. Also behave conservatively when there is no UNPACK pragma @@ -835,7 +835,7 @@ because Int is non-recursive. Note [Unpack equality predicates] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -If we have a GADT with a contructor C :: (a~[b]) => b -> T a +If we have a GADT with a constructor C :: (a~[b]) => b -> T a we definitely want that equality predicate *unboxed* so that it takes no space at all. This is easily done: just give it an UNPACK pragma. The rest of the unpack/repack code does the @@ -993,7 +993,7 @@ mkFCallId dflags uniq fcall ty strict_sig = mkClosedStrictSig (replicate arity topDmd) topRes -- the call does not claim to be strict in its arguments, since they - -- may be lifted (foreign import prim) and the called code doen't + -- may be lifted (foreign import prim) and the called code doesn't -- necessarily force them. See Trac #11076. {- ************************************************************************ From git at git.haskell.org Tue Dec 1 09:51:53 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 1 Dec 2015 09:51:53 +0000 (UTC) Subject: [commit: ghc] master: Build system: Add stage specific SRC_HC_(WARNING_)OPTS (14d0f7f) Message-ID: <20151201095153.92C523A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/14d0f7f1221db758cd06a69f53803d9d0150164a/ghc >--------------------------------------------------------------- commit 14d0f7f1221db758cd06a69f53803d9d0150164a Author: Thomas Miedema Date: Mon Nov 30 12:35:58 2015 +0100 Build system: Add stage specific SRC_HC_(WARNING_)OPTS * Add stage specific versions of SRC_HC_OPTS. These are currently only used for -Werror. The previous combination of GhcStage2HcOpts and GhcLibHcOpts didn't apply to utils/*. * Add stage specific versions of SRC_HC_WARNING_OPTS. These will later be used for new warning supression flags that should not be passed to the bootstrap compiler. * Move -Wall (and -Werror) related code back to mk/warnings.mk, where it was before 987d54274. Now all warning related code is nicely together. Include mk/warnings.mk after mk/custom-settings.mk to make this work. Reviewed By: bgamari, hvr Differential Revision: https://phabricator.haskell.org/D1536 >--------------------------------------------------------------- 14d0f7f1221db758cd06a69f53803d9d0150164a ghc.mk | 17 +++++---------- mk/config.mk.in | 49 +++++++++++++++++++++++++++++++++++-------- mk/warnings.mk | 44 ++++++++++++++++++++++++++++++-------- rules/distdir-way-opts.mk | 19 ++++++++++++++++- utils/mkUserGuidePart/Main.hs | 5 ----- 5 files changed, 98 insertions(+), 36 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 14d0f7f1221db758cd06a69f53803d9d0150164a From git at git.haskell.org Tue Dec 1 11:15:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 1 Dec 2015 11:15:47 +0000 (UTC) Subject: [commit: ghc] master: Fix grammar and typo in TcTyDecls (6dce643) Message-ID: <20151201111547.AAFC73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6dce643d1981f1ecba2b38f5932720385999244b/ghc >--------------------------------------------------------------- commit 6dce643d1981f1ecba2b38f5932720385999244b Author: Bartosz Nitka Date: Mon Nov 30 08:44:27 2015 -0800 Fix grammar and typo in TcTyDecls Summary: It's just a docufix. Test Plan: just a docufix Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1550 >--------------------------------------------------------------- 6dce643d1981f1ecba2b38f5932720385999244b compiler/typecheck/TcTyDecls.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/compiler/typecheck/TcTyDecls.hs b/compiler/typecheck/TcTyDecls.hs index 88b0df9..73b3a0b 100644 --- a/compiler/typecheck/TcTyDecls.hs +++ b/compiler/typecheck/TcTyDecls.hs @@ -996,9 +996,9 @@ like sel :: T [a] -> a For naughty selectors we make a dummy binding sel = () -for naughty selectors, so that the later type-check will add them to the -environment, and they'll be exported. The function is never called, because -the tyepchecker spots the sel_naughty field. +so that the later type-check will add them to the environment, and they'll be +exported. The function is never called, because the typechecker spots the +sel_naughty field. Note [GADT record selectors] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~ From git at git.haskell.org Tue Dec 1 12:59:12 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 1 Dec 2015 12:59:12 +0000 (UTC) Subject: [commit: ghc] wip/T11028: Comment cleanups (7b96954) Message-ID: <20151201125912.EB4C93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T11028 Link : http://ghc.haskell.org/trac/ghc/changeset/7b9695427d4acfe31ef58d4ed4b8b0d63f908597/ghc >--------------------------------------------------------------- commit 7b9695427d4acfe31ef58d4ed4b8b0d63f908597 Author: Alan Zimmerman Date: Tue Dec 1 14:59:27 2015 +0200 Comment cleanups >--------------------------------------------------------------- 7b9695427d4acfe31ef58d4ed4b8b0d63f908597 compiler/deSugar/DsMeta.hs | 1 - compiler/parser/Parser.y | 1 - compiler/parser/RdrHsSyn.hs | 43 +++++--------------------------------- compiler/rename/RnSource.hs | 23 -------------------- compiler/typecheck/TcTyClsDecls.hs | 18 +--------------- 5 files changed, 6 insertions(+), 80 deletions(-) diff --git a/compiler/deSugar/DsMeta.hs b/compiler/deSugar/DsMeta.hs index faac397..48c4126 100644 --- a/compiler/deSugar/DsMeta.hs +++ b/compiler/deSugar/DsMeta.hs @@ -662,7 +662,6 @@ repC tvs (L _ (ConDeclGADT { con_names = cons addTyVarBinds ex_tvs $ \ ex_bndrs -> -- Binds the remaining con_tvs do { cons1 <- mapM lookupLOcc cons -- See Note [Binders and occurrences] ; let (details,res_ty',_,_) = gadtDeclDetails res_ty - -- AZ: Is this doc context appropriate? ; let doc = ptext (sLit "In the constructor for ") <+> ppr (head cons) ; (hs_details,_res_ty) <- update_con_result doc details res_ty' ; c' <- mapM (\c -> repConstr c hs_details) cons1 diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y index b95c415..bbde989 100644 --- a/compiler/parser/Parser.y +++ b/compiler/parser/Parser.y @@ -2670,7 +2670,6 @@ stmtlist :: { Located ([AddAnn],[LStmt RdrName (LHsExpr RdrName)]) } -- here, because we need too much lookahead if we see do { e ; } -- So we use BodyStmts throughout, and switch the last one over -- in ParseUtils.checkDo instead --- AZ: TODO check that we can retrieve multiple semis. stmts :: { Located ([AddAnn],[LStmt RdrName (LHsExpr RdrName)]) } : stmts ';' stmt {% if null (snd $ unLoc $1) diff --git a/compiler/parser/RdrHsSyn.hs b/compiler/parser/RdrHsSyn.hs index b3175dd..70be8e5 100644 --- a/compiler/parser/RdrHsSyn.hs +++ b/compiler/parser/RdrHsSyn.hs @@ -508,39 +508,6 @@ mkGadtDecl names ty = ConDeclGADT { con_names = names , con_type = ty , con_doc = Nothing } -{- -mkGadtDecl' :: [Located RdrName] - -> LHsSigType RdrName - -> ConDecl RdrName --- We allow C,D :: ty --- and expand it as if it had been --- C :: ty; D :: ty --- (Just like type signatures in general.) - -mkGadtDecl' names lbody_ty@(L loc body_ty) - = mk_gadt_con names - where - (tvs, cxt, tau) = splitLHsSigmaTy lbody_ty - (details, res_ty) -- See Note [Sorting out the result type] - = case tau of - L _ (HsFunTy (L l (HsRecTy flds)) res_ty) - -> (RecCon (L l flds), res_ty) - _other -> (PrefixCon [], tau) - - explicit = case body_ty of - HsForAllTy {} -> True - _ -> False - - mk_gadt_con names - = ConDecl { con_names = names - , con_explicit = explicit - , con_qvars = mkHsQTvs tvs - , con_cxt = cxt - , con_details = details - , con_res = ResTyGADT loc res_ty - , con_doc = Nothing } --} - -- AZ:TODO: this probably belongs in a different module gadtDeclDetails :: LHsSigType name -> (HsConDeclDetails name,LHsType name,LHsContext name,[LHsTyVarBndr name]) @@ -652,19 +619,19 @@ really doesn't matter! -- | Note [Sorting out the result type] -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --- In a GADT declaration which is not a record, we put the whole constr --- type into the ResTyGADT for now; the renamer will unravel it once it --- has sorted out operator fixities. Consider for example +-- In a GADT declaration which is not a record, we put the whole constr type +-- into the res_ty for a ConDeclGADT for now; the renamer will unravel it once +-- it has sorted out operator fixities. Consider for example -- C :: a :*: b -> a :*: b -> a :+: b -- Initially this type will parse as -- a :*: (b -> (a :*: (b -> (a :+: b)))) - +-- -- so it's hard to split up the arguments until we've done the precedence -- resolution (in the renamer) On the other hand, for a record -- { x,y :: Int } -> a :*: b -- there is no doubt. AND we need to sort records out so that -- we can bring x,y into scope. So: --- * For PrefixCon we keep all the args in the ResTyGADT +-- * For PrefixCon we keep all the args in the res_ty -- * For RecCon we do not checkTyVarsP :: SDoc -> SDoc -> Located RdrName -> [LHsType RdrName] -> P (LHsQTyVars RdrName) diff --git a/compiler/rename/RnSource.hs b/compiler/rename/RnSource.hs index d1de338..fb6ab27 100644 --- a/compiler/rename/RnSource.hs +++ b/compiler/rename/RnSource.hs @@ -1506,29 +1506,6 @@ modules), we get better error messages, too. \subsection{Support code for type/data declarations} * * ********************************************************* - -Note [Quantification in data constructor declarations] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -Four cases, afer renaming - * ResTyH98 - - data T a = forall b. MkT { x :: b -> a } - The 'b' is explicitly declared; - con_qvars = [b] - - - data T a = MkT { x :: a -> b } - Do *not* implicitly quantify over 'b'; it is - simply out of scope. con_qvars = [] - - * ResTyGADT - - data T a where { MkT :: forall b. (b -> a) -> T a } - con_qvars = [a,b] - - - data T a where { MkT :: (b -> a) -> T a } - con_qvars = [a,b], by implicit quantification - of the type signature - It is uncomfortable that we add implicitly-bound - type variables to the HsQTyVars, which usually - only has explicitly-bound type variables -} --------------- diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index 489b94c..57960d7 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -1274,12 +1274,6 @@ tcConDecl new_or_data is_prom rep_tycon tmpl_tvs res_tmpl ; return (ctxt, arg_tys, field_lbls, stricts) } - -- Generalise the kind variables (returning quantified TcKindVars) - -- and quantify the type variables (substituting their kinds) - -- REMEMBER: 'tkvs' are: - -- ResTyH98: the *existential* type variables only - -- ResTyGADT: *all* the quantified type variables - -- c.f. the comment on con_qvars in HsDecls ; tkvs <- quantifyTyVars (mkVarSet tmpl_tvs) (tyVarsOfTypes (ctxt++arg_tys)) -- Zonk to Types @@ -1321,16 +1315,6 @@ tcConDecl _new_or_data is_prom rep_tycon tmpl_tvs res_tmpl , con_type = ty@(HsIB { hsib_kvs = _kvs, hsib_tvs = _tvs, hsib_body = _bty}) }) = addErrCtxt (dataConCtxtName names) $ do { traceTc "tcConDecl 1" (ppr names) - {- - AZ:TODO:not sure where this comment now belongs: - - -- Generalise the kind variables (returning quantified TcKindVars) - -- and quantify the type variables (substituting their kinds) - -- REMEMBER: 'tkvs' are: - -- ResTyH98: the *existential* type variables only - -- ResTyGADT: *all* the quantified type variables - -- c.f. the comment on con_qvars in HsDecls - -} ; (ctxt, stricts, field_lbls, arg_tys, res_ty,hs_details) <- tcGadtSigType (ppr names) (unLoc $ head names) ty ; tkvs <- quantifyTyVars emptyVarSet (tyVarsOfTypes (res_ty:ctxt++arg_tys)) @@ -1583,7 +1567,7 @@ data SList s as where We call tcResultType with tmpl_tvs = [(k :: BOX), (s :: k -> *), (as :: List k)] res_tmpl = SList k s as - res_ty = ResTyGADT (SList k1 (s1 :: k1 -> *) (Nil k1)) + res_ty = (SList k1 (s1 :: k1 -> *) (Nil k1)) We get subst: k -> k1 From git at git.haskell.org Tue Dec 1 12:59:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 1 Dec 2015 12:59:35 +0000 (UTC) Subject: [commit: ghc] wip/spj-wildcard-refactor: Merge remote-tracking branch 'origin/master' into wip/spj-wildcard-refactor (d5d2338) Message-ID: <20151201125935.BA6C53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/spj-wildcard-refactor Link : http://ghc.haskell.org/trac/ghc/changeset/d5d233848a527b93f1acf386666da0d2b545a307/ghc >--------------------------------------------------------------- commit d5d233848a527b93f1acf386666da0d2b545a307 Merge: 0c60c0e 290def7 Author: Simon Peyton Jones Date: Mon Nov 30 14:10:58 2015 +0000 Merge remote-tracking branch 'origin/master' into wip/spj-wildcard-refactor Conflicts: compiler/hsSyn/HsTypes.hs compiler/rename/RnSplice.hs testsuite/tests/ghci/scripts/T10248.stderr testsuite/tests/typecheck/should_fail/CustomTypeErrors02.stderr testsuite/tests/wcompat-warnings/WCompatWarningsOn.stderr >--------------------------------------------------------------- d5d233848a527b93f1acf386666da0d2b545a307 compiler/hsSyn/HsTypes.hs | 16 ++ compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 10 ++ compiler/main/DynFlags.hs | 33 +++- compiler/main/Packages.hs | 16 ++ compiler/parser/Lexer.x | 26 +-- compiler/prelude/PrelNames.hs | 29 ++- compiler/rename/RnSplice.hs | 28 +-- compiler/simplCore/CoreMonad.hs | 2 +- compiler/simplCore/SimplCore.hs | 9 +- compiler/typecheck/TcErrors.hs | 9 + compiler/typecheck/TcRnDriver.hs | 196 ++++++++++++++++++++- compiler/typecheck/TcTyClsDecls.hs | 23 ++- compiler/utils/OrdList.hs | 9 + compiler/utils/UniqFM.hs | 9 + docs/users_guide/7.12.1-notes.rst | 16 +- docs/users_guide/glasgow_exts.rst | 13 +- docs/users_guide/using-warnings.rst | 18 +- ghc/GhciMonad.hs | 14 +- ghc/InteractiveUI.hs | 167 +++++++++++------- libraries/base/GHC/ExecutionStack.hs | 5 +- libraries/base/GHC/ExecutionStack/Internal.hsc | 14 +- libraries/base/Text/ParserCombinators/ReadP.hs | 7 - libraries/base/Text/ParserCombinators/ReadPrec.hs | 5 - rts/LibdwPool.c | 19 +- rts/Pool.c | 41 +++-- rts/Pool.h | 10 +- testsuite/tests/cabal/cabal07/cabal07.stderr | 2 +- testsuite/tests/driver/T10970.stdout | 2 +- testsuite/tests/driver/T4437.hs | 1 + testsuite/tests/ghci/scripts/T10248.stderr | 0 .../tests/indexed-types/should_fail/T11136.hs | 7 + .../tests/indexed-types/should_fail/T11136.stderr | 5 + testsuite/tests/indexed-types/should_fail/all.T | 1 + testsuite/tests/package/package01e.stderr | 4 +- testsuite/tests/quasiquotation/qq008/Test.hs | 2 +- testsuite/tests/quasiquotation/qq008/qq008.stderr | 4 - testsuite/tests/quotes/T10384.hs | 2 +- testsuite/tests/quotes/all.T | 2 +- .../safeHaskell/safeLanguage/SafeLang12.stderr | 11 +- testsuite/tests/{ado => semigroup}/Makefile | 0 testsuite/tests/semigroup/SemigroupWarnings.hs | 34 ++++ testsuite/tests/semigroup/SemigroupWarnings.stderr | 8 + testsuite/tests/semigroup/all.T | 1 + .../should_fail/CustomTypeErrors02.stderr | 4 +- .../tests/wcompat-warnings/WCompatWarningsNotOn.hs | 2 + .../tests/wcompat-warnings/WCompatWarningsOff.hs | 2 + .../tests/wcompat-warnings/WCompatWarningsOn.hs | 2 + .../wcompat-warnings/WCompatWarningsOn.stderr | 6 +- .../tests/wcompat-warnings/WCompatWarningsOnOff.hs | 2 + utils/ghc-pkg/Main.hs | 2 + utils/mkUserGuidePart/Options/Language.hs | 7 + utils/mkUserGuidePart/Options/Warnings.hs | 11 +- 52 files changed, 681 insertions(+), 187 deletions(-) diff --cc compiler/hsSyn/HsTypes.hs index 9134f39,eda643c..228df71 --- a/compiler/hsSyn/HsTypes.hs +++ b/compiler/hsSyn/HsTypes.hs @@@ -87,6 -86,13 +87,13 @@@ import Maybes( isJust import Data.Data hiding ( Fixity ) import Data.Maybe ( fromMaybe ) + #if __GLASGOW_HASKELL__ < 709 -import Data.Monoid hiding ((<>)) ++import Data.Monoid hiding((<>)) + #endif -#if __GLASGOW_HASKELL__ > 710 ++#if __GLASGOW_HASKELL > 710 + import Data.Semigroup ( Semigroup ) + import qualified Data.Semigroup as Semigroup + #endif {- ************************************************************************ @@@ -205,17 -164,34 +212,26 @@@ data LHsQTyVars name -- See Note [HsT -- See Note [HsForAllTy tyvar binders] } deriving( Typeable ) -deriving instance (DataId name) => Data (LHsTyVarBndrs name) -mkHsQTvs :: [LHsTyVarBndr RdrName] -> LHsTyVarBndrs RdrName --- Just at RdrName because in the Name variant we should know just --- what the kind-variable binders are; and we don't --- We put an empty list (rather than a panic) for the kind vars so --- that the pretty printer works ok on them. -mkHsQTvs tvs = HsQTvs { hsq_kvs = [], hsq_tvs = tvs } +deriving instance (DataId name) => Data (LHsQTyVars name) -emptyHsQTvs :: LHsTyVarBndrs name -- Use only when you know there are no kind binders -emptyHsQTvs = HsQTvs { hsq_kvs = [], hsq_tvs = [] } +mkHsQTvs :: [LHsTyVarBndr RdrName] -> LHsQTyVars RdrName +mkHsQTvs tvs = HsQTvs { hsq_kvs = PlaceHolder, hsq_tvs = tvs } -hsQTvBndrs :: LHsTyVarBndrs name -> [LHsTyVarBndr name] +hsQTvBndrs :: LHsQTyVars name -> [LHsTyVarBndr name] hsQTvBndrs = hsq_tvs -#if __GLASGOW_HASKELL__ > 710 + instance Semigroup (LHsTyVarBndrs name) where + HsQTvs kvs1 tvs1 <> HsQTvs kvs2 tvs2 + = HsQTvs (kvs1 ++ kvs2) (tvs1 ++ tvs2) -#endif + + instance Monoid (LHsTyVarBndrs name) where + mempty = emptyHsQTvs + mappend (HsQTvs kvs1 tvs1) (HsQTvs kvs2 tvs2) + = HsQTvs (kvs1 ++ kvs2) (tvs1 ++ tvs2) + ------------------------------------------------ --- HsWithBndrs +-- HsImplicitBndrs -- Used to quantify the binders of a type in cases -- when a HsForAll isn't appropriate: -- * Patterns in a type/data family instance (HsTyPats) diff --cc compiler/rename/RnSplice.hs index 8c84e3d,2093312..3c7695b --- a/compiler/rename/RnSplice.hs +++ b/compiler/rename/RnSplice.hs @@@ -44,7 -45,7 +44,6 @@@ import Hook import Var ( Id ) import THNames ( quoteExpName, quotePatName, quoteDecName, quoteTypeName , decsQTyConName, expQTyConName, patQTyConName, typeQTyConName, ) - import Util -import RnTypes ( collectWildCards ) import {-# SOURCE #-} TcExpr ( tcMonoExpr ) import {-# SOURCE #-} TcSplice ( runMetaD, runMetaE, runMetaP, runMetaT, tcTopSpliceExpr ) From git at git.haskell.org Tue Dec 1 12:59:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 1 Dec 2015 12:59:38 +0000 (UTC) Subject: [commit: ghc] wip/spj-wildcard-refactor: Wibbles (57b995b) Message-ID: <20151201125938.6018C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/spj-wildcard-refactor Link : http://ghc.haskell.org/trac/ghc/changeset/57b995b83bc6f3483c0322fc13043e73e7f7e4ee/ghc >--------------------------------------------------------------- commit 57b995b83bc6f3483c0322fc13043e73e7f7e4ee Author: Simon Peyton Jones Date: Tue Dec 1 12:47:13 2015 +0000 Wibbles >--------------------------------------------------------------- 57b995b83bc6f3483c0322fc13043e73e7f7e4ee compiler/hsSyn/HsTypes.hs | 32 +++++++++++++++------- compiler/rename/RnTypes.hs | 22 --------------- testsuite/tests/ghci/scripts/T10248.stderr | 30 +++++++++----------- .../should_fail/CustomTypeErrors02.stderr | 2 +- .../wcompat-warnings/WCompatWarningsOn.stderr | 2 +- 5 files changed, 37 insertions(+), 51 deletions(-) diff --git a/compiler/hsSyn/HsTypes.hs b/compiler/hsSyn/HsTypes.hs index 228df71..f7883f2 100644 --- a/compiler/hsSyn/HsTypes.hs +++ b/compiler/hsSyn/HsTypes.hs @@ -88,7 +88,8 @@ import Maybes( isJust ) import Data.Data hiding ( Fixity ) import Data.Maybe ( fromMaybe ) #if __GLASGOW_HASKELL__ < 709 -import Data.Monoid hiding((<>)) +-- SPJ temp +-- import Data.Monoid hiding((<>)) #endif #if __GLASGOW_HASKELL > 710 import Data.Semigroup ( Semigroup ) @@ -202,7 +203,7 @@ type LHsKind name = Located (HsKind name) -------------------------------------------------- -- LHsQTyVars -- The explicitly-quantified binders in a data/type declaration - +SQua type LHsTyVarBndr name = Located (HsTyVarBndr name) -- See Note [HsType binders] @@ -221,14 +222,18 @@ mkHsQTvs tvs = HsQTvs { hsq_kvs = PlaceHolder, hsq_tvs = tvs } hsQTvBndrs :: LHsQTyVars name -> [LHsTyVarBndr name] hsQTvBndrs = hsq_tvs +{- +#if __GLASGOW_HASKELL__ > 710 instance Semigroup (LHsTyVarBndrs name) where HsQTvs kvs1 tvs1 <> HsQTvs kvs2 tvs2 = HsQTvs (kvs1 ++ kvs2) (tvs1 ++ tvs2) +#endif -instance Monoid (LHsTyVarBndrs name) where - mempty = emptyHsQTvs +instance Monoid (LHsQTyVars name) where + mempty = mkHsQTvs [] mappend (HsQTvs kvs1 tvs1) (HsQTvs kvs2 tvs2) = HsQTvs (kvs1 ++ kvs2) (tvs1 ++ tvs2) +-} ------------------------------------------------ -- HsImplicitBndrs @@ -247,12 +252,19 @@ data HsImplicitBndrs name thing -- See Note [HsType binders] deriving (Typeable) data HsWildCardBndrs name thing -- See Note [HsType binders] - = HsWC { hswc_wcs :: PostRn name [Name] -- Wild cards - , hswc_ctx :: Maybe SrcSpan -- Indicates whether hswc_body has an - -- extra-constraint wildcard, and if so where - -- e.g. (Eq a, _) => a -> a - -- NB: the wildcard stays in the type - , hswc_body :: thing } -- Main payload (type or list of types) + = HsWC { hswc_wcs :: PostRn name [Name] + -- Wild cards, both named and anonymous + + , hswc_ctx :: Maybe SrcSpan + -- Indicates whether hswc_body has an + -- extra-constraint wildcard, and if so where + -- e.g. (Eq a, _) => a -> a + -- NB: the wildcard stays in HsQualTy inside the type! + -- So for pretty printing purposes you can ignore + -- hswc_ctx + + , hswc_body :: thing -- Main payload (type or list of types) + } deriving( Typeable ) deriving instance (Data name, Data thing, Data (PostRn name [Name])) diff --git a/compiler/rename/RnTypes.hs b/compiler/rename/RnTypes.hs index 90aa942..49b707c 100644 --- a/compiler/rename/RnTypes.hs +++ b/compiler/rename/RnTypes.hs @@ -178,28 +178,6 @@ rnWcSigContext ctxt (L loc hs_ctxt) , hswc_ctx = Nothing , hswc_body = L loc hs_ctxt' }, fvs) } -{- Note [Error checkingp for wildcards] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -Here is how various wildcard-related errors are reported - -* Named extra-constraints wild cards aren't allowed, - e.g. invalid: @(Show a, _x) => a -> String at . - -* There is only one extra-constraints wild card in the context and it must - come last, e.g. invalid: @(_, Show a) => a -> String@ - or @(_, Show a, _) => a -> String at . - -* There should be no unnamed wild cards in the context. - -* An extra-constraints wild card can only occur in the top-level context. - This would be invalid: @(Eq a, _) => a -> (Num a, _) => a -> Bool at . - -* Named wild cards occurring in the context must also occur in the monotype. - -When an invalid wild card is found, we fail with an error. - -????? What about f :: (forall a. (Eq _) => a -> a -> Bool) -> Int --} {- ****************************************************** * * diff --git a/testsuite/tests/ghci/scripts/T10248.stderr b/testsuite/tests/ghci/scripts/T10248.stderr index 9235aec..c9df22b 100644 --- a/testsuite/tests/ghci/scripts/T10248.stderr +++ b/testsuite/tests/ghci/scripts/T10248.stderr @@ -1,18 +1,14 @@ -:2:10: warning: - Found hole: _ :: IO () - In the second argument of ?(<$>)?, namely ?_? - In the first argument of ?ghciStepIO :: - forall a. IO a -> IO a?, namely - ?Just <$> _? - In a stmt of an interactive GHCi command: - it <- ghciStepIO :: forall a. IO a -> IO a (Just <$> _) -*** Exception: :2:10: error: - Found hole: _ :: IO () - In the second argument of ?(<$>)?, namely ?_? - In the first argument of ?ghciStepIO :: - forall a. IO a -> IO a?, namely - ?Just <$> _? - In a stmt of an interactive GHCi command: - it <- ghciStepIO :: forall a. IO a -> IO a (Just <$> _) -(deferred type error) +:2:10: error: + ? Found hole: _ :: f a + Where: ?f? is a rigid type variable bound by + the inferred type of it :: Functor f => f (Maybe a) + at :2:1 + ?a? is a rigid type variable bound by + the inferred type of it :: Functor f => f (Maybe a) + at :2:1 + ? In the second argument of ?(<$>)?, namely ?_? + In the expression: Just <$> _ + In an equation for ?it?: it = Just <$> _ + ? Relevant bindings include + it :: f (Maybe a) (bound at :2:1) diff --git a/testsuite/tests/typecheck/should_fail/CustomTypeErrors02.stderr b/testsuite/tests/typecheck/should_fail/CustomTypeErrors02.stderr index 02ae259..464c62d 100644 --- a/testsuite/tests/typecheck/should_fail/CustomTypeErrors02.stderr +++ b/testsuite/tests/typecheck/should_fail/CustomTypeErrors02.stderr @@ -1,7 +1,7 @@ CustomTypeErrors02.hs:17:1: error: ? The type 'a_aEN -> a_aEN' cannot be represented as an integer. - ? When checking that ?err? has the inferred type + ? When checking the inferred type err :: (TypeError ...) CustomTypeErrors02.hs:17:7: error: diff --git a/testsuite/tests/wcompat-warnings/WCompatWarningsOn.stderr b/testsuite/tests/wcompat-warnings/WCompatWarningsOn.stderr index 23d1a28..7b6b501 100644 --- a/testsuite/tests/wcompat-warnings/WCompatWarningsOn.stderr +++ b/testsuite/tests/wcompat-warnings/WCompatWarningsOn.stderr @@ -6,7 +6,7 @@ WCompatWarningsOn.hs:11:5: warning: from the context: Monad m bound by the type signature for: monadFail :: Monad m => m a - at WCompatWarningsOn.hs:9:14-27 + at WCompatWarningsOn.hs:9:1-27 Possible fix: add (MonadFail m) to the context of the type signature for: From git at git.haskell.org Tue Dec 1 12:59:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 1 Dec 2015 12:59:41 +0000 (UTC) Subject: [commit: ghc] wip/spj-wildcard-refactor: Merge remote-tracking branch 'origin/master' into wip/spj-wildcard-refactor (744d4b0) Message-ID: <20151201125941.C093E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/spj-wildcard-refactor Link : http://ghc.haskell.org/trac/ghc/changeset/744d4b0086f9aac866b98227158a41125153e1e4/ghc >--------------------------------------------------------------- commit 744d4b0086f9aac866b98227158a41125153e1e4 Merge: 57b995b 6dce643 Author: Simon Peyton Jones Date: Tue Dec 1 12:48:32 2015 +0000 Merge remote-tracking branch 'origin/master' into wip/spj-wildcard-refactor >--------------------------------------------------------------- 744d4b0086f9aac866b98227158a41125153e1e4 compiler/basicTypes/MkId.hs | 12 +++++----- compiler/hsSyn/HsTypes.hs | 2 +- compiler/typecheck/TcTyDecls.hs | 6 ++--- ghc.mk | 17 +++++--------- mk/config.mk.in | 49 +++++++++++++++++++++++++++++++++-------- mk/warnings.mk | 44 ++++++++++++++++++++++++++++-------- rules/distdir-way-opts.mk | 19 +++++++++++++++- utils/mkUserGuidePart/Main.hs | 5 ----- 8 files changed, 108 insertions(+), 46 deletions(-) diff --cc compiler/hsSyn/HsTypes.hs index f7883f2,eda643c..ed4c3be --- a/compiler/hsSyn/HsTypes.hs +++ b/compiler/hsSyn/HsTypes.hs @@@ -201,14 -153,13 +201,14 @@@ type LHsKind name = Located (HsKind nam -- For details on above see note [Api annotations] in ApiAnnotation -------------------------------------------------- --- LHsTyVarBndrs --- The quantified binders in a HsForallTy +-- LHsQTyVars +-- The explicitly-quantified binders in a data/type declaration - SQua + type LHsTyVarBndr name = Located (HsTyVarBndr name) + -- See Note [HsType binders] -data LHsTyVarBndrs name - = HsQTvs { hsq_kvs :: [Name] -- Kind variables +data LHsQTyVars name -- See Note [HsType binders] + = HsQTvs { hsq_kvs :: PostRn name [Name] -- Kind variables , hsq_tvs :: [LHsTyVarBndr name] -- Type variables -- See Note [HsForAllTy tyvar binders] } From git at git.haskell.org Tue Dec 1 12:59:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 1 Dec 2015 12:59:44 +0000 (UTC) Subject: [commit: ghc] wip/spj-wildcard-refactor's head updated: Merge remote-tracking branch 'origin/master' into wip/spj-wildcard-refactor (744d4b0) Message-ID: <20151201125944.168BE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/spj-wildcard-refactor' now includes: c4308b4 rts/Pool: Add poolTryTake 1712a9e LibdwPool: Use poolTryTake ba14f04 Libdw: Handle failure to grab session for location lookup d25f853 Update transformers submodule 49aae12 Check arity on default decl for assoc types 583867b Update haskeline & terminfo submodules 85fcd03 Implement new -XTemplateHaskellQuotes pragma 72e3620 ghci: Add support for prompt functions 55c737f ghc-pkg: print version when verbose 399a5b4 Remove deprecated quasiquoter syntax. 71c0cc1 GHCi should not defer typed holes 54a9456 Update containers submodule 616aceb Update deepseq submodule 5897213 Remove redundant `#if`s f101a82 ghci: Refactor handling of :show bcd55a9 Some improvements on CoreToDos passed to plugins 290def7 Implement warnings for Semigroups as parent of Monoid d5d2338 Merge remote-tracking branch 'origin/master' into wip/spj-wildcard-refactor afb7213 MkId: Typos in comments 14d0f7f Build system: Add stage specific SRC_HC_(WARNING_)OPTS 6dce643 Fix grammar and typo in TcTyDecls 57b995b Wibbles 744d4b0 Merge remote-tracking branch 'origin/master' into wip/spj-wildcard-refactor From git at git.haskell.org Tue Dec 1 14:22:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 1 Dec 2015 14:22:43 +0000 (UTC) Subject: [commit: ghc] wip/T11028: Refactor ConDecl (410b647) Message-ID: <20151201142243.B30E33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T11028 Link : http://ghc.haskell.org/trac/ghc/changeset/410b6477ce9396555900b46f740515a432171524/ghc >--------------------------------------------------------------- commit 410b6477ce9396555900b46f740515a432171524 Author: Alan Zimmerman Date: Mon Nov 23 22:59:27 2015 +0200 Refactor ConDecl The ConDecl type in HsDecls is an uneasy compromise. For the most part, HsSyn directly reflects the syntax written by the programmer; and that gives just the right "pegs" on which to hang Alan's API annotations. But ConDecl doesn't properly reflect the syntax of Haskell-98 and GADT-style data type declarations. To be concrete, here's a draft new data type data ConDecl name | ConDeclGADT { con_names :: [Located name] , con_type :: LHsSigType name -- The type after the ?::? , con_doc :: Maybe LHsDocString } | ConDeclH98 { con_name :: Located name , con_qvars :: Maybe (LHsQTyVars name) -- User-written forall (if any), and its implicit -- kind variables -- Non-Nothing needs -XExistentialQuantification , con_cxt :: Maybe (LHsContext name) -- ^ User-written context (if any) , con_details :: HsConDeclDetails name -- ^ Arguments , con_doc :: Maybe LHsDocString -- ^ A possible Haddock comment. } deriving (Typeable) Note that For GADTs, just keep a type. That's what the user writes. NB:HsType can represent records on the LHS of an arrow: { x:Int,y:Bool} -> T con_qvars and con_cxt are both Maybe because they are both optional (the forall and the context of an existential data type For ConDeclGADT the type variables of the data type do not scope over the con_type; whereas for ConDeclH98 they do scope over con_cxt and con_details. Trac issue: #11028 >--------------------------------------------------------------- 410b6477ce9396555900b46f740515a432171524 compiler/deSugar/DsMeta.hs | 89 ++++++++-- compiler/hsSyn/Convert.hs | 17 +- compiler/hsSyn/HsDecls.hs | 133 +++++--------- compiler/hsSyn/HsTypes.hs | 4 +- compiler/hsSyn/HsUtils.hs | 19 +- compiler/parser/Parser.y | 12 +- compiler/parser/RdrHsSyn.hs | 72 +++----- compiler/rename/RnEnv.hs | 4 +- compiler/rename/RnNames.hs | 11 +- compiler/rename/RnSource.hs | 120 +++++-------- compiler/rename/RnTypes.hs | 22 ++- compiler/typecheck/TcHsType.hs | 9 +- compiler/typecheck/TcRnDriver.hs | 2 +- compiler/typecheck/TcTyClsDecls.hs | 191 +++++++++++++++------ testsuite/tests/ghc-api/annotations/T10399.stdout | 2 - testsuite/tests/ghc-api/annotations/all.T | 2 +- testsuite/tests/ghc-api/landmines/landmines.stdout | 2 +- testsuite/tests/rename/should_compile/T5331.stderr | 2 +- testsuite/tests/rename/should_fail/T7943.stderr | 6 +- utils/haddock | 2 +- 20 files changed, 391 insertions(+), 330 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 410b6477ce9396555900b46f740515a432171524 From git at git.haskell.org Tue Dec 1 14:22:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 1 Dec 2015 14:22:46 +0000 (UTC) Subject: [commit: ghc] wip/T11028's head updated: Refactor ConDecl (410b647) Message-ID: <20151201142246.2E72A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T11028' now includes: c4308b4 rts/Pool: Add poolTryTake 1712a9e LibdwPool: Use poolTryTake ba14f04 Libdw: Handle failure to grab session for location lookup d25f853 Update transformers submodule 49aae12 Check arity on default decl for assoc types 583867b Update haskeline & terminfo submodules 85fcd03 Implement new -XTemplateHaskellQuotes pragma 72e3620 ghci: Add support for prompt functions 55c737f ghc-pkg: print version when verbose 399a5b4 Remove deprecated quasiquoter syntax. 71c0cc1 GHCi should not defer typed holes 54a9456 Update containers submodule 616aceb Update deepseq submodule 5897213 Remove redundant `#if`s f101a82 ghci: Refactor handling of :show bcd55a9 Some improvements on CoreToDos passed to plugins 290def7 Implement warnings for Semigroups as parent of Monoid d5d2338 Merge remote-tracking branch 'origin/master' into wip/spj-wildcard-refactor afb7213 MkId: Typos in comments 14d0f7f Build system: Add stage specific SRC_HC_(WARNING_)OPTS 6dce643 Fix grammar and typo in TcTyDecls 57b995b Wibbles 744d4b0 Merge remote-tracking branch 'origin/master' into wip/spj-wildcard-refactor 410b647 Refactor ConDecl From git at git.haskell.org Tue Dec 1 15:59:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 1 Dec 2015 15:59:36 +0000 (UTC) Subject: [commit: ghc] master: Fix warning about unused pattern variable (44c3e37) Message-ID: <20151201155936.345F13A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/44c3e3768e28199468d2ffff0b25db055d22c310/ghc >--------------------------------------------------------------- commit 44c3e3768e28199468d2ffff0b25db055d22c310 Author: Gabor Greif Date: Tue Dec 1 16:59:39 2015 +0100 Fix warning about unused pattern variable >--------------------------------------------------------------- 44c3e3768e28199468d2ffff0b25db055d22c310 utils/deriveConstants/Main.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/deriveConstants/Main.hs b/utils/deriveConstants/Main.hs index 09c94ab..6a88ac2 100644 --- a/utils/deriveConstants/Main.hs +++ b/utils/deriveConstants/Main.hs @@ -786,7 +786,7 @@ getWanted verbose os tmpdir gccProgram gccFlags nmProgram mobjdumpProgram , Just sym <- stripPrefix prefix sym0 = Just (sym, read n) | otherwise = Nothing where - [sym0, adr] = take 2 (reverse $ words l1) + [sym0, _] = take 2 (reverse $ words l1) -- If an Int value is larger than 2^28 or smaller -- than -2^28, then fail. From git at git.haskell.org Tue Dec 1 15:59:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 1 Dec 2015 15:59:33 +0000 (UTC) Subject: [commit: ghc] master: Remove duplicated line (36c1247) Message-ID: <20151201155933.900CF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/36c1247846bbbc1af939c098660ce27ddaa36a0d/ghc >--------------------------------------------------------------- commit 36c1247846bbbc1af939c098660ce27ddaa36a0d Author: Gabor Greif Date: Wed Oct 28 08:27:58 2015 +0100 Remove duplicated line >--------------------------------------------------------------- 36c1247846bbbc1af939c098660ce27ddaa36a0d compiler/ghc.mk | 1 - 1 file changed, 1 deletion(-) diff --git a/compiler/ghc.mk b/compiler/ghc.mk index b75fdc2..74cbd29 100644 --- a/compiler/ghc.mk +++ b/compiler/ghc.mk @@ -457,7 +457,6 @@ compiler_stage1_MUNGED_VERSION = $(subst .$(ProjectPatchLevel),,$(ProjectVersion define compiler_PACKAGE_MAGIC compiler_stage1_VERSION = $(compiler_stage1_MUNGED_VERSION) compiler_stage1_COMPONENT_ID = $(subst .$(ProjectPatchLevel),,$(compiler_stage1_COMPONENT_ID)) -compiler_stage1_COMPONENT_ID = $(subst .$(ProjectPatchLevel),,$(compiler_stage1_COMPONENT_ID)) endef # NB: the COMPONENT_ID munging has no effect for new-style unit ids From git at git.haskell.org Tue Dec 1 16:58:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 1 Dec 2015 16:58:29 +0000 (UTC) Subject: [commit: ghc] master: Make the determinism tests more robust (b432e2f) Message-ID: <20151201165829.1368A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b432e2f39c095d8acbb0cfcc63bd08436c7a3e49/ghc >--------------------------------------------------------------- commit b432e2f39c095d8acbb0cfcc63bd08436c7a3e49 Author: Bartosz Nitka Date: Tue Dec 1 07:42:35 2015 -0800 Make the determinism tests more robust The tests weren't explicit enough about comparing under different unique allocation strategies. This led to some confusion on my part when I started overriding flags in `testsuite/mk/test.mk`. Includes a `.gitignore` rule. Test Plan: harbormaster Reviewers: austin, simonmar, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1555 >--------------------------------------------------------------- b432e2f39c095d8acbb0cfcc63bd08436c7a3e49 testsuite/.gitignore | 3 ++- testsuite/tests/determinism/determ003/Makefile | 2 +- testsuite/tests/determinism/typecheck/Makefile | 2 +- 3 files changed, 4 insertions(+), 3 deletions(-) diff --git a/testsuite/.gitignore b/testsuite/.gitignore index b8493f5..dee9012 100644 --- a/testsuite/.gitignore +++ b/testsuite/.gitignore @@ -471,6 +471,7 @@ mk/ghcconfig*_test___spaces_ghc*.exe.mk /tests/deriving/should_run/drvrun019 /tests/deriving/should_run/drvrun020 /tests/deriving/should_run/drvrun021 +/tests/determinism/determinism001 /tests/dph/classes/dph-classes-copy-fast /tests/dph/classes/dph-classes-fast /tests/dph/classes/dph-classes-vseg-fast @@ -1175,6 +1176,7 @@ mk/ghcconfig*_test___spaces_ghc*.exe.mk /tests/perf/should_run/InlineCloneArrayAlloc /tests/perf/should_run/MethSharing /tests/perf/should_run/MethSharing.stats +/tests/perf/should_run/T10359 /tests/perf/should_run/T149_A /tests/perf/should_run/T149_B /tests/perf/should_run/T2902_A @@ -1221,7 +1223,6 @@ mk/ghcconfig*_test___spaces_ghc*.exe.mk /tests/perf/should_run/T876 /tests/perf/should_run/T9203 /tests/perf/should_run/T9339 -/tests/perf/should_run/T10359 /tests/perf/should_run/lazy-bs-alloc /tests/perf/should_run/lazy-bs-alloc.stats /tests/perf/should_run/speed.f32 diff --git a/testsuite/tests/determinism/determ003/Makefile b/testsuite/tests/determinism/determ003/Makefile index 73231a0..bab18e8 100644 --- a/testsuite/tests/determinism/determ003/Makefile +++ b/testsuite/tests/determinism/determ003/Makefile @@ -6,7 +6,7 @@ TEST_HC_OPTS_NO_RECOMP = $(filter-out -fforce-recomp,$(TEST_HC_OPTS)) determ003: $(RM) A.hi A.o - '$(TEST_HC)' $(TEST_HC_OPTS_NO_RECOMP) -O A.hs + '$(TEST_HC)' $(TEST_HC_OPTS_NO_RECOMP) -O -dinitial-unique=0 -dunique-increment=1 A.hs $(CP) A.hi A.normal.hi $(RM) A.hi A.o '$(TEST_HC)' $(TEST_HC_OPTS_NO_RECOMP) -O -dinitial-unique=16777215 -dunique-increment=-1 A.hs diff --git a/testsuite/tests/determinism/typecheck/Makefile b/testsuite/tests/determinism/typecheck/Makefile index f95bfc5..ac98ea1 100644 --- a/testsuite/tests/determinism/typecheck/Makefile +++ b/testsuite/tests/determinism/typecheck/Makefile @@ -6,7 +6,7 @@ TEST_HC_OPTS_NO_RECOMP = $(filter-out -fforce-recomp,$(TEST_HC_OPTS)) determ005: $(RM) A.hi A.o - '$(TEST_HC)' $(TEST_HC_OPTS_NO_RECOMP) -O A.hs + '$(TEST_HC)' $(TEST_HC_OPTS_NO_RECOMP) -dinitial-unique=0 -dunique-increment=1 -O A.hs $(CP) A.hi A.old.hi $(RM) A.o '$(TEST_HC)' $(TEST_HC_OPTS_NO_RECOMP) -dinitial-unique=16777206 -dunique-increment=-1 -O A.hs From git at git.haskell.org Tue Dec 1 17:15:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 1 Dec 2015 17:15:39 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: Overloaded literals (f62b371) Message-ID: <20151201171539.399C33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/f62b371a1f6e94323cf56ecaa8ce832da97bb5d2/ghc >--------------------------------------------------------------- commit f62b371a1f6e94323cf56ecaa8ce832da97bb5d2 Author: George Karachalias Date: Mon Nov 30 16:49:03 2015 +0100 Overloaded literals >--------------------------------------------------------------- f62b371a1f6e94323cf56ecaa8ce832da97bb5d2 compiler/deSugar/Check.hs | 57 ++++++++++++++---- compiler/deSugar/TmOracle.hs | 79 ++++++++++++++++++++++++- testsuite/tests/deSugar/should_compile/ds022.hs | 2 + 3 files changed, 123 insertions(+), 15 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc f62b371a1f6e94323cf56ecaa8ce832da97bb5d2 From git at git.haskell.org Tue Dec 1 17:15:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 1 Dec 2015 17:15:41 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: documented the **HACK** (0cdbf4d) Message-ID: <20151201171541.D9F223A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/0cdbf4d08fdc9728d28e0a954763a51250a463c8/ghc >--------------------------------------------------------------- commit 0cdbf4d08fdc9728d28e0a954763a51250a463c8 Author: George Karachalias Date: Tue Dec 1 12:40:14 2015 +0100 documented the **HACK** >--------------------------------------------------------------- 0cdbf4d08fdc9728d28e0a954763a51250a463c8 compiler/deSugar/Check.hs | 35 ++++++----- compiler/deSugar/TmOracle.hs | 139 +++++++++++++++++++++++++++++++++++++++---- 2 files changed, 147 insertions(+), 27 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 0cdbf4d08fdc9728d28e0a954763a51250a463c8 From git at git.haskell.org Tue Dec 1 17:15:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 1 Dec 2015 17:15:44 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: fixed ds022 stderr (0ae502d) Message-ID: <20151201171544.823833A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/0ae502dafffe64a6f664875657ff36153700422e/ghc >--------------------------------------------------------------- commit 0ae502dafffe64a6f664875657ff36153700422e Author: George Karachalias Date: Tue Dec 1 12:48:05 2015 +0100 fixed ds022 stderr >--------------------------------------------------------------- 0ae502dafffe64a6f664875657ff36153700422e testsuite/tests/deSugar/should_compile/ds022.stderr | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/deSugar/should_compile/ds022.stderr b/testsuite/tests/deSugar/should_compile/ds022.stderr index 45fe3d8..17b62fe 100644 --- a/testsuite/tests/deSugar/should_compile/ds022.stderr +++ b/testsuite/tests/deSugar/should_compile/ds022.stderr @@ -1,6 +1,6 @@ -ds022.hs:20:1: Warning: - Pattern match(es) are overlapped +ds022.hs:22:1: Warning: + Pattern match(es) are redundant In an equation for ?i?: i 1 0.011e2 = ... i 2 2.20000 = ... From git at git.haskell.org Tue Dec 1 17:15:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 1 Dec 2015 17:15:47 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: more documentation on guard approximation (e7d0a00) Message-ID: <20151201171547.35DF13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/e7d0a0080fa3781fc24c13d47c0f7612a9c5ccad/ghc >--------------------------------------------------------------- commit e7d0a0080fa3781fc24c13d47c0f7612a9c5ccad Author: George Karachalias Date: Tue Dec 1 18:08:57 2015 +0100 more documentation on guard approximation >--------------------------------------------------------------- e7d0a0080fa3781fc24c13d47c0f7612a9c5ccad compiler/deSugar/Check.hs | 138 +++++++++++++++++++++++++++++++++++++++------- 1 file changed, 117 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 e7d0a0080fa3781fc24c13d47c0f7612a9c5ccad From git at git.haskell.org Tue Dec 1 17:45:08 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 1 Dec 2015 17:45:08 +0000 (UTC) Subject: [commit: ghc] master: Refactor treatment of wildcards (1e041b7) Message-ID: <20151201174508.D478C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1e041b7382b6aa329e4ad9625439f811e0f27232/ghc >--------------------------------------------------------------- commit 1e041b7382b6aa329e4ad9625439f811e0f27232 Author: Simon Peyton Jones Date: Tue Dec 1 17:38:23 2015 +0100 Refactor treatment of wildcards This patch began as a modest refactoring of HsType and friends, to clarify and tidy up exactly where quantification takes place in types. Although initially driven by making the implementation of wildcards more tidy (and fixing a number of bugs), I gradually got drawn into a pretty big process, which I've been doing on and off for quite a long time. There is one compiler performance regression as a result of all this, in perf/compiler/T3064. I still need to look into that. * The principal driving change is described in Note [HsType binders] in HsType. Well worth reading! * Those data type changes drive almost everything else. In particular we now statically know where (a) implicit quantification only (LHsSigType), e.g. in instance declaratios and SPECIALISE signatures (b) implicit quantification and wildcards (LHsSigWcType) can appear, e.g. in function type signatures * As part of this change, HsForAllTy is (a) simplified (no wildcards) and (b) split into HsForAllTy and HsQualTy. The two contructors appear when and only when the correponding user-level construct appears. Again see Note [HsType binders]. HsExplicitFlag disappears altogether. * Other simplifications - ExprWithTySig no longer needs an ExprWithTySigOut variant - TypeSig no longer needs a PostRn name [name] field for wildcards - PatSynSig records a LHsSigType rather than the decomposed pieces - The mysterious 'GenericSig' is now 'ClassOpSig' * Renamed LHsTyVarBndrs to LHsQTyVars * There are some uninteresting knock-on changes in Haddock, because of the HsSyn changes I also did a bunch of loosely-related changes: * We already had type synonyms CoercionN/CoercionR for nominal and representational coercions. I've added similar treatment for TcCoercionN/TcCoercionR mkWpCastN/mkWpCastN All just type synonyms but jolly useful. * I record-ised ForeignImport and ForeignExport * I improved the (poor) fix to Trac #10896, by making TcTyClsDecls.checkValidTyCl recover from errors, but adding a harmless, abstract TyCon to the envt if so. * I did some significant refactoring in RnEnv.lookupSubBndrOcc, for reasons that I have (embarrassingly) now totally forgotten. It had to do with something to do with import and export Updates haddock submodule. >--------------------------------------------------------------- 1e041b7382b6aa329e4ad9625439f811e0f27232 compiler/basicTypes/RdrName.hs | 3 +- compiler/deSugar/Coverage.hs | 13 +- compiler/deSugar/DsArrows.hs | 2 +- compiler/deSugar/DsBinds.hs | 8 +- compiler/deSugar/DsExpr.hs | 2 +- compiler/deSugar/DsForeign.hs | 6 +- compiler/deSugar/DsMeta.hs | 184 ++-- compiler/ghc.mk | 2 - compiler/hsSyn/Convert.hs | 78 +- compiler/hsSyn/HsBinds.hs | 73 +- compiler/hsSyn/HsDecls.hs | 140 +-- compiler/hsSyn/HsExpr.hs | 48 +- compiler/hsSyn/HsPat.hs | 8 +- compiler/hsSyn/HsSyn.hs | 2 +- compiler/hsSyn/HsTypes.hs | 502 ++++++----- compiler/hsSyn/HsUtils.hs | 112 +-- compiler/iface/IfaceSyn.hs | 29 +- compiler/main/HscStats.hs | 16 +- compiler/main/HscTypes.hs | 2 + compiler/parser/Lexer.x | 14 +- compiler/parser/Parser.y | 230 ++--- compiler/parser/RdrHsSyn.hs | 156 ++-- compiler/prelude/PrelNames.hs | 4 +- compiler/rename/RnBinds.hs | 131 ++- compiler/rename/RnEnv.hs | 261 +++--- compiler/rename/RnExpr.hs | 49 +- compiler/rename/RnNames.hs | 8 +- compiler/rename/RnPat.hs | 10 +- compiler/rename/RnSource.hs | 234 ++--- compiler/rename/RnSplice.hs | 33 +- compiler/rename/RnTypes.hs | 976 +++++++++++---------- compiler/typecheck/TcArrows.hs | 2 +- compiler/typecheck/TcBinds.hs | 462 ++++++---- compiler/typecheck/TcClassDcl.hs | 20 +- compiler/typecheck/TcDefaults.hs | 2 +- compiler/typecheck/TcDeriv.hs | 21 +- compiler/typecheck/TcEnv.hs | 25 +- compiler/typecheck/TcErrors.hs | 63 +- compiler/typecheck/TcEvidence.hs | 29 +- compiler/typecheck/TcExpr.hs | 194 ++-- compiler/typecheck/TcForeign.hs | 24 +- compiler/typecheck/TcGenDeriv.hs | 29 +- compiler/typecheck/TcHsSyn.hs | 8 +- compiler/typecheck/TcHsType.hs | 379 ++++---- compiler/typecheck/TcInstDcls.hs | 42 +- compiler/typecheck/TcMType.hs | 40 +- compiler/typecheck/TcMatches.hs | 2 +- compiler/typecheck/TcPat.hs | 222 +---- compiler/typecheck/TcPatSyn.hs | 5 +- compiler/typecheck/TcPatSyn.hs-boot | 3 +- compiler/typecheck/TcRnDriver.hs | 42 +- compiler/typecheck/TcRnMonad.hs | 30 +- compiler/typecheck/TcRnTypes.hs | 248 +++++- compiler/typecheck/TcRules.hs | 33 +- compiler/typecheck/TcSMonad.hs | 16 +- compiler/typecheck/TcSimplify.hs | 67 +- compiler/typecheck/TcSplice.hs | 6 +- compiler/typecheck/TcTyClsDecls.hs | 45 +- compiler/typecheck/TcTyDecls.hs | 25 +- compiler/typecheck/TcType.hs | 30 +- compiler/typecheck/TcTypeable.hs | 8 +- compiler/typecheck/TcUnify.hs | 54 +- compiler/typecheck/TcValidity.hs | 52 +- compiler/types/Coercion.hs | 6 +- compiler/types/InstEnv.hs | 3 +- compiler/utils/Util.hs | 27 +- ghc/InteractiveUI.hs | 8 +- libraries/base/Data/Monoid.hs | 2 +- testsuite/tests/ado/ado005.stderr | 8 +- testsuite/tests/arrows/should_fail/T5380.stderr | 48 +- testsuite/tests/deriving/should_fail/T5287.stderr | 8 +- testsuite/tests/gadt/T3169.stderr | 28 +- testsuite/tests/gadt/T7558.stderr | 8 +- testsuite/tests/gadt/rw.stderr | 48 +- testsuite/tests/ghc-api/annotations/all.T | 2 +- testsuite/tests/ghc-api/landmines/landmines.stdout | 2 +- testsuite/tests/ghci/scripts/Defer02.stderr | 267 +++--- testsuite/tests/ghci/scripts/T10248.stderr | 16 +- testsuite/tests/ghci/scripts/T7873.stdout | 3 +- testsuite/tests/ghci/scripts/ghci050.stderr | 1 + .../should_compile/PushedInAsGivens.stderr | 51 +- .../tests/indexed-types/should_compile/Records.hs | 0 .../indexed-types/should_compile/Simple14.stderr | 17 +- .../indexed-types/should_compile/T3208b.stderr | 44 +- .../tests/indexed-types/should_fail/BadSock.hs | 0 .../indexed-types/should_fail/GADTwrong1.stderr | 24 +- .../indexed-types/should_fail/NoMatchErr.stderr | 7 +- .../indexed-types/should_fail/Overlap6.stderr | 23 +- .../indexed-types/should_fail/SimpleFail15.stderr | 5 +- .../indexed-types/should_fail/SimpleFail16.stderr | 2 +- .../indexed-types/should_fail/SimpleFail5a.stderr | 21 +- .../tests/indexed-types/should_fail/T1897b.stderr | 7 +- .../tests/indexed-types/should_fail/T1900.stderr | 5 +- .../tests/indexed-types/should_fail/T2693.stderr | 66 +- .../tests/indexed-types/should_fail/T3330a.stderr | 84 +- .../tests/indexed-types/should_fail/T3440.stderr | 39 +- .../tests/indexed-types/should_fail/T4093a.stderr | 24 +- .../tests/indexed-types/should_fail/T4093b.stderr | 75 +- .../tests/indexed-types/should_fail/T4174.stderr | 52 +- .../tests/indexed-types/should_fail/T4272.stderr | 29 +- .../tests/indexed-types/should_fail/T7194.stderr | 25 +- .../tests/indexed-types/should_fail/T9036.stderr | 8 +- .../tests/indexed-types/should_fail/T9171.stderr | 15 +- .../tests/indexed-types/should_fail/T9433.stderr | 2 +- .../tests/indexed-types/should_fail/T9662.stderr | 144 +-- testsuite/tests/module/mod98.stderr | 4 +- testsuite/tests/monadfail/MonadFailErrors.stderr | 2 +- testsuite/tests/monadfail/MonadFailWarnings.stderr | 104 +-- .../should_fail/overloadedlabelsfail01.stderr | 2 +- .../parser/should_fail/NoPatternSynonyms.stderr | 2 +- testsuite/tests/parser/should_fail/T3811.stderr | 4 +- testsuite/tests/parser/should_fail/T7848.stderr | 78 +- .../tests/parser/should_fail/readFail031.stderr | 4 +- .../should_compile/Defaulting2MROn.stderr | 2 +- .../partial-sigs/should_compile/ExprSigLocal.hs | 12 + .../should_compile/ExprSigLocal.stderr | 19 + .../should_compile/ExtraConstraints3.stderr | 14 +- .../should_compile/SomethingShowable.hs | 2 +- .../should_compile/SomethingShowable.stderr | 3 +- .../partial-sigs/should_compile/SplicesUsed.stderr | 108 ++- .../tests/partial-sigs/should_compile/T10403.hs | 1 + .../partial-sigs/should_compile/T10403.stderr | 91 +- .../partial-sigs/should_compile/T10438.stderr | 51 +- .../partial-sigs/should_compile/T10519.stderr | 4 +- .../WarningWildcardInstantiations.stderr | 65 +- testsuite/tests/partial-sigs/should_compile/all.T | 1 + .../partial-sigs/should_fail/Defaulting1MROff.hs | 2 + .../should_fail/Defaulting1MROff.stderr | 11 +- ...ConstraintsWildcardInExpressionSignature.stderr | 6 +- ...traConstraintsWildcardInPatternSignature.stderr | 6 +- .../ExtraConstraintsWildcardInTypeSplice2.hs | 2 +- .../ExtraConstraintsWildcardInTypeSplice2.stderr | 5 +- ...ExtraConstraintsWildcardInTypeSpliceUsed.stderr | 12 +- .../ExtraConstraintsWildcardNotEnabled.stderr | 4 +- .../ExtraConstraintsWildcardNotLast.stderr | 10 +- .../ExtraConstraintsWildcardNotPresent.stderr | 12 +- .../ExtraConstraintsWildcardTwice.stderr | 9 +- .../InstantiatedNamedWildcardsInConstraints.stderr | 17 +- .../NamedExtraConstraintsWildcard.stderr | 8 +- .../NamedWildcardInDataFamilyInstanceLHS.stderr | 4 +- .../NamedWildcardInTypeFamilyInstanceLHS.stderr | 4 +- .../should_fail/NamedWildcardInTypeSplice.stderr | 9 +- .../should_fail/NamedWildcardsEnabled.stderr | 20 +- .../should_fail/NamedWildcardsNotEnabled.stderr | 36 +- .../should_fail/NamedWildcardsNotInMonotype.hs | 2 +- .../should_fail/NamedWildcardsNotInMonotype.stderr | 16 +- .../NestedExtraConstraintsWildcard.stderr | 10 +- .../NestedNamedExtraConstraintsWildcard.stderr | 7 +- .../should_fail/PartialClassMethodSignature.stderr | 7 +- .../PartialClassMethodSignature2.stderr | 7 +- .../PartialTypeSignaturesDisabled.stderr | 20 +- .../tests/partial-sigs/should_fail/T10045.stderr | 43 +- .../tests/partial-sigs/should_fail/T10615.stderr | 52 +- testsuite/tests/partial-sigs/should_fail/T10999.hs | 2 +- .../tests/partial-sigs/should_fail/T10999.stderr | 24 +- .../partial-sigs/should_fail/TidyClash.stderr | 26 +- .../tests/partial-sigs/should_fail/Trac10045.hs | 8 - .../partial-sigs/should_fail/Trac10045.stderr | 46 - .../should_fail/UnnamedConstraintWildcard1.stderr | 9 +- .../should_fail/UnnamedConstraintWildcard2.stderr | 9 +- .../partial-sigs/should_fail/WildcardInADT1.stderr | 8 +- .../partial-sigs/should_fail/WildcardInADT2.stderr | 8 +- .../partial-sigs/should_fail/WildcardInADT3.stderr | 8 +- .../should_fail/WildcardInADTContext1.stderr | 8 +- .../should_fail/WildcardInADTContext2.stderr | 8 +- .../should_fail/WildcardInDefault.stderr | 7 +- .../should_fail/WildcardInDefaultSignature.stderr | 7 +- .../should_fail/WildcardInDeriving.stderr | 6 +- .../should_fail/WildcardInForeignExport.stderr | 8 +- .../should_fail/WildcardInForeignImport.stderr | 8 +- .../should_fail/WildcardInGADT1.stderr | 8 +- .../should_fail/WildcardInGADT2.stderr | 7 +- .../should_fail/WildcardInInstanceHead.stderr | 6 +- .../should_fail/WildcardInInstanceSig.stderr | 5 +- .../should_fail/WildcardInNewtype.stderr | 8 +- .../should_fail/WildcardInPatSynSig.stderr | 5 +- .../WildcardInStandaloneDeriving.stderr | 6 +- .../WildcardInTypeFamilyInstanceRHS.stderr | 8 +- .../should_fail/WildcardInTypeSynonymRHS.stderr | 7 +- .../should_fail/WildcardInstantiations.stderr | 75 +- testsuite/tests/partial-sigs/should_fail/all.T | 5 +- testsuite/tests/patsyn/should_fail/T9161-1.stderr | 5 +- testsuite/tests/patsyn/should_fail/T9161-2.stderr | 4 +- testsuite/tests/perf/compiler/T5837.stderr | 8 +- testsuite/tests/perf/compiler/all.T | 4 +- testsuite/tests/polykinds/PolyKinds02.stderr | 4 +- testsuite/tests/polykinds/T10503.stderr | 13 +- testsuite/tests/polykinds/T10516.stderr | 2 +- testsuite/tests/polykinds/T6021.stderr | 7 +- testsuite/tests/polykinds/T6068.hs | 4 +- testsuite/tests/polykinds/T7224.stderr | 5 +- testsuite/tests/polykinds/T7230.stderr | 54 +- testsuite/tests/polykinds/T7278.stderr | 4 +- testsuite/tests/polykinds/T7328.stderr | 5 +- testsuite/tests/polykinds/T7438.stderr | 1 + testsuite/tests/polykinds/T9222.stderr | 15 +- testsuite/tests/rename/should_compile/T4426.hs | 8 +- testsuite/tests/rename/should_compile/T4426.stderr | 51 +- testsuite/tests/rename/should_compile/T5331.stderr | 7 +- testsuite/tests/rename/should_compile/all.T | 2 +- testsuite/tests/rename/should_fail/T2901.stderr | 3 +- testsuite/tests/rename/should_fail/T5372.hs | 0 testsuite/tests/rename/should_fail/T5372.stderr | 6 +- .../tests/rename/should_fail/rnfail026.stderr | 6 +- .../tests/roles/should_fail/RolesIArray.stderr | 8 +- .../tests/simplCore/should_compile/T8848.stderr | 4 +- .../tests/simplCore/should_compile/T8848a.stderr | 2 +- .../tests/simplCore/should_compile/rule2.stderr | 2 +- testsuite/tests/th/T10267.stderr | 68 +- testsuite/tests/th/T3177a.stderr | 10 +- testsuite/tests/th/T8625.stdout | 2 +- testsuite/tests/th/TH_pragma.stderr | 0 .../tests/typecheck/should_compile/FD1.stderr | 15 +- .../tests/typecheck/should_compile/FD2.stderr | 32 +- .../tests/typecheck/should_compile/FD3.stderr | 23 +- .../tests/typecheck/should_compile/T10632.stderr | 5 +- .../tests/typecheck/should_compile/T7220a.stderr | 14 +- .../tests/typecheck/should_compile/T9834.stderr | 46 +- .../tests/typecheck/should_compile/T9939.stderr | 18 +- .../tests/typecheck/should_compile/tc141.stderr | 86 +- testsuite/tests/typecheck/should_compile/tc166.hs | 0 .../tests/typecheck/should_compile/tc168.stderr | 10 +- testsuite/tests/typecheck/should_compile/tc182.hs | 2 - testsuite/tests/typecheck/should_compile/tc244.hs | 2 + .../typecheck/should_fail/ContextStack2.stderr | 7 +- .../should_fail/CustomTypeErrors02.stderr | 2 +- .../should_fail/CustomTypeErrors03.stderr | 2 +- .../typecheck/should_fail/FDsFromGivens.stderr | 27 +- .../should_fail/FailDueToGivenOverlapping.stderr | 7 +- .../tests/typecheck/should_fail/IPFail.stderr | 5 +- .../tests/typecheck/should_fail/T10285.stderr | 34 +- .../tests/typecheck/should_fail/T10351.stderr | 2 +- .../tests/typecheck/should_fail/T10534.stderr | 28 +- .../tests/typecheck/should_fail/T10715.stderr | 11 +- .../tests/typecheck/should_fail/T11112.stderr | 5 +- .../tests/typecheck/should_fail/T1897a.stderr | 10 +- testsuite/tests/typecheck/should_fail/T1899.stderr | 21 +- testsuite/tests/typecheck/should_fail/T2538.stderr | 6 +- testsuite/tests/typecheck/should_fail/T2714.stderr | 18 +- testsuite/tests/typecheck/should_fail/T3102.stderr | 8 +- testsuite/tests/typecheck/should_fail/T3540.stderr | 25 +- testsuite/tests/typecheck/should_fail/T4875.stderr | 4 +- testsuite/tests/typecheck/should_fail/T5236.stderr | 19 +- testsuite/tests/typecheck/should_fail/T5300.stderr | 14 +- testsuite/tests/typecheck/should_fail/T5957.stderr | 5 +- testsuite/tests/typecheck/should_fail/T6022.stderr | 2 +- testsuite/tests/typecheck/should_fail/T7279.stderr | 5 +- testsuite/tests/typecheck/should_fail/T7410.stderr | 4 +- testsuite/tests/typecheck/should_fail/T7453.stderr | 81 +- testsuite/tests/typecheck/should_fail/T7609.stderr | 8 +- testsuite/tests/typecheck/should_fail/T7645.stderr | 4 +- testsuite/tests/typecheck/should_fail/T7696.stderr | 14 +- testsuite/tests/typecheck/should_fail/T7697.stderr | 4 +- .../tests/typecheck/should_fail/T7748a.stderr | 34 +- testsuite/tests/typecheck/should_fail/T7778.stderr | 4 +- testsuite/tests/typecheck/should_fail/T7809.stderr | 2 +- testsuite/tests/typecheck/should_fail/T7869.stderr | 1 + testsuite/tests/typecheck/should_fail/T8030.stderr | 6 +- testsuite/tests/typecheck/should_fail/T8034.stderr | 3 +- testsuite/tests/typecheck/should_fail/T8142.stderr | 5 +- .../tests/typecheck/should_fail/T8392a.stderr | 10 +- testsuite/tests/typecheck/should_fail/T8450.stderr | 16 +- testsuite/tests/typecheck/should_fail/T8603.stderr | 43 +- testsuite/tests/typecheck/should_fail/T8806.stderr | 10 +- testsuite/tests/typecheck/should_fail/T8883.stderr | 2 +- testsuite/tests/typecheck/should_fail/T9196.stderr | 10 +- testsuite/tests/typecheck/should_fail/T9201.stderr | 2 +- testsuite/tests/typecheck/should_fail/mc19.stderr | 8 +- testsuite/tests/typecheck/should_fail/mc21.stderr | 8 +- testsuite/tests/typecheck/should_fail/mc22.stderr | 13 +- .../tests/typecheck/should_fail/tcfail032.stderr | 1 + .../tests/typecheck/should_fail/tcfail034.stderr | 10 +- .../tests/typecheck/should_fail/tcfail057.stderr | 5 +- .../tests/typecheck/should_fail/tcfail058.stderr | 4 +- .../tests/typecheck/should_fail/tcfail063.stderr | 4 +- .../tests/typecheck/should_fail/tcfail065.stderr | 21 +- .../tests/typecheck/should_fail/tcfail067.stderr | 37 +- .../tests/typecheck/should_fail/tcfail068.stderr | 159 ++-- .../tests/typecheck/should_fail/tcfail072.stderr | 2 +- .../tests/typecheck/should_fail/tcfail076.stderr | 28 +- .../tests/typecheck/should_fail/tcfail078.stderr | 4 +- .../tests/typecheck/should_fail/tcfail080.stderr | 10 +- .../tests/typecheck/should_fail/tcfail097.stderr | 10 +- .../tests/typecheck/should_fail/tcfail098.stderr | 5 +- .../tests/typecheck/should_fail/tcfail101.stderr | 2 +- .../tests/typecheck/should_fail/tcfail102.stderr | 8 +- .../tests/typecheck/should_fail/tcfail103.stderr | 14 +- .../tests/typecheck/should_fail/tcfail107.stderr | 2 +- .../tests/typecheck/should_fail/tcfail110.stderr | 5 +- .../tests/typecheck/should_fail/tcfail113.stderr | 12 +- .../tests/typecheck/should_fail/tcfail116.stderr | 8 +- .../tests/typecheck/should_fail/tcfail127.stderr | 2 +- .../tests/typecheck/should_fail/tcfail131.stderr | 18 +- .../tests/typecheck/should_fail/tcfail134.stderr | 4 +- .../tests/typecheck/should_fail/tcfail135.stderr | 4 +- .../tests/typecheck/should_fail/tcfail142.stderr | 11 +- .../tests/typecheck/should_fail/tcfail153.stderr | 8 +- .../tests/typecheck/should_fail/tcfail158.stderr | 4 +- .../tests/typecheck/should_fail/tcfail160.stderr | 4 +- .../tests/typecheck/should_fail/tcfail161.stderr | 4 +- .../tests/typecheck/should_fail/tcfail174.stderr | 17 +- .../tests/typecheck/should_fail/tcfail175.stderr | 18 +- .../tests/typecheck/should_fail/tcfail179.stderr | 30 +- .../tests/typecheck/should_fail/tcfail181.stderr | 1 - .../tests/typecheck/should_fail/tcfail191.stderr | 8 +- .../tests/typecheck/should_fail/tcfail193.stderr | 8 +- .../tests/typecheck/should_fail/tcfail196.stderr | 5 +- .../tests/typecheck/should_fail/tcfail197.stderr | 2 +- .../tests/typecheck/should_fail/tcfail201.stderr | 23 +- .../tests/typecheck/should_fail/tcfail206.stderr | 26 +- .../tests/typecheck/should_fail/tcfail208.stderr | 6 +- .../tests/typecheck/should_fail/tcfail209a.stderr | 5 +- .../tests/typecheck/should_fail/tcfail212.stderr | 8 +- .../tests/typecheck/should_fail/tcfail215.stderr | 4 +- testsuite/tests/typecheck/should_run/Defer01.hs | 1 - testsuite/tests/typecheck/should_run/T7861.stderr | 6 +- testsuite/tests/typecheck/should_run/tcrun008.hs | 11 +- .../wcompat-warnings/WCompatWarningsOn.stderr | 2 +- utils/haddock | 2 +- 319 files changed, 5296 insertions(+), 4495 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1e041b7382b6aa329e4ad9625439f811e0f27232 From git at git.haskell.org Wed Dec 2 13:18:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 2 Dec 2015 13:18:29 +0000 (UTC) Subject: [commit: ghc] master: Make the order of fixities in the iface file deterministic (218fdf9) Message-ID: <20151202131829.32DAB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/218fdf92370021b900af1e78323764cceb7ac609/ghc >--------------------------------------------------------------- commit 218fdf92370021b900af1e78323764cceb7ac609 Author: Bartosz Nitka Date: Wed Dec 2 03:28:13 2015 -0800 Make the order of fixities in the iface file deterministic This normalizes the order of written fixities by sorting by `OccName` making it independent of `Unique` order. Test Plan: I've added a new testcase Reviewers: austin, bgamari, simonmar Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1557 GHC Trac Issues: #4012 >--------------------------------------------------------------- 218fdf92370021b900af1e78323764cceb7ac609 compiler/iface/MkIface.hs | 6 +++++- .../should_compile/read002.hs => determinism/determ010/A.hs} | 5 +++-- .../tests/determinism/{typecheck => determ010}/Makefile | 12 ++++++------ testsuite/tests/determinism/{determ003 => determ010}/all.T | 4 ++-- testsuite/tests/determinism/determ010/determ010.stdout | 2 ++ 5 files changed, 18 insertions(+), 11 deletions(-) diff --git a/compiler/iface/MkIface.hs b/compiler/iface/MkIface.hs index d955fa5..e428b58 100644 --- a/compiler/iface/MkIface.hs +++ b/compiler/iface/MkIface.hs @@ -222,7 +222,11 @@ mkIface_ hsc_env maybe_old_fingerprint nameIsLocalOrFrom this_mod name ] -- Sigh: see Note [Root-main Id] in TcRnDriver - fixities = [(occ,fix) | FixItem occ fix <- nameEnvElts fix_env] + fixities = sortBy (comparing fst) + [(occ,fix) | FixItem occ fix <- nameEnvElts fix_env] + -- The order of fixities returned from nameEnvElts is not + -- deterministic, so we sort by OccName to canonicalize it. + -- See Note [Deterministic UniqFM] in UniqDFM for more details. warns = src_warns iface_rules = map coreRuleToIfaceRule rules iface_insts = map instanceToIfaceInst $ fixSafeInstances safe_mode insts diff --git a/testsuite/tests/parser/should_compile/read002.hs b/testsuite/tests/determinism/determ010/A.hs similarity index 75% copy from testsuite/tests/parser/should_compile/read002.hs copy to testsuite/tests/determinism/determ010/A.hs index 8d9ea5e..b60f90a 100644 --- a/testsuite/tests/parser/should_compile/read002.hs +++ b/testsuite/tests/determinism/determ010/A.hs @@ -1,8 +1,8 @@ {-# OPTIONS_GHC -fno-warn-redundant-constraints #-} - --- !!! tests fixity reading and printing module ShouldCompile where +-- tests deterministic order of fixities in the interface file + infixl 1 `f` infixr 2 \\\ infix 3 :==> @@ -10,6 +10,7 @@ infix 4 `MkFoo` data Foo = MkFoo Int | Float :==> Double +f :: a -> b -> a x `f` y = x (\\\) :: (Eq a) => [a] -> [a] -> [a] diff --git a/testsuite/tests/determinism/typecheck/Makefile b/testsuite/tests/determinism/determ010/Makefile similarity index 54% copy from testsuite/tests/determinism/typecheck/Makefile copy to testsuite/tests/determinism/determ010/Makefile index ac98ea1..1f12622 100644 --- a/testsuite/tests/determinism/typecheck/Makefile +++ b/testsuite/tests/determinism/determ010/Makefile @@ -4,10 +4,10 @@ include $(TOP)/mk/test.mk TEST_HC_OPTS_NO_RECOMP = $(filter-out -fforce-recomp,$(TEST_HC_OPTS)) -determ005: +determ010: $(RM) A.hi A.o - '$(TEST_HC)' $(TEST_HC_OPTS_NO_RECOMP) -dinitial-unique=0 -dunique-increment=1 -O A.hs - $(CP) A.hi A.old.hi - $(RM) A.o - '$(TEST_HC)' $(TEST_HC_OPTS_NO_RECOMP) -dinitial-unique=16777206 -dunique-increment=-1 -O A.hs - diff A.hi A.old.hi + '$(TEST_HC)' $(TEST_HC_OPTS_NO_RECOMP) -dinitial-unique=0 -dunique-increment=1 A.hs + $(CP) A.hi A.normal.hi + $(RM) A.hi A.o + '$(TEST_HC)' $(TEST_HC_OPTS_NO_RECOMP) -dinitial-unique=16777215 -dunique-increment=-1 A.hs + diff A.hi A.normal.hi diff --git a/testsuite/tests/determinism/determ003/all.T b/testsuite/tests/determinism/determ010/all.T similarity index 50% copy from testsuite/tests/determinism/determ003/all.T copy to testsuite/tests/determinism/determ010/all.T index c00544d..030868f 100644 --- a/testsuite/tests/determinism/determ003/all.T +++ b/testsuite/tests/determinism/determ010/all.T @@ -1,4 +1,4 @@ -test('determ003', +test('determ010', extra_clean(['A.o', 'A.hi', 'A.normal.hi']), run_command, - ['$MAKE -s --no-print-directory determ003']) + ['$MAKE -s --no-print-directory determ010']) diff --git a/testsuite/tests/determinism/determ010/determ010.stdout b/testsuite/tests/determinism/determ010/determ010.stdout new file mode 100644 index 0000000..9a2bb82 --- /dev/null +++ b/testsuite/tests/determinism/determ010/determ010.stdout @@ -0,0 +1,2 @@ +[1 of 1] Compiling ShouldCompile ( A.hs, A.o ) +[1 of 1] Compiling ShouldCompile ( A.hs, A.o ) From git at git.haskell.org Wed Dec 2 13:23:14 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 2 Dec 2015 13:23:14 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: Pattern Match Checking (Fixes #595) (8a0eb7e) Message-ID: <20151202132314.31BBF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/8a0eb7e431d4a26b34c99110ad68cbcf6cf0af26/ghc >--------------------------------------------------------------- commit 8a0eb7e431d4a26b34c99110ad68cbcf6cf0af26 Author: George Karachalias Date: Wed Dec 2 13:49:08 2015 +0100 Pattern Match Checking (Fixes #595) >--------------------------------------------------------------- 8a0eb7e431d4a26b34c99110ad68cbcf6cf0af26 compiler/basicTypes/UniqSupply.hs | 26 +- compiler/deSugar/Check.hs | 1971 +++++++++++++++++++++++------------ compiler/deSugar/DsBinds.hs | 10 +- compiler/deSugar/DsExpr.hs | 18 +- compiler/deSugar/DsGRHSs.hs | 2 +- compiler/deSugar/DsMonad.hs | 64 +- compiler/deSugar/Match.hs | 174 +--- compiler/deSugar/Match.hs-boot | 1 + compiler/deSugar/PmExpr.hs | 376 +++++++ compiler/deSugar/TmOracle.hs | 432 ++++++++ compiler/ghc.cabal.in | 2 + compiler/ghc.mk | 1 + compiler/hsSyn/HsLit.hs | 22 + compiler/hsSyn/HsPat.hs | 41 +- compiler/prelude/TysWiredIn.hs-boot | 2 +- compiler/typecheck/TcMType.hs | 15 + compiler/typecheck/TcRnTypes.hs | 5 +- compiler/typecheck/TcSMonad.hs | 1 - compiler/typecheck/TcSimplify.hs | 14 + compiler/typecheck/TcType.hs | 42 + compiler/types/Type.hs | 22 +- compiler/utils/Bag.hs | 26 +- compiler/utils/MonadUtils.hs | 6 +- 23 files changed, 2420 insertions(+), 853 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 8a0eb7e431d4a26b34c99110ad68cbcf6cf0af26 From git at git.haskell.org Wed Dec 2 13:23:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 2 Dec 2015 13:23:16 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: Add & adjust tests for pattern match check (1c3542f) Message-ID: <20151202132316.E57233A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/1c3542f72dd6b9d1fa64d854ecb1c748adb0333c/ghc >--------------------------------------------------------------- commit 1c3542f72dd6b9d1fa64d854ecb1c748adb0333c Author: George Karachalias Date: Wed Dec 2 13:59:07 2015 +0100 Add & adjust tests for pattern match check >--------------------------------------------------------------- 1c3542f72dd6b9d1fa64d854ecb1c748adb0333c .../tests/deSugar/should_compile/T2395.stderr | 4 +- .../tests/deSugar/should_compile/T5117.stderr | 2 +- testsuite/tests/deSugar/should_compile/all.T | 1 - .../tests/deSugar/should_compile/ds002.stderr | 4 +- .../tests/deSugar/should_compile/ds003.stderr | 2 +- .../tests/deSugar/should_compile/ds019.stderr | 2 +- .../tests/deSugar/should_compile/ds020.stderr | 8 +-- testsuite/tests/deSugar/should_compile/ds022.hs | 2 + .../tests/deSugar/should_compile/ds022.stderr | 4 +- .../tests/deSugar/should_compile/ds043.stderr | 6 +- .../tests/deSugar/should_compile/ds051.stderr | 6 +- .../tests/deSugar/should_compile/ds056.stderr | 4 +- .../tests/deSugar/should_compile/ds058.stderr | 6 +- testsuite/tests/deSugar/should_compile/ds060.hs | 25 -------- testsuite/tests/driver/werror.stderr | 4 +- testsuite/tests/gadt/Gadt17_help.hs | 1 - testsuite/tests/gadt/T7294.stderr | 4 ++ testsuite/tests/ghci/scripts/Defer02.stderr | 8 +++ testsuite/tests/{ado => pmcheck}/Makefile | 0 .../should_compile/Makefile | 0 testsuite/tests/pmcheck/should_compile/T2006.hs | 13 ++++ .../tests/pmcheck/should_compile/T2006.stderr | 0 testsuite/tests/pmcheck/should_compile/T2204.hs | 9 +++ .../tests/pmcheck/should_compile/T2204.stderr | 14 ++++ testsuite/tests/pmcheck/should_compile/T3078.hs | 12 ++++ .../tests/pmcheck/should_compile/T3078.stderr | 0 testsuite/tests/pmcheck/should_compile/T322.hs | 29 +++++++++ .../tests/pmcheck/should_compile/T322.stderr | 0 testsuite/tests/pmcheck/should_compile/T366.hs | 10 +++ .../tests/pmcheck/should_compile/T366.stderr | 0 testsuite/tests/pmcheck/should_compile/T3927.hs | 13 ++++ .../tests/pmcheck/should_compile/T3927.stderr | 0 testsuite/tests/pmcheck/should_compile/T3927a.hs | 15 +++++ .../tests/pmcheck/should_compile/T3927a.stderr | 0 testsuite/tests/pmcheck/should_compile/T3927b.hs | 75 ++++++++++++++++++++++ .../tests/pmcheck/should_compile/T3927b.stderr | 39 +++++++++++ testsuite/tests/pmcheck/should_compile/T4139.hs | 28 ++++++++ .../tests/pmcheck/should_compile/T4139.stderr | 0 testsuite/tests/pmcheck/should_compile/T6124.hs | 14 ++++ .../tests/pmcheck/should_compile/T6124.stderr | 0 testsuite/tests/pmcheck/should_compile/T7669.hs | 9 +++ .../tests/pmcheck/should_compile/T7669.stderr | 0 testsuite/tests/pmcheck/should_compile/T8970.hs | 22 +++++++ .../tests/pmcheck/should_compile/T8970.stderr | 0 testsuite/tests/pmcheck/should_compile/T9951.hs | 10 +++ .../tests/pmcheck/should_compile/T9951.stderr | 0 testsuite/tests/pmcheck/should_compile/T9951b.hs | 7 ++ .../tests/pmcheck/should_compile/T9951b.stderr | 9 +++ testsuite/tests/pmcheck/should_compile/all.T | 35 ++++++++++ testsuite/tests/pmcheck/should_compile/pmc001.hs | 22 +++++++ .../tests/pmcheck/should_compile/pmc001.stderr | 17 +++++ testsuite/tests/pmcheck/should_compile/pmc002.hs | 7 ++ .../tests/pmcheck/should_compile/pmc002.stderr | 0 testsuite/tests/pmcheck/should_compile/pmc003.hs | 9 +++ .../tests/pmcheck/should_compile/pmc003.stderr | 3 + testsuite/tests/pmcheck/should_compile/pmc004.hs | 16 +++++ .../tests/pmcheck/should_compile/pmc004.stderr | 3 + testsuite/tests/pmcheck/should_compile/pmc005.hs | 12 ++++ .../tests/pmcheck/should_compile/pmc005.stderr | 7 ++ testsuite/tests/pmcheck/should_compile/pmc006.hs | 22 +++++++ .../tests/pmcheck/should_compile/pmc006.stderr | 0 testsuite/tests/pmcheck/should_compile/pmc007.hs | 20 ++++++ .../tests/pmcheck/should_compile/pmc007.stderr | 24 +++++++ .../tests/typecheck/should_compile/T5490.stderr | 8 +++ 64 files changed, 573 insertions(+), 53 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1c3542f72dd6b9d1fa64d854ecb1c748adb0333c From git at git.haskell.org Wed Dec 2 13:23:19 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 2 Dec 2015 13:23:19 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm's head updated: Add & adjust tests for pattern match check (1c3542f) Message-ID: <20151202132319.3976A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/gadtpm' now includes: c4308b4 rts/Pool: Add poolTryTake 1712a9e LibdwPool: Use poolTryTake ba14f04 Libdw: Handle failure to grab session for location lookup d25f853 Update transformers submodule 49aae12 Check arity on default decl for assoc types 583867b Update haskeline & terminfo submodules 85fcd03 Implement new -XTemplateHaskellQuotes pragma 72e3620 ghci: Add support for prompt functions 55c737f ghc-pkg: print version when verbose 399a5b4 Remove deprecated quasiquoter syntax. 71c0cc1 GHCi should not defer typed holes 54a9456 Update containers submodule 616aceb Update deepseq submodule 5897213 Remove redundant `#if`s f101a82 ghci: Refactor handling of :show bcd55a9 Some improvements on CoreToDos passed to plugins 290def7 Implement warnings for Semigroups as parent of Monoid afb7213 MkId: Typos in comments 14d0f7f Build system: Add stage specific SRC_HC_(WARNING_)OPTS 6dce643 Fix grammar and typo in TcTyDecls 36c1247 Remove duplicated line 44c3e37 Fix warning about unused pattern variable b432e2f Make the determinism tests more robust 1e041b7 Refactor treatment of wildcards 8a0eb7e Pattern Match Checking (Fixes #595) 1c3542f Add & adjust tests for pattern match check From git at git.haskell.org Wed Dec 2 14:09:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 2 Dec 2015 14:09:48 +0000 (UTC) Subject: [commit: ghc] master: Implement more deterministic operations and document them (741f837) Message-ID: <20151202140948.92BE53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/741f837d652fd00671614d52a6cb16fbc3758480/ghc >--------------------------------------------------------------- commit 741f837d652fd00671614d52a6cb16fbc3758480 Author: Bartosz Nitka Date: Wed Dec 2 05:30:22 2015 -0800 Implement more deterministic operations and document them I will need them for the future determinism fixes. Test Plan: ./validate Reviewers: simonpj, goldfire, bgamari, austin, hvr, simonmar Reviewed By: simonpj, simonmar Subscribers: osa1, thomie Differential Revision: https://phabricator.haskell.org/D1537 GHC Trac Issues: #4012 >--------------------------------------------------------------- 741f837d652fd00671614d52a6cb16fbc3758480 compiler/basicTypes/VarSet.hs | 68 ++++++++++++++++---- compiler/coreSyn/CoreFVs.hs | 94 ++++++++++++++++------------ compiler/ghci/ByteCodeGen.hs | 2 +- compiler/simplCore/SetLevels.hs | 8 +-- compiler/specialise/Rules.hs | 6 +- compiler/typecheck/Inst.hs | 45 +++++++++++--- compiler/typecheck/TcType.hs | 5 +- compiler/types/TypeRep.hs | 52 +++++++++++++--- compiler/utils/FV.hs | 135 ++++++++++++++++++++++++++++++++++++---- compiler/utils/UniqDFM.hs | 45 ++++++++++++++ compiler/utils/UniqDSet.hs | 8 +++ 11 files changed, 379 insertions(+), 89 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 741f837d652fd00671614d52a6cb16fbc3758480 From git at git.haskell.org Wed Dec 2 14:42:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 2 Dec 2015 14:42:32 +0000 (UTC) Subject: [commit: ghc] master: Comments only (isIrrefutablePat) (52b02e6) Message-ID: <20151202144232.8CF003A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/52b02e66025f029ca1b99dfccedca909fdc86831/ghc >--------------------------------------------------------------- commit 52b02e66025f029ca1b99dfccedca909fdc86831 Author: Simon Peyton Jones Date: Wed Dec 2 14:38:42 2015 +0000 Comments only (isIrrefutablePat) >--------------------------------------------------------------- 52b02e66025f029ca1b99dfccedca909fdc86831 compiler/hsSyn/HsPat.hs | 8 ++++++-- compiler/rename/RnExpr.hs | 5 +++++ 2 files changed, 11 insertions(+), 2 deletions(-) diff --git a/compiler/hsSyn/HsPat.hs b/compiler/hsSyn/HsPat.hs index 24ef065..359990a 100644 --- a/compiler/hsSyn/HsPat.hs +++ b/compiler/hsSyn/HsPat.hs @@ -540,8 +540,12 @@ isIrrefutableHsPat :: OutputableBndr id => LPat id -> Bool -- (NB: this is not quite the same as the (silly) defn -- in 3.17.2 of the Haskell 98 report.) -- --- isIrrefutableHsPat returns False if it's in doubt; specifically --- on a ConPatIn it doesn't know the size of the constructor family +-- WARNING: isIrrefutableHsPat returns False if it's in doubt. +-- Specifically on a ConPatIn, which is what it sees for a +-- (LPat Name) in the renamer, it doesn't know the size of the +-- constructor family, so it returns False. Result: only +-- tuple patterns are considered irrefuable at the renamer stage. +-- -- But if it returns True, the pattern is definitely irrefutable isIrrefutableHsPat pat = go pat diff --git a/compiler/rename/RnExpr.hs b/compiler/rename/RnExpr.hs index 035b4db..5df96cf 100644 --- a/compiler/rename/RnExpr.hs +++ b/compiler/rename/RnExpr.hs @@ -1437,6 +1437,11 @@ ado _ctxt [] tail _ = return (tail, emptyNameSet) -- the bind form, which would give rise to a Monad constraint. ado ctxt [(L _ (BindStmt pat rhs _ _),_)] tail _ | isIrrefutableHsPat pat, (False,tail') <- needJoin tail + -- WARNING: isIrrefutableHsPat on (HsPat Name) doesn't have enough info + -- to know which types have only one constructor. So only + -- tuples come out as irrefutable; other single-constructor + -- types, and newtypes, will not. See the code for + -- isIrrefuatableHsPat = mkApplicativeStmt ctxt [ApplicativeArgOne pat rhs] False tail' ado _ctxt [(one,_)] tail _ = return (one:tail, emptyNameSet) From git at git.haskell.org Wed Dec 2 14:42:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 2 Dec 2015 14:42:35 +0000 (UTC) Subject: [commit: ghc] master: Comments (TcSMonad) (b564731) Message-ID: <20151202144235.3547A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b5647315f778f3efd2be8a2f5b2aea7535179232/ghc >--------------------------------------------------------------- commit b5647315f778f3efd2be8a2f5b2aea7535179232 Author: Simon Peyton Jones Date: Wed Dec 2 14:41:12 2015 +0000 Comments (TcSMonad) >--------------------------------------------------------------- b5647315f778f3efd2be8a2f5b2aea7535179232 compiler/typecheck/TcSMonad.hs | 12 ++++++++---- 1 file changed, 8 insertions(+), 4 deletions(-) diff --git a/compiler/typecheck/TcSMonad.hs b/compiler/typecheck/TcSMonad.hs index bf3f397..4a4d766 100644 --- a/compiler/typecheck/TcSMonad.hs +++ b/compiler/typecheck/TcSMonad.hs @@ -705,6 +705,9 @@ A generalised substitution S is "inert" iff (IG2) if (b -f-> t) in S, and f >= f, then S(f,t) = t that is, each individual binding is "self-stable" +By (IG1) we define S*(f,t) to be the result of exahaustively +applying S(f,_) to t. + ---------------------------------------------------------------- Our main invariant: the inert CTyEqCans should be an inert generalised substitution @@ -737,7 +740,8 @@ This is the main theorem! or (K2c) not (fw >= fs) or (K2d) a not in s - (K3) If (b -fs-> s) is in S with (fw >= fs), then + (K3) See Note [K3: completeness of solving] + If (b -fs-> s) is in S with (fw >= fs), then (K3a) If the role of fs is nominal: s /= a (K3b) If the role of fs is representational: EITHER a not in s, OR @@ -818,9 +822,9 @@ Key lemma to make it watertight. Also, consider roles more carefully. See Note [Flavours with roles]. -Completeness -~~~~~~~~~~~~~ -K3: completeness. (K3) is not necessary for the extended substitution +Note [K3: completeness of solving] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +(K3) is not necessary for the extended substitution to be inert. In fact K1 could be made stronger by saying ... then (not (fw >= fs) or not (fs >= fs)) But it's not enough for S to be inert; we also want completeness. From git at git.haskell.org Wed Dec 2 14:46:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 2 Dec 2015 14:46:54 +0000 (UTC) Subject: [commit: ghc] master: Revert "ghci: Add support for prompt functions" (d00cdf2) Message-ID: <20151202144654.066E33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d00cdf237f28d72df74157bfdf30e623786b68c3/ghc >--------------------------------------------------------------- commit d00cdf237f28d72df74157bfdf30e623786b68c3 Author: Ben Gamari Date: Wed Dec 2 14:59:39 2015 +0100 Revert "ghci: Add support for prompt functions" This reverts commit 72e362076e7ce823678797a162d0645e088cd594 which was accidentally merged. >--------------------------------------------------------------- d00cdf237f28d72df74157bfdf30e623786b68c3 ghc/GhciMonad.hs | 14 ++----- ghc/InteractiveUI.hs | 105 ++++++++++++++++++++++----------------------------- 2 files changed, 48 insertions(+), 71 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d00cdf237f28d72df74157bfdf30e623786b68c3 From git at git.haskell.org Wed Dec 2 15:30:04 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 2 Dec 2015 15:30:04 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T11028-2' created Message-ID: <20151202153004.9461A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T11028-2 Referencing: d9c274b4180616cdba64a68f7d5610117ca01e06 From git at git.haskell.org Wed Dec 2 15:30:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 2 Dec 2015 15:30:07 +0000 (UTC) Subject: [commit: ghc] wip/T11028-2: Refactor ConDecl (d9c274b) Message-ID: <20151202153007.4DD163A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T11028-2 Link : http://ghc.haskell.org/trac/ghc/changeset/d9c274b4180616cdba64a68f7d5610117ca01e06/ghc >--------------------------------------------------------------- commit d9c274b4180616cdba64a68f7d5610117ca01e06 Author: Alan Zimmerman Date: Mon Nov 23 22:59:27 2015 +0200 Refactor ConDecl Summary: The ConDecl type in HsDecls is an uneasy compromise. For the most part, HsSyn directly reflects the syntax written by the programmer; and that gives just the right "pegs" on which to hang Alan's API annotations. But ConDecl doesn't properly reflect the syntax of Haskell-98 and GADT-style data type declarations. To be concrete, here's a draft new data type data ConDecl name | ConDeclGADT { con_names :: [Located name] , con_type :: LHsSigType name -- The type after the ?::? , con_doc :: Maybe LHsDocString } | ConDeclH98 { con_name :: Located name , con_qvars :: Maybe (LHsQTyVars name) -- User-written forall (if any), and its implicit -- kind variables -- Non-Nothing needs -XExistentialQuantification , con_cxt :: Maybe (LHsContext name) -- ^ User-written context (if any) , con_details :: HsConDeclDetails name -- ^ Arguments , con_doc :: Maybe LHsDocString -- ^ A possible Haddock comment. } deriving (Typeable) Note that For GADTs, just keep a type. That's what the user writes. NB:HsType can represent records on the LHS of an arrow: { x:Int,y:Bool} -> T con_qvars and con_cxt are both Maybe because they are both optional (the forall and the context of an existential data type For ConDeclGADT the type variables of the data type do not scope over the con_type; whereas for ConDeclH98 they do scope over con_cxt and con_details. Test Plan: ./validate Reviewers: simonpj, austin, goldfire, bgamari Subscribers: goldfire, thomie, mpickering Differential Revision: https://phabricator.haskell.org/D1558 GHC Trac Issues: #11028 >--------------------------------------------------------------- d9c274b4180616cdba64a68f7d5610117ca01e06 compiler/deSugar/DsMeta.hs | 99 ++++++++--- compiler/hsSyn/Convert.hs | 22 ++- compiler/hsSyn/HsDecls.hs | 133 +++++--------- compiler/hsSyn/HsTypes.hs | 4 +- compiler/hsSyn/HsUtils.hs | 26 ++- compiler/parser/Parser.y | 12 +- compiler/parser/RdrHsSyn.hs | 72 +++----- compiler/rename/RnEnv.hs | 4 +- compiler/rename/RnNames.hs | 13 +- compiler/rename/RnSource.hs | 120 +++++-------- compiler/rename/RnTypes.hs | 22 ++- compiler/typecheck/TcHsType.hs | 9 +- compiler/typecheck/TcRnDriver.hs | 2 +- compiler/typecheck/TcTyClsDecls.hs | 194 +++++++++++++++------ testsuite/tests/ghc-api/annotations/T10399.stdout | 2 - testsuite/tests/ghc-api/annotations/all.T | 2 +- testsuite/tests/ghc-api/landmines/landmines.stdout | 2 +- testsuite/tests/rename/should_compile/T5331.stderr | 2 +- testsuite/tests/rename/should_fail/T7943.stderr | 6 +- utils/haddock | 2 +- 20 files changed, 416 insertions(+), 332 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d9c274b4180616cdba64a68f7d5610117ca01e06 From git at git.haskell.org Wed Dec 2 17:07:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 2 Dec 2015 17:07:21 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: made hlint a bit happier (afd5190) Message-ID: <20151202170721.C056A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/afd5190443c32c7fd97a2e0d9c8256a2c098ba7b/ghc >--------------------------------------------------------------- commit afd5190443c32c7fd97a2e0d9c8256a2c098ba7b Author: George Karachalias Date: Wed Dec 2 16:33:35 2015 +0100 made hlint a bit happier >--------------------------------------------------------------- afd5190443c32c7fd97a2e0d9c8256a2c098ba7b compiler/deSugar/Check.hs | 113 +++++++++++++++++++++++++++---------------- compiler/deSugar/PmExpr.hs | 11 +++-- compiler/deSugar/TmOracle.hs | 27 +++++------ 3 files changed, 89 insertions(+), 62 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc afd5190443c32c7fd97a2e0d9c8256a2c098ba7b From git at git.haskell.org Wed Dec 2 17:07:24 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 2 Dec 2015 17:07:24 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: some more simplification & comments about overloaded literals (850905a) Message-ID: <20151202170724.7E53C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/850905ab3f2e87d5d3def01dfd2ad63dd012937a/ghc >--------------------------------------------------------------- commit 850905ab3f2e87d5d3def01dfd2ad63dd012937a Author: George Karachalias Date: Wed Dec 2 17:54:16 2015 +0100 some more simplification & comments about overloaded literals >--------------------------------------------------------------- 850905ab3f2e87d5d3def01dfd2ad63dd012937a compiler/deSugar/Check.hs | 14 +++------- compiler/deSugar/TmOracle.hs | 61 ++++++++++++++++++++++++++++++-------------- 2 files changed, 45 insertions(+), 30 deletions(-) diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs index 0287803..5b33167 100644 --- a/compiler/deSugar/Check.hs +++ b/compiler/deSugar/Check.hs @@ -876,14 +876,9 @@ pruneVSABound n v = pruneVSABound' n init_cs emptylist v -- Have another go at the term oracle state, for strange -- equalities between overloaded literals. See -- Note [Undecidable Equality on Overloaded Literals] in TmOracle - case tryLitEqs tm_env of - -- An equality (l1 ~ l2) is in the residual constraints. This - -- means that the whole subtree makes the assumption that - -- from l1 ~ from l2. We do not want to print such warnings. - Just True -> return [] - -- No strange constraints (l1 ~ l2) are present. Proceed with - -- the type oracle. - Just False -> do + if containsEqLits tm_env + then return [] -- not on the safe side + else do -- TODO: Provide an incremental interface for the type oracle sat <- tyOracle (listToBag ty_cs) return $ case sat of @@ -891,9 +886,6 @@ pruneVSABound n v = pruneVSABound' n init_cs emptylist v vector = substInValVecAbs subst (toList vec) in [(vector, residual_eqs)] False -> [] - -- Literal constraints (l1 ~ l2) were present and exploiting them - -- detected an inconsistency. - Nothing -> return [] Constraint cs vsa -> case splitConstraints cs of (new_ty_cs, new_tm_cs, new_bot_ct) -> diff --git a/compiler/deSugar/TmOracle.hs b/compiler/deSugar/TmOracle.hs index 39b61b6..d69ffdb 100644 --- a/compiler/deSugar/TmOracle.hs +++ b/compiler/deSugar/TmOracle.hs @@ -14,7 +14,7 @@ module TmOracle ( pprPmExprWithParens, lhsExprToPmExpr, hsExprToPmExpr, -- the term oracle - tmOracle, TmState, initialTmState, tryLitEqs, + tmOracle, TmState, initialTmState, containsEqLits, -- misc. exprDeepLookup, pmLitType, flattenPmVarEnv @@ -149,6 +149,7 @@ simplifyComplexEq (e1, e2) = (fst $ simplifyPmExpr e1, fst $ simplifyPmExpr e2) -- | Simplify an expression. The boolean indicates if there has been any -- simplification or if the operation was a no-op. simplifyPmExpr :: PmExpr -> (PmExpr, Bool) +-- See Note [Deep equalities] simplifyPmExpr e = case e of PmExprCon c ts -> case mapAndUnzip simplifyPmExpr ts of (ts', bs) -> (PmExprCon c ts', or bs) @@ -157,6 +158,7 @@ simplifyPmExpr e = case e of -- | Simplify an equality expression. The equality is given in parts. simplifyEqExpr :: PmExpr -> PmExpr -> (PmExpr, Bool) +-- See Note [Deep equalities] simplifyEqExpr e1 e2 = case (e1, e2) of -- Varables (PmExprVar x, PmExprVar y) @@ -322,9 +324,9 @@ cannot detect that constraint: False ~ (l1 ~ l3), False ~ (l2 ~ l4), l1 ~ l3 -is inconsistent. That's what function @tryLitEqs@ tries to do: use the equality -l1 ~ l3 to replace False ~ (l1 ~ l3) with False ~ (l1 ~ l1) and expose the -inconsistency. +is inconsistent. That's what function @tryLitEqs@ (in comments) tries to do: +use the equality l1 ~ l3 to replace False ~ (l1 ~ l3) with False ~ (l1 ~ l1) +and expose the inconsistency. PROBLEM 2: ~~~~~~~~~~ @@ -354,16 +356,33 @@ issue a warning like: In an equation for f: Patterns not matched: ... - l1 y where y not one of {l2, l4} -- (*) + l1 y where y not one of {l2, l4} under the assumption that l1 ~ l3 It may be more complex but I would prefer to play on the safe side and (safely) issue all warnings and leave it up to the user to decide whether the assumption holds or not. --} +At the moment, we use @containsEqLits@ and consider all constraints that +include literal equalities inconsistent. We could achieve the same by replacing +this clause of @eqPmLit@: + + eqPmLit (PmOLit b1 l1) (PmOLit b2 l2) + | b1 == b2 && l1 == l2 = Just True + | otherwise = Nothing + +with this: + eqPmLit (PmOLit b1 l1) (PmOLit b2 l2) + | b1 == b2 && l1 == l2 = Just True + | otherwise = Just False +which approximates on the unsafe side. Hopefully, literals always need a +catch-all case to be considered exhaustive so in practice it makes small +difference. I hate this but it gives the warnings the users are used to. +-} + +{- Not Enabled at the moment -- | Check whether overloaded literal constraints exist in the state and if -- they can be used to detect further inconsistencies. @@ -402,19 +421,6 @@ exploitLitEqs tm_state = case tm_state of replaceLitSimplifyComplexEq l1 l2 (e1,e2) = simplifyComplexEq (replaceLit l1 l2 e1, replaceLit l1 l2 e2) -exists :: (a -> Maybe b) -> [a] -> Maybe (b, [a]) -exists _ [] = Nothing -exists p (x:xs) = case p x of - Just y -> Just (y, xs) - Nothing -> do - (y, ys) <- exists p xs - return (y, x:ys) - --- | Check whether a complex equality refers to literals only -isLitEq_mb :: ComplexEq -> Maybe (PmLit, PmLit) -isLitEq_mb (PmExprLit l1, PmExprLit l2) = Just (l1, l2) -isLitEq_mb _other_eq = Nothing - -- | Replace a literal with another in an expression -- See Note [Undecidable Equality on Overloaded Literals] replaceLit :: PmLit -> PmLit -> PmExpr -> PmExpr @@ -427,5 +433,22 @@ replaceLit l1 l2 e = case e of Nothing -> e PmExprEq e1 e2 -> PmExprEq (replaceLit l1 l2 e1) (replaceLit l1 l2 e2) PmExprOther {} -> e -- do nothing +-} +-- | Check whether the term oracle state +-- contains any equalities between literals. +containsEqLits :: TmState -> Bool +containsEqLits (stb, _) = isJust (exists isLitEq_mb stb) + +exists :: (a -> Maybe b) -> [a] -> Maybe (b, [a]) +exists _ [] = Nothing +exists p (x:xs) = case p x of + Just y -> Just (y, xs) + Nothing -> do + (y, ys) <- exists p xs + return (y, x:ys) +-- | Check whether a complex equality refers to literals only +isLitEq_mb :: ComplexEq -> Maybe (PmLit, PmLit) +isLitEq_mb (PmExprLit l1, PmExprLit l2) = Just (l1, l2) +isLitEq_mb _other_eq = Nothing From git at git.haskell.org Wed Dec 2 20:03:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 2 Dec 2015 20:03:54 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: make hlint even happier: fit everything in 80 columns (baff06d) Message-ID: <20151202200354.2EF653A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/baff06dedb173113ec190b3697f7095fce481a4b/ghc >--------------------------------------------------------------- commit baff06dedb173113ec190b3697f7095fce481a4b Author: George Karachalias Date: Wed Dec 2 20:41:33 2015 +0100 make hlint even happier: fit everything in 80 columns >--------------------------------------------------------------- baff06dedb173113ec190b3697f7095fce481a4b compiler/deSugar/Check.hs | 137 +++++++++++++++++++++++-------------------- compiler/deSugar/PmExpr.hs | 8 +-- compiler/deSugar/TmOracle.hs | 3 +- 3 files changed, 81 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 baff06dedb173113ec190b3697f7095fce481a4b From git at git.haskell.org Wed Dec 2 20:21:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 2 Dec 2015 20:21:09 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: Major Overhaul of Pattern Match Checking (Fixes #595) (60d7d28) Message-ID: <20151202202109.9F4603A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/60d7d287b70e4b432307325a38577c6b2d17fe5a/ghc >--------------------------------------------------------------- commit 60d7d287b70e4b432307325a38577c6b2d17fe5a Author: George Karachalias Date: Wed Dec 2 21:20:43 2015 +0100 Major Overhaul of Pattern Match Checking (Fixes #595) This patch adresses several problems concerned with exhaustiveness and redundancy checking of pattern matching. The list of improvements includes: * Making the check type-aware (handles GADTs, Type Families, DataKinds, etc.). This fixes #4139, #3927, #8970 and other related tickets. * Making the check laziness-aware. Cases that are overlapped but affect evaluation are issued now with "Patterns have inaccessible right hand side". Additionally, "Patterns are overlapped" is now replaced by "Patterns are redundant". * Improved messages for literals. This addresses tickets #5724, #2204, etc. * Improved reasoning concerning cases where simple and overloaded patterns are matched (See #322). * Substantially improved reasoning for pattern guards. Addresses #3078. * OverloadedLists extension does not break exhaustiveness checking anymore (addresses #9951). Note that in general this cannot be handled but if we know that an argument has type '[a]', we treat it as a list since, the instance of 'IsList' gives the identity for both 'fromList' and 'toList'. If the type is not clear or is not the list type, then the check cannot do much still. I am a bit concerned about OverlappingInstances though, since one may override the '[a]' instance with e.g. an '[Int]' instance that is not the identity. * Improved reasoning for nested pattern matching (partial solution). Now we propagate type and (some) term constraints deeper when checking, so we can detect more inconsistencies. For example, this is needed for #4139. I am still not satisfied with several things but I would like to address at least the following before the next release: Term constraints are too many and not printed for non-exhaustive matches (with the exception of literals). This sometimes results in two identical (in appearance) uncovered warnings. Unless we actually show their difference, I would like to have a single warning. >--------------------------------------------------------------- 60d7d287b70e4b432307325a38577c6b2d17fe5a compiler/basicTypes/UniqSupply.hs | 26 +- compiler/deSugar/Check.hs | 2017 +++++++++++++------- compiler/deSugar/DsBinds.hs | 10 +- compiler/deSugar/DsExpr.hs | 18 +- compiler/deSugar/DsGRHSs.hs | 2 +- compiler/deSugar/DsMonad.hs | 64 +- compiler/deSugar/Match.hs | 174 +- compiler/deSugar/Match.hs-boot | 1 + compiler/deSugar/PmExpr.hs | 377 ++++ compiler/deSugar/TmOracle.hs | 455 +++++ compiler/ghc.cabal.in | 2 + compiler/ghc.mk | 1 + compiler/hsSyn/HsLit.hs | 22 + compiler/hsSyn/HsPat.hs | 41 +- compiler/prelude/TysWiredIn.hs-boot | 2 +- compiler/typecheck/TcMType.hs | 15 + compiler/typecheck/TcRnTypes.hs | 5 +- compiler/typecheck/TcSMonad.hs | 1 - compiler/typecheck/TcSimplify.hs | 14 + compiler/typecheck/TcType.hs | 42 + compiler/types/Type.hs | 22 +- compiler/utils/Bag.hs | 26 +- compiler/utils/MonadUtils.hs | 6 +- .../tests/deSugar/should_compile/T2395.stderr | 4 +- .../tests/deSugar/should_compile/T5117.stderr | 2 +- testsuite/tests/deSugar/should_compile/all.T | 1 - .../tests/deSugar/should_compile/ds002.stderr | 4 +- .../tests/deSugar/should_compile/ds003.stderr | 2 +- .../tests/deSugar/should_compile/ds019.stderr | 2 +- .../tests/deSugar/should_compile/ds020.stderr | 8 +- testsuite/tests/deSugar/should_compile/ds022.hs | 2 + .../tests/deSugar/should_compile/ds022.stderr | 4 +- .../tests/deSugar/should_compile/ds043.stderr | 6 +- .../tests/deSugar/should_compile/ds051.stderr | 6 +- .../tests/deSugar/should_compile/ds056.stderr | 4 +- .../tests/deSugar/should_compile/ds058.stderr | 6 +- testsuite/tests/deSugar/should_compile/ds060.hs | 25 - testsuite/tests/driver/werror.stderr | 4 +- testsuite/tests/gadt/Gadt17_help.hs | 1 - testsuite/tests/gadt/T7294.stderr | 4 + testsuite/tests/ghci/scripts/Defer02.stderr | 8 + testsuite/tests/{ado => pmcheck}/Makefile | 0 .../should_compile/Makefile | 0 testsuite/tests/pmcheck/should_compile/T2006.hs | 13 + .../tests/pmcheck/should_compile/T2006.stderr | 0 testsuite/tests/pmcheck/should_compile/T2204.hs | 9 + .../tests/pmcheck/should_compile/T2204.stderr | 14 + testsuite/tests/pmcheck/should_compile/T3078.hs | 12 + .../tests/pmcheck/should_compile/T3078.stderr | 0 testsuite/tests/pmcheck/should_compile/T322.hs | 29 + .../tests/pmcheck/should_compile/T322.stderr | 0 testsuite/tests/pmcheck/should_compile/T366.hs | 10 + .../tests/pmcheck/should_compile/T366.stderr | 0 testsuite/tests/pmcheck/should_compile/T3927.hs | 13 + .../tests/pmcheck/should_compile/T3927.stderr | 0 testsuite/tests/pmcheck/should_compile/T3927a.hs | 15 + .../tests/pmcheck/should_compile/T3927a.stderr | 0 testsuite/tests/pmcheck/should_compile/T3927b.hs | 75 + .../tests/pmcheck/should_compile/T3927b.stderr | 39 + testsuite/tests/pmcheck/should_compile/T4139.hs | 28 + .../tests/pmcheck/should_compile/T4139.stderr | 0 testsuite/tests/pmcheck/should_compile/T6124.hs | 14 + .../tests/pmcheck/should_compile/T6124.stderr | 0 testsuite/tests/pmcheck/should_compile/T7669.hs | 9 + .../tests/pmcheck/should_compile/T7669.stderr | 0 testsuite/tests/pmcheck/should_compile/T8970.hs | 22 + .../tests/pmcheck/should_compile/T8970.stderr | 0 testsuite/tests/pmcheck/should_compile/T9951.hs | 10 + .../tests/pmcheck/should_compile/T9951.stderr | 0 testsuite/tests/pmcheck/should_compile/T9951b.hs | 7 + .../tests/pmcheck/should_compile/T9951b.stderr | 9 + testsuite/tests/pmcheck/should_compile/all.T | 35 + testsuite/tests/pmcheck/should_compile/pmc001.hs | 22 + .../tests/pmcheck/should_compile/pmc001.stderr | 17 + testsuite/tests/pmcheck/should_compile/pmc002.hs | 7 + .../tests/pmcheck/should_compile/pmc002.stderr | 0 testsuite/tests/pmcheck/should_compile/pmc003.hs | 9 + .../tests/pmcheck/should_compile/pmc003.stderr | 3 + testsuite/tests/pmcheck/should_compile/pmc004.hs | 16 + .../tests/pmcheck/should_compile/pmc004.stderr | 3 + testsuite/tests/pmcheck/should_compile/pmc005.hs | 12 + .../tests/pmcheck/should_compile/pmc005.stderr | 7 + testsuite/tests/pmcheck/should_compile/pmc006.hs | 22 + .../tests/pmcheck/should_compile/pmc006.stderr | 0 testsuite/tests/pmcheck/should_compile/pmc007.hs | 20 + .../tests/pmcheck/should_compile/pmc007.stderr | 24 + .../tests/typecheck/should_compile/T5490.stderr | 8 + 87 files changed, 3056 insertions(+), 913 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 60d7d287b70e4b432307325a38577c6b2d17fe5a From git at git.haskell.org Wed Dec 2 20:38:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 2 Dec 2015 20:38:33 +0000 (UTC) Subject: [commit: ghc] master: StgSyn: Remove unused SRT constructor (1caff20) Message-ID: <20151202203833.A53403A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1caff20fad1e533d7dfb4215e69ce8678def943b/ghc >--------------------------------------------------------------- commit 1caff20fad1e533d7dfb4215e69ce8678def943b Author: ?mer Sinan A?acan Date: Wed Dec 2 14:35:27 2015 -0600 StgSyn: Remove unused SRT constructor Reviewed By: bgamari, austin Differential Revision: https://phabricator.haskell.org/D1560 >--------------------------------------------------------------- 1caff20fad1e533d7dfb4215e69ce8678def943b compiler/simplStg/UnariseStg.hs | 1 - compiler/stgSyn/StgSyn.hs | 5 ----- 2 files changed, 6 deletions(-) diff --git a/compiler/simplStg/UnariseStg.hs b/compiler/simplStg/UnariseStg.hs index a1533ba..81de31b 100644 --- a/compiler/simplStg/UnariseStg.hs +++ b/compiler/simplStg/UnariseStg.hs @@ -164,7 +164,6 @@ unariseAlt us rho (con, xs, uses, e) unariseSRT :: UnariseEnv -> SRT -> SRT unariseSRT _ NoSRT = NoSRT unariseSRT rho (SRTEntries ids) = SRTEntries (concatMapVarSet (unariseId rho) ids) -unariseSRT _ (SRT {}) = panic "unariseSRT" unariseLives :: UnariseEnv -> StgLiveVars -> StgLiveVars unariseLives rho ids = concatMapVarSet (unariseId rho) ids diff --git a/compiler/stgSyn/StgSyn.hs b/compiler/stgSyn/StgSyn.hs index 1c6a00f..f0eb2d5 100644 --- a/compiler/stgSyn/StgSyn.hs +++ b/compiler/stgSyn/StgSyn.hs @@ -46,7 +46,6 @@ module StgSyn ( #include "HsVersions.h" -import Bitmap import CoreSyn ( AltCon, Tickish ) import CostCentre ( CostCentreStack ) import Data.List ( intersperse ) @@ -604,18 +603,14 @@ data SRT = NoSRT | SRTEntries IdSet -- generated by CoreToStg - | SRT !Int{-offset-} !Int{-length-} !Bitmap{-bitmap-} - -- generated by computeSRTs nonEmptySRT :: SRT -> Bool nonEmptySRT NoSRT = False nonEmptySRT (SRTEntries vs) = not (isEmptyVarSet vs) -nonEmptySRT _ = True pprSRT :: SRT -> SDoc pprSRT (NoSRT) = ptext (sLit "_no_srt_") pprSRT (SRTEntries ids) = text "SRT:" <> ppr ids -pprSRT (SRT off _ _) = parens (ppr off <> comma <> text "*bitmap*") {- ************************************************************************ From git at git.haskell.org Wed Dec 2 20:38:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 2 Dec 2015 20:38:36 +0000 (UTC) Subject: [commit: ghc] master: Move Stg-specific code from DynFlags to SimplStg (c75948b) Message-ID: <20151202203836.4D0453A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c75948b9dcf5a2761223f4ef3777042982c33cc8/ghc >--------------------------------------------------------------- commit c75948b9dcf5a2761223f4ef3777042982c33cc8 Author: ?mer Sinan A?acan Date: Wed Dec 2 14:36:56 2015 -0600 Move Stg-specific code from DynFlags to SimplStg Reviewed By: bgamari, austin Differential Revision: https://phabricator.haskell.org/D1552 >--------------------------------------------------------------- c75948b9dcf5a2761223f4ef3777042982c33cc8 compiler/main/DynFlags.hs | 26 -------------------------- compiler/simplStg/SimplStg.hs | 22 ++++++++++++++++++++++ 2 files changed, 22 insertions(+), 26 deletions(-) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 98c61e7..7779732 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -113,10 +113,6 @@ module DynFlags ( -- ** DynFlags C compiler options picCCOpts, picPOpts, - -- * Configuration of the stg-to-stg passes - StgToDo(..), - getStgToDo, - -- * Compiler configuration suitable for display to the user compilerInfo, @@ -2028,28 +2024,6 @@ updOptLevel n dfs extra_gopts = [ f | (ns,f) <- optLevelFlags, final_n `elem` ns ] remove_gopts = [ f | (ns,f) <- optLevelFlags, final_n `notElem` ns ] --- ----------------------------------------------------------------------------- --- StgToDo: abstraction of stg-to-stg passes to run. - -data StgToDo - = StgDoMassageForProfiling -- should be (next to) last - -- There's also setStgVarInfo, but its absolute "lastness" - -- is so critical that it is hardwired in (no flag). - | D_stg_stats - -getStgToDo :: DynFlags -> [StgToDo] -getStgToDo dflags - = todo2 - where - stg_stats = gopt Opt_StgStats dflags - - todo1 = if stg_stats then [D_stg_stats] else [] - - todo2 | WayProf `elem` ways dflags - = StgDoMassageForProfiling : todo1 - | otherwise - = todo1 - {- ********************************************************************** %* * DynFlags parser diff --git a/compiler/simplStg/SimplStg.hs b/compiler/simplStg/SimplStg.hs index b8804a4..b8491fc 100644 --- a/compiler/simplStg/SimplStg.hs +++ b/compiler/simplStg/SimplStg.hs @@ -87,3 +87,25 @@ stg2stg dflags module_name binds -- UniqueSupply for the next guy to use -- cost-centres to be declared/registered (specialised) -- add to description of what's happened (reverse order) + +-- ----------------------------------------------------------------------------- +-- StgToDo: abstraction of stg-to-stg passes to run. + +-- | Optional Stg-to-Stg passes. +data StgToDo + = StgDoMassageForProfiling -- should be (next to) last + | D_stg_stats + +-- | Which optional Stg-to-Stg passes to run. Depends on flags, ways etc. +getStgToDo :: DynFlags -> [StgToDo] +getStgToDo dflags + = todo2 + where + stg_stats = gopt Opt_StgStats dflags + + todo1 = if stg_stats then [D_stg_stats] else [] + + todo2 | WayProf `elem` ways dflags + = StgDoMassageForProfiling : todo1 + | otherwise + = todo1 From git at git.haskell.org Wed Dec 2 20:38:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 2 Dec 2015 20:38:38 +0000 (UTC) Subject: [commit: ghc] master: Remove *.xml from gitignore (d4d54b4) Message-ID: <20151202203838.E6ADA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d4d54b463ef73a577054e9ed1dfce5044072bce7/ghc >--------------------------------------------------------------- commit d4d54b463ef73a577054e9ed1dfce5044072bce7 Author: David Luposchainsky Date: Wed Dec 2 14:37:07 2015 -0600 Remove *.xml from gitignore With the move to RST-based documentation, there is no need to ignore XML files in the source tree anymore. Reviewed By: bgamari Differential Revision: https://phabricator.haskell.org/D1554 >--------------------------------------------------------------- d4d54b463ef73a577054e9ed1dfce5044072bce7 .gitignore | 1 - 1 file changed, 1 deletion(-) diff --git a/.gitignore b/.gitignore index a223f30..b61ba02 100644 --- a/.gitignore +++ b/.gitignore @@ -91,7 +91,6 @@ _darcs/ /docs/index.html /docs/users_guide/users_guide /docs/users_guide/ghc.1 -/docs/users_guide/*.xml /docs/users_guide/*.gen.rst /docs/users_guide/ghc_config.py /docs/users_guide/ghc_config.pyc From git at git.haskell.org Wed Dec 2 20:38:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 2 Dec 2015 20:38:41 +0000 (UTC) Subject: [commit: ghc] master: Avoid panic due to partial ieName (a12e47b) Message-ID: <20151202203841.EC73D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a12e47bed74e305b37e68014c52feba3dd075514/ghc >--------------------------------------------------------------- commit a12e47bed74e305b37e68014c52feba3dd075514 Author: Eric Seidel Date: Wed Dec 2 14:37:21 2015 -0600 Avoid panic due to partial ieName HsImpExp.ieName is partial and fails when given e.g. `module X` solution: use ieNames instead which returns a list of names instead of a single name. Reviewed By: bgamari, austin Differential Revision: https://phabricator.haskell.org/D1551 GHC Trac Issues: #11077 >--------------------------------------------------------------- a12e47bed74e305b37e68014c52feba3dd075514 compiler/typecheck/TcHsSyn.hs | 2 +- testsuite/tests/warnings/should_compile/T11077.hs | 3 +++ testsuite/tests/warnings/should_compile/T11077.stderr | 3 +++ testsuite/tests/warnings/should_compile/all.T | 1 + 4 files changed, 8 insertions(+), 1 deletion(-) diff --git a/compiler/typecheck/TcHsSyn.hs b/compiler/typecheck/TcHsSyn.hs index ae095e0..39e7f2d 100644 --- a/compiler/typecheck/TcHsSyn.hs +++ b/compiler/typecheck/TcHsSyn.hs @@ -317,7 +317,7 @@ zonkTopDecls ev_binds binds export_ies sig_ns rules vects imp_specs fords ; warn_missing_sigs <- woptM Opt_WarnMissingSigs ; warn_only_exported <- woptM Opt_WarnMissingExportedSigs ; let export_occs = maybe emptyBag - (listToBag . map (rdrNameOcc . ieName . unLoc) . unLoc) + (listToBag . concatMap (map rdrNameOcc . ieNames . unLoc) . unLoc) export_ies sig_warn | warn_only_exported = topSigWarnIfExported export_occs sig_ns diff --git a/testsuite/tests/warnings/should_compile/T11077.hs b/testsuite/tests/warnings/should_compile/T11077.hs new file mode 100644 index 0000000..76533cb --- /dev/null +++ b/testsuite/tests/warnings/should_compile/T11077.hs @@ -0,0 +1,3 @@ +module T11077 (module X, foo) where +import Data.List as X +foo = undefined diff --git a/testsuite/tests/warnings/should_compile/T11077.stderr b/testsuite/tests/warnings/should_compile/T11077.stderr new file mode 100644 index 0000000..3cb2cba --- /dev/null +++ b/testsuite/tests/warnings/should_compile/T11077.stderr @@ -0,0 +1,3 @@ + +T11077.hs:3:1: warning: + Top-level binding with no type signature: foo :: forall t. t diff --git a/testsuite/tests/warnings/should_compile/all.T b/testsuite/tests/warnings/should_compile/all.T index 3954ba8..c2b8dd2 100644 --- a/testsuite/tests/warnings/should_compile/all.T +++ b/testsuite/tests/warnings/should_compile/all.T @@ -4,6 +4,7 @@ test('T9178', extra_clean(['T9178.o', 'T9178DataType.o', 'T9178.hi', 'T9178DataType.hi']), multimod_compile, ['T9178', '-Wall']) test('T9230', normal, compile_without_flag('-fno-warn-tabs'), ['']) +test('T11077', normal, compile, ['-fwarn-missing-exported-sigs']) test('T11128', normal, compile, ['']) test('DeprU', From git at git.haskell.org Wed Dec 2 20:56:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 2 Dec 2015 20:56:03 +0000 (UTC) Subject: [commit: ghc] master: Create empty dump files when there was nothing to dump (8cba907) Message-ID: <20151202205603.64F1B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8cba907ad404ba4005558b5a8966390159938172/ghc >--------------------------------------------------------------- commit 8cba907ad404ba4005558b5a8966390159938172 Author: Vladimir Trubilov Date: Wed Dec 2 20:47:23 2015 +0100 Create empty dump files when there was nothing to dump This patch creates empty dump file when GHC was run with `-ddump-rule-firings` (or `-ddump-rule-rewrites`) and `-ddump-to-file` specified, and there were no rules applied. If dump already exists it will be overwritten by empty one. Test Plan: ./validate Reviewers: austin, thomie, bgamari Reviewed By: thomie, bgamari Subscribers: thomie Projects: #ghc Differential Revision: https://phabricator.haskell.org/D1514 GHC Trac Issues: #10320 >--------------------------------------------------------------- 8cba907ad404ba4005558b5a8966390159938172 compiler/main/DriverPipeline.hs | 7 +- compiler/main/DynFlags.hs | 4 +- compiler/main/ErrUtils.hs | 93 ++++++++++++++++++-------- testsuite/tests/driver/Makefile | 39 +++++++++++ testsuite/tests/driver/T10320-with-rule.hs | 9 +++ testsuite/tests/driver/T10320-without-rules.hs | 4 ++ testsuite/tests/driver/all.T | 10 +++ 7 files changed, 135 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 8cba907ad404ba4005558b5a8966390159938172 From git at git.haskell.org Wed Dec 2 20:56:06 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 2 Dec 2015 20:56:06 +0000 (UTC) Subject: [commit: ghc] master: ErrUtils: Spruce up Haddocks (0d1a2d2) Message-ID: <20151202205606.08EED3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0d1a2d23be3c980d9710294fe52d010690a2e56e/ghc >--------------------------------------------------------------- commit 0d1a2d23be3c980d9710294fe52d010690a2e56e Author: Ben Gamari Date: Wed Dec 2 20:59:25 2015 +0100 ErrUtils: Spruce up Haddocks This is a pretty commonly needed module; Haddocks are worth the effort. >--------------------------------------------------------------- 0d1a2d23be3c980d9710294fe52d010690a2e56e compiler/main/ErrUtils.hs | 59 ++++++++++++++++++++++++++--------------------- 1 file changed, 33 insertions(+), 26 deletions(-) diff --git a/compiler/main/ErrUtils.hs b/compiler/main/ErrUtils.hs index 9fc9e49..5e585da 100644 --- a/compiler/main/ErrUtils.hs +++ b/compiler/main/ErrUtils.hs @@ -7,29 +7,35 @@ {-# LANGUAGE CPP #-} module ErrUtils ( - MsgDoc, + -- * Basic types Validity(..), andValid, allValid, isValid, getInvalids, + Severity(..), - ErrMsg, ErrDoc, errDoc, WarnMsg, Severity(..), + -- * Messages + MsgDoc, ErrMsg, ErrDoc, errDoc, WarnMsg, Messages, ErrorMessages, WarningMessages, errMsgSpan, errMsgContext, - mkLocMessage, pprMessageBag, pprErrMsgBagWithLoc, - pprLocErrMsg, makeIntoWarning, + errorsFound, isEmptyMessages, - errorsFound, emptyMessages, isEmptyMessages, + -- ** Formatting + pprMessageBag, pprErrMsgBagWithLoc, + pprLocErrMsg, printBagOfErrors, + + -- ** Construction + emptyMessages, mkLocMessage, makeIntoWarning, mkErrMsg, mkPlainErrMsg, mkErrDoc, mkLongErrMsg, mkWarnMsg, mkPlainWarnMsg, - printBagOfErrors, warnIsErrorMsg, mkLongWarnMsg, - ghcExit, + -- * Utilities doIfSet, doIfSet_dyn, + + -- * Dump files dumpIfSet, dumpIfSet_dyn, dumpIfSet_dyn_printer, mkDumpDoc, dumpSDoc, - openDumpFiles, closeDumpFiles, - -- * Messages during compilation + -- * Issuing messages during compilation putMsg, printInfoForUser, printOutputForUser, logInfo, logOutput, errorMsg, warningMsg, @@ -37,7 +43,7 @@ module ErrUtils ( compilationProgressMsg, showPass, debugTraceMsg, - + ghcExit, prettyPrintGhcErrors, ) where @@ -69,8 +75,8 @@ type MsgDoc = SDoc ------------------------- data Validity - = IsValid -- Everything is fine - | NotValid MsgDoc -- A problem, and some indication of why + = IsValid -- ^ Everything is fine + | NotValid MsgDoc -- ^ A problem, and some indication of why isValid :: Validity -> Bool isValid IsValid = True @@ -80,7 +86,8 @@ andValid :: Validity -> Validity -> Validity andValid IsValid v = v andValid v _ = v -allValid :: [Validity] -> Validity -- If they aren't all valid, return the first +-- | If they aren't all valid, return the first +allValid :: [Validity] -> Validity allValid [] = IsValid allValid (v : vs) = v `andValid` allValid vs @@ -127,16 +134,16 @@ data Severity | SevInteractive | SevDump - -- Log messagse intended for compiler developers + -- ^ Log messagse intended for compiler developers -- No file/line/column stuff | SevInfo - -- Log messages intended for end users. + -- ^ Log messages intended for end users. -- No file/line/column stuff. | SevWarning | SevError - -- SevWarning and SevError are used for warnings and errors + -- ^ SevWarning and SevError are used for warnings and errors -- o The message has a file/line/column heading, -- plus "warning:" or "error:", -- added by mkLocMessags @@ -186,11 +193,11 @@ mkErrDoc :: DynFlags -> SrcSpan -> PrintUnqualified -> ErrDoc -> ErrMsg mkErrDoc dflags = mk_err_msg dflags SevError mkLongErrMsg, mkLongWarnMsg :: DynFlags -> SrcSpan -> PrintUnqualified -> MsgDoc -> MsgDoc -> ErrMsg --- A long (multi-line) error message +-- ^ A long (multi-line) error message mkErrMsg, mkWarnMsg :: DynFlags -> SrcSpan -> PrintUnqualified -> MsgDoc -> ErrMsg --- A short (one-line) error message +-- ^ A short (one-line) error message mkPlainErrMsg, mkPlainWarnMsg :: DynFlags -> SrcSpan -> MsgDoc -> ErrMsg --- Variant that doesn't care about qualified/unqualified names +-- ^ Variant that doesn't care about qualified/unqualified names mkLongErrMsg dflags locn unqual msg extra = mk_err_msg dflags SevError locn unqual (ErrDoc [msg] [] [extra]) mkErrMsg dflags locn unqual msg = mk_err_msg dflags SevError locn unqual (ErrDoc [msg] [] []) @@ -330,14 +337,14 @@ closeDumpFiles dflags mapM_ hClose $ Map.elems gd -- | Write out a dump. --- If --dump-to-file is set then this goes to a file. --- otherwise emit to stdout. +-- If --dump-to-file is set then this goes to a file. +-- otherwise emit to stdout. -- --- When hdr is empty, we print in a more compact format (no separators and +-- When @hdr@ is empty, we print in a more compact format (no separators and -- blank lines) -- --- The DumpFlag is used only to choose the filename to use if --dump-to-file is --- used; it is not used to decide whether to dump the output +-- The 'DumpFlag' is used only to choose the filename to use if @--dump-to-file@ +-- is used; it is not used to decide whether to dump the output dumpSDoc :: DynFlags -> PrintUnqualified -> DumpFlag -> String -> SDoc -> IO () dumpSDoc dflags print_unqual flag hdr doc = do let mFile = chooseDumpFile dflags flag @@ -361,7 +368,7 @@ dumpSDoc dflags print_unqual flag hdr doc | otherwise = (mkDumpDoc hdr doc, SevDump) log_action dflags dflags severity noSrcSpan dump_style doc' --- | Return a handle assigned to the 'fileName' +-- | Return a handle assigned to the given filename. -- -- If the requested file doesn't exist the new one will be created getDumpFileHandle :: DynFlags -> FilePath -> IO Handle @@ -486,7 +493,7 @@ logInfo :: DynFlags -> PprStyle -> MsgDoc -> IO () logInfo dflags sty msg = log_action dflags dflags SevInfo noSrcSpan sty msg logOutput :: DynFlags -> PprStyle -> MsgDoc -> IO () --- Like logInfo but with SevOutput rather then SevInfo +-- ^ Like 'logInfo' but with 'SevOutput' rather then 'SevInfo' logOutput dflags sty msg = log_action dflags dflags SevOutput noSrcSpan sty msg prettyPrintGhcErrors :: ExceptionMonad m => DynFlags -> m a -> m a From git at git.haskell.org Wed Dec 2 21:10:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 2 Dec 2015 21:10:37 +0000 (UTC) Subject: [commit: ghc] master: Update bytestring submodule (e7929ba) Message-ID: <20151202211037.D34E43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e7929bac932da4951e8304f674896e6090aab905/ghc >--------------------------------------------------------------- commit e7929bac932da4951e8304f674896e6090aab905 Author: Herbert Valerio Riedel Date: Wed Dec 2 15:20:10 2015 +0100 Update bytestring submodule Differential Revision: https://phabricator.haskell.org/D1549 >--------------------------------------------------------------- e7929bac932da4951e8304f674896e6090aab905 libraries/bytestring | 2 +- testsuite/tests/safeHaskell/check/pkg01/ImpSafe03.stderr | 2 +- testsuite/tests/safeHaskell/check/pkg01/ImpSafeOnly07.stderr | 2 +- testsuite/tests/safeHaskell/check/pkg01/ImpSafeOnly08.stderr | 2 +- testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout | 6 +++--- 5 files changed, 7 insertions(+), 7 deletions(-) diff --git a/libraries/bytestring b/libraries/bytestring index c2ddcf9..84d0416 160000 --- a/libraries/bytestring +++ b/libraries/bytestring @@ -1 +1 @@ -Subproject commit c2ddcf96cdc6bf83206457a781801f6ff45a1aa6 +Subproject commit 84d041649c39e7dc0fe8d348da10d6ed1679a8f9 diff --git a/testsuite/tests/safeHaskell/check/pkg01/ImpSafe03.stderr b/testsuite/tests/safeHaskell/check/pkg01/ImpSafe03.stderr index 74b08a9..d8c8d67 100644 --- a/testsuite/tests/safeHaskell/check/pkg01/ImpSafe03.stderr +++ b/testsuite/tests/safeHaskell/check/pkg01/ImpSafe03.stderr @@ -1,4 +1,4 @@ [2 of 2] Compiling Main ( ImpSafe03.hs, ImpSafe03.o ) : - The package (bytestring-0.10.6.0) is required to be trusted but it isn't! + The package (bytestring-0.10.7.0) is required to be trusted but it isn't! diff --git a/testsuite/tests/safeHaskell/check/pkg01/ImpSafeOnly07.stderr b/testsuite/tests/safeHaskell/check/pkg01/ImpSafeOnly07.stderr index 0e6877b..0758def 100644 --- a/testsuite/tests/safeHaskell/check/pkg01/ImpSafeOnly07.stderr +++ b/testsuite/tests/safeHaskell/check/pkg01/ImpSafeOnly07.stderr @@ -3,4 +3,4 @@ The package (base-4.9.0.0) is required to be trusted but it isn't! : error: - The package (bytestring-0.10.6.0) is required to be trusted but it isn't! + The package (bytestring-0.10.7.0) is required to be trusted but it isn't! diff --git a/testsuite/tests/safeHaskell/check/pkg01/ImpSafeOnly08.stderr b/testsuite/tests/safeHaskell/check/pkg01/ImpSafeOnly08.stderr index 0e6877b..0758def 100644 --- a/testsuite/tests/safeHaskell/check/pkg01/ImpSafeOnly08.stderr +++ b/testsuite/tests/safeHaskell/check/pkg01/ImpSafeOnly08.stderr @@ -3,4 +3,4 @@ The package (base-4.9.0.0) is required to be trusted but it isn't! : error: - The package (bytestring-0.10.6.0) is required to be trusted but it isn't! + The package (bytestring-0.10.7.0) is required to be trusted but it isn't! diff --git a/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout b/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout index b5fa578..42e1778 100644 --- a/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout +++ b/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout @@ -29,17 +29,17 @@ trusted: safe require own pkg trusted: True M_SafePkg6 -package dependencies: array-0.5.1.0 base-4.9.0.0* bytestring-0.10.6.0* deepseq-1.4.1.1 ghc-prim-0.5.0.0 integer-gmp-1.0.0.0 +package dependencies: array-0.5.1.0 base-4.9.0.0* bytestring-0.10.7.0* deepseq-1.4.1.1 ghc-prim-0.5.0.0 integer-gmp-1.0.0.0 trusted: trustworthy require own pkg trusted: False M_SafePkg7 -package dependencies: array-0.5.1.0 base-4.9.0.0* bytestring-0.10.6.0* deepseq-1.4.1.1 ghc-prim-0.5.0.0 integer-gmp-1.0.0.0 +package dependencies: array-0.5.1.0 base-4.9.0.0* bytestring-0.10.7.0* deepseq-1.4.1.1 ghc-prim-0.5.0.0 integer-gmp-1.0.0.0 trusted: safe require own pkg trusted: False M_SafePkg8 -package dependencies: array-0.5.1.0 base-4.9.0.0 bytestring-0.10.6.0* deepseq-1.4.1.1 ghc-prim-0.5.0.0 integer-gmp-1.0.0.0 +package dependencies: array-0.5.1.0 base-4.9.0.0 bytestring-0.10.7.0* deepseq-1.4.1.1 ghc-prim-0.5.0.0 integer-gmp-1.0.0.0 trusted: trustworthy require own pkg trusted: False From git at git.haskell.org Wed Dec 2 22:55:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 2 Dec 2015 22:55:32 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: Major Overhaul of Pattern Match Checking (Fixes #595) (5d13d6b) Message-ID: <20151202225532.84D4E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/5d13d6b41fd00f2cb279416b8baa957b218e3ec5/ghc >--------------------------------------------------------------- commit 5d13d6b41fd00f2cb279416b8baa957b218e3ec5 Author: George Karachalias Date: Wed Dec 2 23:43:28 2015 +0100 Major Overhaul of Pattern Match Checking (Fixes #595) This patch adresses several problems concerned with exhaustiveness and redundancy checking of pattern matching. The list of improvements includes: * Making the check type-aware (handles GADTs, Type Families, DataKinds, etc.). This fixes #4139, #3927, #8970 and other related tickets. * Making the check laziness-aware. Cases that are overlapped but affect evaluation are issued now with "Patterns have inaccessible right hand side". Additionally, "Patterns are overlapped" is now replaced by "Patterns are redundant". * Improved messages for literals. This addresses tickets #5724, #2204, etc. * Improved reasoning concerning cases where simple and overloaded patterns are matched (See #322). * Substantially improved reasoning for pattern guards. Addresses #3078. * OverloadedLists extension does not break exhaustiveness checking anymore (addresses #9951). Note that in general this cannot be handled but if we know that an argument has type '[a]', we treat it as a list since, the instance of 'IsList' gives the identity for both 'fromList' and 'toList'. If the type is not clear or is not the list type, then the check cannot do much still. I am a bit concerned about OverlappingInstances though, since one may override the '[a]' instance with e.g. an '[Int]' instance that is not the identity. * Improved reasoning for nested pattern matching (partial solution). Now we propagate type and (some) term constraints deeper when checking, so we can detect more inconsistencies. For example, this is needed for #4139. I am still not satisfied with several things but I would like to address at least the following before the next release: Term constraints are too many and not printed for non-exhaustive matches (with the exception of literals). This sometimes results in two identical (in appearance) uncovered warnings. Unless we actually show their difference, I would like to have a single warning. >--------------------------------------------------------------- 5d13d6b41fd00f2cb279416b8baa957b218e3ec5 compiler/basicTypes/UniqSupply.hs | 26 +- compiler/deSugar/Check.hs | 2017 +++++++++++++------- compiler/deSugar/DsBinds.hs | 10 +- compiler/deSugar/DsExpr.hs | 18 +- compiler/deSugar/DsGRHSs.hs | 2 +- compiler/deSugar/DsMonad.hs | 64 +- compiler/deSugar/Match.hs | 174 +- compiler/deSugar/Match.hs-boot | 1 + compiler/deSugar/PmExpr.hs | 377 ++++ compiler/deSugar/TmOracle.hs | 455 +++++ compiler/ghc.cabal.in | 2 + compiler/ghc.mk | 1 + compiler/hsSyn/HsLit.hs | 22 + compiler/hsSyn/HsPat.hs | 41 +- compiler/prelude/TysWiredIn.hs-boot | 2 +- compiler/typecheck/TcMType.hs | 15 + compiler/typecheck/TcRnTypes.hs | 5 +- compiler/typecheck/TcSMonad.hs | 1 - compiler/typecheck/TcSimplify.hs | 14 + compiler/typecheck/TcType.hs | 42 + compiler/types/Type.hs | 22 +- compiler/utils/Bag.hs | 26 +- compiler/utils/MonadUtils.hs | 6 +- .../tests/deSugar/should_compile/T2395.stderr | 4 +- .../tests/deSugar/should_compile/T5117.stderr | 2 +- testsuite/tests/deSugar/should_compile/all.T | 1 - .../tests/deSugar/should_compile/ds002.stderr | 4 +- .../tests/deSugar/should_compile/ds003.stderr | 2 +- .../tests/deSugar/should_compile/ds019.stderr | 2 +- .../tests/deSugar/should_compile/ds020.stderr | 8 +- testsuite/tests/deSugar/should_compile/ds022.hs | 2 + .../tests/deSugar/should_compile/ds022.stderr | 4 +- .../tests/deSugar/should_compile/ds043.stderr | 6 +- .../tests/deSugar/should_compile/ds051.stderr | 6 +- .../tests/deSugar/should_compile/ds056.stderr | 4 +- .../tests/deSugar/should_compile/ds058.stderr | 6 +- testsuite/tests/deSugar/should_compile/ds060.hs | 25 - testsuite/tests/driver/werror.stderr | 4 +- testsuite/tests/gadt/Gadt17_help.hs | 1 - testsuite/tests/gadt/T7294.stderr | 4 + testsuite/tests/ghci/scripts/Defer02.stderr | 8 + testsuite/tests/{ado => pmcheck}/Makefile | 0 .../should_compile/Makefile | 0 testsuite/tests/pmcheck/should_compile/T2006.hs | 13 + .../tests/pmcheck/should_compile/T2006.stderr | 0 testsuite/tests/pmcheck/should_compile/T2204.hs | 9 + .../tests/pmcheck/should_compile/T2204.stderr | 14 + testsuite/tests/pmcheck/should_compile/T3078.hs | 12 + .../tests/pmcheck/should_compile/T3078.stderr | 0 testsuite/tests/pmcheck/should_compile/T322.hs | 29 + .../tests/pmcheck/should_compile/T322.stderr | 0 testsuite/tests/pmcheck/should_compile/T366.hs | 10 + .../tests/pmcheck/should_compile/T366.stderr | 0 testsuite/tests/pmcheck/should_compile/T3927.hs | 13 + .../tests/pmcheck/should_compile/T3927.stderr | 0 testsuite/tests/pmcheck/should_compile/T3927a.hs | 15 + .../tests/pmcheck/should_compile/T3927a.stderr | 0 testsuite/tests/pmcheck/should_compile/T3927b.hs | 75 + .../tests/pmcheck/should_compile/T3927b.stderr | 39 + testsuite/tests/pmcheck/should_compile/T4139.hs | 28 + .../tests/pmcheck/should_compile/T4139.stderr | 0 testsuite/tests/pmcheck/should_compile/T6124.hs | 14 + .../tests/pmcheck/should_compile/T6124.stderr | 0 testsuite/tests/pmcheck/should_compile/T7669.hs | 9 + .../tests/pmcheck/should_compile/T7669.stderr | 0 testsuite/tests/pmcheck/should_compile/T8970.hs | 22 + .../tests/pmcheck/should_compile/T8970.stderr | 0 testsuite/tests/pmcheck/should_compile/T9951.hs | 10 + .../tests/pmcheck/should_compile/T9951.stderr | 0 testsuite/tests/pmcheck/should_compile/T9951b.hs | 7 + .../tests/pmcheck/should_compile/T9951b.stderr | 9 + testsuite/tests/pmcheck/should_compile/all.T | 35 + testsuite/tests/pmcheck/should_compile/pmc001.hs | 22 + .../tests/pmcheck/should_compile/pmc001.stderr | 17 + testsuite/tests/pmcheck/should_compile/pmc002.hs | 7 + .../tests/pmcheck/should_compile/pmc002.stderr | 0 testsuite/tests/pmcheck/should_compile/pmc003.hs | 9 + .../tests/pmcheck/should_compile/pmc003.stderr | 3 + testsuite/tests/pmcheck/should_compile/pmc004.hs | 16 + .../tests/pmcheck/should_compile/pmc004.stderr | 3 + testsuite/tests/pmcheck/should_compile/pmc005.hs | 12 + .../tests/pmcheck/should_compile/pmc005.stderr | 7 + testsuite/tests/pmcheck/should_compile/pmc006.hs | 22 + .../tests/pmcheck/should_compile/pmc006.stderr | 0 testsuite/tests/pmcheck/should_compile/pmc007.hs | 20 + .../tests/pmcheck/should_compile/pmc007.stderr | 24 + .../tests/typecheck/should_compile/T5490.stderr | 8 + 87 files changed, 3056 insertions(+), 913 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 5d13d6b41fd00f2cb279416b8baa957b218e3ec5 From git at git.haskell.org Wed Dec 2 22:55:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 2 Dec 2015 22:55:34 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm's head updated: Major Overhaul of Pattern Match Checking (Fixes #595) (5d13d6b) Message-ID: <20151202225534.C06473A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/gadtpm' now includes: 218fdf9 Make the order of fixities in the iface file deterministic 741f837 Implement more deterministic operations and document them 52b02e6 Comments only (isIrrefutablePat) b564731 Comments (TcSMonad) d00cdf2 Revert "ghci: Add support for prompt functions" 1caff20 StgSyn: Remove unused SRT constructor c75948b Move Stg-specific code from DynFlags to SimplStg d4d54b4 Remove *.xml from gitignore a12e47b Avoid panic due to partial ieName 8cba907 Create empty dump files when there was nothing to dump 0d1a2d2 ErrUtils: Spruce up Haddocks e7929ba Update bytestring submodule 5d13d6b Major Overhaul of Pattern Match Checking (Fixes #595) From git at git.haskell.org Thu Dec 3 09:37:22 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 3 Dec 2015 09:37:22 +0000 (UTC) Subject: [commit: ghc] master: users_guide/glasgow_exts.rst: fix link markup (d25f3c0) Message-ID: <20151203093722.20D393A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d25f3c076e6c47bc7c8d0d27e724a3ad2b7d7399/ghc >--------------------------------------------------------------- commit d25f3c076e6c47bc7c8d0d27e724a3ad2b7d7399 Author: Sergei Trofimovich Date: Thu Dec 3 09:31:44 2015 +0000 users_guide/glasgow_exts.rst: fix link markup sphinx-1.3.1 found errors as: users_guide/glasgow_exts.rst:1799: WARNING: malformed hyperlink target. users_guide/glasgow_exts.rst:10638: WARNING: Inline interpreted text or phrase reference start-string without end-string. Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- d25f3c076e6c47bc7c8d0d27e724a3ad2b7d7399 docs/users_guide/glasgow_exts.rst | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index 11cebb1..4513f74 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -1796,7 +1796,7 @@ In the case of transform comprehensions, notice that the groups are parameterised over some arbitrary type ``n`` (provided it has an ``fmap``, as well as the comprehension being over an arbitrary monad. -.. _monadfail-desugaring +.. _monadfail-desugaring: New monadic failure desugaring mechanism ---------------------------------------- @@ -10642,7 +10642,7 @@ strict, regardless of the pattern. (We say "apparent" exception because the Right Way to think of it is that the bang at the top of a binding is not part of the *pattern*; rather it is part of the syntax of the *binding*, creating a "bang-pattern binding".) See :ref:`Strict recursive and -polymorphic let bindings for +polymorphic let bindings ` for how bang-pattern bindings are compiled. However, *nested* bangs in a pattern binding behave uniformly with all From git at git.haskell.org Thu Dec 3 10:46:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 3 Dec 2015 10:46:13 +0000 (UTC) Subject: [commit: ghc] tag 'ghc-7.10.3-release' created Message-ID: <20151203104613.0F0BD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New tag : ghc-7.10.3-release Referencing: 5c2495781f013a9adaab3bb96a8fdfc564f56f7b From git at git.haskell.org Thu Dec 3 10:46:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 3 Dec 2015 10:46:15 +0000 (UTC) Subject: [commit: ghc] : release notes: Cabal/haddock/Windows issue is now fixed (6b0795d) Message-ID: <20151203104615.A90193A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : Link : http://ghc.haskell.org/trac/ghc/changeset/6b0795d66047c457bed967997833e4d3ec71f61e/ghc >--------------------------------------------------------------- commit 6b0795d66047c457bed967997833e4d3ec71f61e Author: Ben Gamari Date: Mon Nov 30 22:41:56 2015 +0100 release notes: Cabal/haddock/Windows issue is now fixed >--------------------------------------------------------------- 6b0795d66047c457bed967997833e4d3ec71f61e docs/users_guide/7.10.3-notes.xml | 7 ------- 1 file changed, 7 deletions(-) diff --git a/docs/users_guide/7.10.3-notes.xml b/docs/users_guide/7.10.3-notes.xml index 358d9fc..120299a 100644 --- a/docs/users_guide/7.10.3-notes.xml +++ b/docs/users_guide/7.10.3-notes.xml @@ -156,13 +156,6 @@ - The Cabal release shipped with this GHC release lacks - support for response files, a mechanism used on Windows to workaround the - low command-line length limit on that platform. For this reason you - may experience line length issues when building Haddock documentation with Cabal - on Windows. - - At the time of release there is a fix in the Cabal upstream respository, although it is not yet From git at git.haskell.org Thu Dec 3 10:46:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 3 Dec 2015 10:46:18 +0000 (UTC) Subject: [commit: ghc] : configure.ac: Set RELEASE=YES, version 7.10.3 (97e7c29) Message-ID: <20151203104618.4384A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : Link : http://ghc.haskell.org/trac/ghc/changeset/97e7c293abbde5223d2bf0516f8969bdd1a9a7a2/ghc >--------------------------------------------------------------- commit 97e7c293abbde5223d2bf0516f8969bdd1a9a7a2 Author: Ben Gamari Date: Tue Dec 1 00:37:29 2015 +0100 configure.ac: Set RELEASE=YES, version 7.10.3 >--------------------------------------------------------------- 97e7c293abbde5223d2bf0516f8969bdd1a9a7a2 configure.ac | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/configure.ac b/configure.ac index 0af15e8..37601ae 100644 --- a/configure.ac +++ b/configure.ac @@ -13,10 +13,10 @@ dnl # see what flags are available. (Better yet, read the documentation!) # -AC_INIT([The Glorious Glasgow Haskell Compilation System], [7.10.2], [glasgow-haskell-bugs at haskell.org], [ghc]) +AC_INIT([The Glorious Glasgow Haskell Compilation System], [7.10.3], [glasgow-haskell-bugs at haskell.org], [ghc]) # Set this to YES for a released version, otherwise NO -: ${RELEASE=NO} +: ${RELEASE=YES} # 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 Thu Dec 3 10:48:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 3 Dec 2015 10:48:03 +0000 (UTC) Subject: [commit: ghc] ghc-7.10's head updated: configure.ac: Set RELEASE=YES, version 7.10.3 (97e7c29) Message-ID: <20151203104803.2F86A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'ghc-7.10' now includes: 6b0795d release notes: Cabal/haddock/Windows issue is now fixed 97e7c29 configure.ac: Set RELEASE=YES, version 7.10.3 From git at git.haskell.org Thu Dec 3 11:58:04 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 3 Dec 2015 11:58:04 +0000 (UTC) Subject: [commit: ghc] master: Major Overhaul of Pattern Match Checking (Fixes #595) (8a50610) Message-ID: <20151203115804.18DB93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8a506104d5b5b71d5640afc69c992e0af40f2213/ghc >--------------------------------------------------------------- commit 8a506104d5b5b71d5640afc69c992e0af40f2213 Author: George Karachalias Date: Thu Dec 3 12:57:19 2015 +0100 Major Overhaul of Pattern Match Checking (Fixes #595) This patch adresses several problems concerned with exhaustiveness and redundancy checking of pattern matching. The list of improvements includes: * Making the check type-aware (handles GADTs, Type Families, DataKinds, etc.). This fixes #4139, #3927, #8970 and other related tickets. * Making the check laziness-aware. Cases that are overlapped but affect evaluation are issued now with "Patterns have inaccessible right hand side". Additionally, "Patterns are overlapped" is now replaced by "Patterns are redundant". * Improved messages for literals. This addresses tickets #5724, #2204, etc. * Improved reasoning concerning cases where simple and overloaded patterns are matched (See #322). * Substantially improved reasoning for pattern guards. Addresses #3078. * OverloadedLists extension does not break exhaustiveness checking anymore (addresses #9951). Note that in general this cannot be handled but if we know that an argument has type '[a]', we treat it as a list since, the instance of 'IsList' gives the identity for both 'fromList' and 'toList'. If the type is not clear or is not the list type, then the check cannot do much still. I am a bit concerned about OverlappingInstances though, since one may override the '[a]' instance with e.g. an '[Int]' instance that is not the identity. * Improved reasoning for nested pattern matching (partial solution). Now we propagate type and (some) term constraints deeper when checking, so we can detect more inconsistencies. For example, this is needed for #4139. I am still not satisfied with several things but I would like to address at least the following before the next release: Term constraints are too many and not printed for non-exhaustive matches (with the exception of literals). This sometimes results in two identical (in appearance) uncovered warnings. Unless we actually show their difference, I would like to have a single warning. >--------------------------------------------------------------- 8a506104d5b5b71d5640afc69c992e0af40f2213 compiler/basicTypes/UniqSupply.hs | 26 +- compiler/deSugar/Check.hs | 2017 +++++++++++++------- compiler/deSugar/DsBinds.hs | 10 +- compiler/deSugar/DsExpr.hs | 18 +- compiler/deSugar/DsGRHSs.hs | 2 +- compiler/deSugar/DsMonad.hs | 64 +- compiler/deSugar/Match.hs | 174 +- compiler/deSugar/Match.hs-boot | 1 + compiler/deSugar/PmExpr.hs | 377 ++++ compiler/deSugar/TmOracle.hs | 455 +++++ compiler/ghc.cabal.in | 2 + compiler/ghc.mk | 1 + compiler/hsSyn/HsLit.hs | 22 + compiler/hsSyn/HsPat.hs | 41 +- compiler/prelude/TysWiredIn.hs-boot | 2 +- compiler/typecheck/TcMType.hs | 15 + compiler/typecheck/TcRnTypes.hs | 5 +- compiler/typecheck/TcSMonad.hs | 1 - compiler/typecheck/TcSimplify.hs | 14 + compiler/typecheck/TcType.hs | 42 + compiler/types/Type.hs | 22 +- compiler/utils/Bag.hs | 26 +- compiler/utils/MonadUtils.hs | 6 +- .../tests/deSugar/should_compile/T2395.stderr | 4 +- .../tests/deSugar/should_compile/T5117.stderr | 2 +- testsuite/tests/deSugar/should_compile/all.T | 1 - .../tests/deSugar/should_compile/ds002.stderr | 4 +- .../tests/deSugar/should_compile/ds003.stderr | 2 +- .../tests/deSugar/should_compile/ds019.stderr | 2 +- .../tests/deSugar/should_compile/ds020.stderr | 8 +- testsuite/tests/deSugar/should_compile/ds022.hs | 2 + .../tests/deSugar/should_compile/ds022.stderr | 4 +- .../tests/deSugar/should_compile/ds043.stderr | 6 +- .../tests/deSugar/should_compile/ds051.stderr | 6 +- .../tests/deSugar/should_compile/ds056.stderr | 4 +- .../tests/deSugar/should_compile/ds058.stderr | 6 +- testsuite/tests/deSugar/should_compile/ds060.hs | 25 - testsuite/tests/driver/werror.stderr | 4 +- testsuite/tests/gadt/Gadt17_help.hs | 1 - testsuite/tests/gadt/T7294.stderr | 4 + testsuite/tests/ghci/scripts/Defer02.stderr | 8 + testsuite/tests/{ado => pmcheck}/Makefile | 0 .../should_compile/Makefile | 0 testsuite/tests/pmcheck/should_compile/T2006.hs | 13 + .../tests/pmcheck/should_compile/T2006.stderr | 0 testsuite/tests/pmcheck/should_compile/T2204.hs | 9 + .../tests/pmcheck/should_compile/T2204.stderr | 14 + testsuite/tests/pmcheck/should_compile/T3078.hs | 12 + .../tests/pmcheck/should_compile/T3078.stderr | 0 testsuite/tests/pmcheck/should_compile/T322.hs | 29 + .../tests/pmcheck/should_compile/T322.stderr | 0 testsuite/tests/pmcheck/should_compile/T366.hs | 10 + .../tests/pmcheck/should_compile/T366.stderr | 0 testsuite/tests/pmcheck/should_compile/T3927.hs | 13 + .../tests/pmcheck/should_compile/T3927.stderr | 0 testsuite/tests/pmcheck/should_compile/T3927a.hs | 15 + .../tests/pmcheck/should_compile/T3927a.stderr | 0 testsuite/tests/pmcheck/should_compile/T3927b.hs | 75 + .../tests/pmcheck/should_compile/T3927b.stderr | 39 + testsuite/tests/pmcheck/should_compile/T4139.hs | 28 + .../tests/pmcheck/should_compile/T4139.stderr | 0 testsuite/tests/pmcheck/should_compile/T6124.hs | 14 + .../tests/pmcheck/should_compile/T6124.stderr | 0 testsuite/tests/pmcheck/should_compile/T7669.hs | 9 + .../tests/pmcheck/should_compile/T7669.stderr | 0 testsuite/tests/pmcheck/should_compile/T8970.hs | 22 + .../tests/pmcheck/should_compile/T8970.stderr | 0 testsuite/tests/pmcheck/should_compile/T9951.hs | 10 + .../tests/pmcheck/should_compile/T9951.stderr | 0 testsuite/tests/pmcheck/should_compile/T9951b.hs | 7 + .../tests/pmcheck/should_compile/T9951b.stderr | 9 + testsuite/tests/pmcheck/should_compile/all.T | 35 + testsuite/tests/pmcheck/should_compile/pmc001.hs | 22 + .../tests/pmcheck/should_compile/pmc001.stderr | 17 + testsuite/tests/pmcheck/should_compile/pmc002.hs | 7 + .../tests/pmcheck/should_compile/pmc002.stderr | 0 testsuite/tests/pmcheck/should_compile/pmc003.hs | 9 + .../tests/pmcheck/should_compile/pmc003.stderr | 3 + testsuite/tests/pmcheck/should_compile/pmc004.hs | 16 + .../tests/pmcheck/should_compile/pmc004.stderr | 3 + testsuite/tests/pmcheck/should_compile/pmc005.hs | 12 + .../tests/pmcheck/should_compile/pmc005.stderr | 7 + testsuite/tests/pmcheck/should_compile/pmc006.hs | 22 + .../tests/pmcheck/should_compile/pmc006.stderr | 0 testsuite/tests/pmcheck/should_compile/pmc007.hs | 20 + .../tests/pmcheck/should_compile/pmc007.stderr | 24 + .../tests/typecheck/should_compile/T5490.stderr | 8 + 87 files changed, 3056 insertions(+), 913 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 8a506104d5b5b71d5640afc69c992e0af40f2213 From git at git.haskell.org Thu Dec 3 13:44:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 3 Dec 2015 13:44:32 +0000 (UTC) Subject: [commit: ghc] master: testsuite: haddock.compiler: Bump expected allocations (43a31fe) Message-ID: <20151203134432.68B723A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/43a31fe4c0cc0f72dfe9e0c96e1576f5cfba6e19/ghc >--------------------------------------------------------------- commit 43a31fe4c0cc0f72dfe9e0c96e1576f5cfba6e19 Author: Ben Gamari Date: Thu Dec 3 14:44:24 2015 +0100 testsuite: haddock.compiler: Bump expected allocations >--------------------------------------------------------------- 43a31fe4c0cc0f72dfe9e0c96e1576f5cfba6e19 testsuite/tests/perf/haddock/all.T | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/perf/haddock/all.T b/testsuite/tests/perf/haddock/all.T index c7a60e3..22107a9 100644 --- a/testsuite/tests/perf/haddock/all.T +++ b/testsuite/tests/perf/haddock/all.T @@ -89,7 +89,7 @@ test('haddock.Cabal', test('haddock.compiler', [unless(in_tree_compiler(), skip), req_haddock ,stats_num_field('bytes allocated', - [(wordsize(64), 40624322224, 10) + [(wordsize(64), 44721228752, 10) # 2012P-08-14: 26070600504 (amd64/Linux) # 2012-08-29: 26353100288 (amd64/Linux, new CG) # 2012-09-18: 26882813032 (amd64/Linux) @@ -100,6 +100,7 @@ test('haddock.compiler', # 2014-11-22: 33562468736 (amd64/Linux) # 2015-06-02: 36740649320 (amd64/Linux) unknown cause # 2015-06-29: 40624322224 (amd64/Linux) due to #10482, not yet investigated + # 2015-12-03: 44721228752 (amd64/Linux) slow creep upwards ,(platform('i386-unknown-mingw32'), 902576468, 10) # 2012-10-30: 13773051312 (x86/Windows) From git at git.haskell.org Thu Dec 3 21:11:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 3 Dec 2015 21:11:47 +0000 (UTC) Subject: [commit: ghc] master: extending_ghc.rst: fix broken link (Trac #10950) (a034031) Message-ID: <20151203211147.6DF063A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a034031a102bc08c76a6cdb104b72922ae22c96b/ghc >--------------------------------------------------------------- commit a034031a102bc08c76a6cdb104b72922ae22c96b Author: Sergei Trofimovich Date: Thu Dec 3 21:07:19 2015 +0000 extending_ghc.rst: fix broken link (Trac #10950) The error exibits as build failures of two types: 1. extending_ghc.rst:: ERROR: Anonymous hyperlink mismatch: 1 references but 0 targets. See "backrefs" attribute for IDs. 2. reading sources... [ 33%] glasgow_exts Exception occurred: pickle.dump(doctree, f, pickle.HIGHEST_PROTOCOL) RecursionError: maximum recursion depth exceeded while pickling an object Broken link created circular reference and failed to serialize the result. Fixed the problem by pointing to relevant section. Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- a034031a102bc08c76a6cdb104b72922ae22c96b docs/users_guide/extending_ghc.rst | 2 +- docs/users_guide/glasgow_exts.rst | 2 ++ 2 files changed, 3 insertions(+), 1 deletion(-) diff --git a/docs/users_guide/extending_ghc.rst b/docs/users_guide/extending_ghc.rst index efe18b0..a0c3bd1 100644 --- a/docs/users_guide/extending_ghc.rst +++ b/docs/users_guide/extending_ghc.rst @@ -58,7 +58,7 @@ A number of restrictions apply to use of annotations: - The expression you are annotating with must have a type with ``Typeable`` and ``Data`` instances -- The `Template Haskell staging restrictions <>`__ apply to the +- The :ref:`Template Haskell staging restrictions ` apply to the expression being annotated with, so for example you cannot run a function from the module being compiled. diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index 4513f74..93261a2 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -9772,6 +9772,8 @@ The syntax for a declaration splice uses "``$``" not "``splice``". The type of the enclosed expression must be ``Q [Dec]``, not ``[Q Dec]``. Typed expression splices and quotations are supported.) +.. _th-usage: + Using Template Haskell ---------------------- From git at git.haskell.org Thu Dec 3 22:00:42 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 3 Dec 2015 22:00:42 +0000 (UTC) Subject: [commit: ghc] master: Update test output (934b3a0) Message-ID: <20151203220042.CEDA93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/934b3a06af6e716e20f4d9aa1c22c9d9300568dd/ghc >--------------------------------------------------------------- commit 934b3a06af6e716e20f4d9aa1c22c9d9300568dd Author: Ben Gamari Date: Thu Dec 3 15:20:01 2015 -0500 Update test output >--------------------------------------------------------------- 934b3a06af6e716e20f4d9aa1c22c9d9300568dd testsuite/tests/th/TH_repUnboxedTuples.stderr | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/testsuite/tests/th/TH_repUnboxedTuples.stderr b/testsuite/tests/th/TH_repUnboxedTuples.stderr index d5bfa68..4ae798c 100644 --- a/testsuite/tests/th/TH_repUnboxedTuples.stderr +++ b/testsuite/tests/th/TH_repUnboxedTuples.stderr @@ -3,3 +3,7 @@ case (# 'b', GHC.Types.False #) of (# 'a', GHC.Types.True #) -> (# "One", 1 #) (# 'b', GHC.Types.False #) -> (# "Two", 2 #) (# _, _ #) -> (# "Three", 3 #) + +TH_repUnboxedTuples.hs:18:13: warning: + Pattern match(es) are redundant + In a case alternative: (# 'a', True #) -> ... From git at git.haskell.org Thu Dec 3 22:00:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 3 Dec 2015 22:00:45 +0000 (UTC) Subject: [commit: ghc] master: Kill redundant patterns (0dd61fe) Message-ID: <20151203220045.76E7B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0dd61fe72144a829a9e5bb87a1094244e53cdebb/ghc >--------------------------------------------------------------- commit 0dd61fe72144a829a9e5bb87a1094244e53cdebb Author: Ben Gamari Date: Thu Dec 3 13:43:39 2015 -0500 Kill redundant patterns George's new exhaustiveness checker now realizes these are impossible. Yay! >--------------------------------------------------------------- 0dd61fe72144a829a9e5bb87a1094244e53cdebb compiler/cmm/Hoopl/Dataflow.hs | 5 ----- compiler/nativeGen/RegAlloc/Graph/Main.hs | 3 --- compiler/nativeGen/RegAlloc/Liveness.hs | 2 -- 3 files changed, 10 deletions(-) diff --git a/compiler/cmm/Hoopl/Dataflow.hs b/compiler/cmm/Hoopl/Dataflow.hs index 29c7afe..beaf6bc 100644 --- a/compiler/cmm/Hoopl/Dataflow.hs +++ b/compiler/cmm/Hoopl/Dataflow.hs @@ -163,7 +163,6 @@ arfGraph pass at FwdPass { fp_lattice = lattice, -> Fact e f -> UniqSM (DG f n e C, Fact C f) c NothingC (JustO entry) f = (block entry `cat` body (successors entry) bdy) f c (JustC entries) NothingO f = body entries bdy f - c _ _ _ = error "bogus GADT pattern match failure" -- Lift from nodes to blocks block BNil f = return (dgnil, f) @@ -253,7 +252,6 @@ analyzeFwd FwdPass { fp_lattice = lattice, = case (entries, entry) of (NothingC, JustO entry) -> block entry `cat` body (successors entry) (JustC entries, NothingO) -> body entries - _ -> error "bogus GADT pattern match failure" where body :: [Label] -> Fact C f -> Fact C f body entries f @@ -296,7 +294,6 @@ analyzeFwdBlocks FwdPass { fp_lattice = lattice, = case (entries, entry) of (NothingC, JustO entry) -> block entry `cat` body (successors entry) (JustC entries, NothingO) -> body entries - _ -> error "bogus GADT pattern match failure" where body :: [Label] -> Fact C f -> Fact C f body entries f @@ -339,7 +336,6 @@ analyzeBwd BwdPass { bp_lattice = lattice, = case (entries, entry) of (NothingC, JustO entry) -> body (successors entry) (JustC entries, NothingO) -> body entries - _ -> error "bogus GADT pattern match failure" where body :: [Label] -> Fact C f -> Fact C f body entries f @@ -429,7 +425,6 @@ arbGraph pass at BwdPass { bp_lattice = lattice, -> Fact C f -> UniqSM (DG f n e C, Fact e f) c NothingC (JustO entry) f = (block entry `cat` body (successors entry) bdy) f c (JustC entries) NothingO f = body entries bdy f - c _ _ _ = error "bogus GADT pattern match failure" -- Lift from nodes to blocks block BNil f = return (dgnil, f) diff --git a/compiler/nativeGen/RegAlloc/Graph/Main.hs b/compiler/nativeGen/RegAlloc/Graph/Main.hs index 05db68d..8d5a4db 100644 --- a/compiler/nativeGen/RegAlloc/Graph/Main.hs +++ b/compiler/nativeGen/RegAlloc/Graph/Main.hs @@ -355,9 +355,6 @@ graphAddCoalesce (r1, r2) graph , RegReal _ <- r2 = graph -graphAddCoalesce _ _ - = panic "graphAddCoalesce: bogus" - -- | Patch registers in code using the reg -> reg mapping in this graph. patchRegsFromGraph diff --git a/compiler/nativeGen/RegAlloc/Liveness.hs b/compiler/nativeGen/RegAlloc/Liveness.hs index 167197d..c1c2e3c 100644 --- a/compiler/nativeGen/RegAlloc/Liveness.hs +++ b/compiler/nativeGen/RegAlloc/Liveness.hs @@ -909,8 +909,6 @@ livenessForward platform rsLiveEntry (li@(LiveInstr instr mLive) : lis) in LiveInstr instr (Just live { liveBorn = rsBorn }) : livenessForward platform rsLiveNext lis -livenessForward _ _ _ = panic "RegLiveness.livenessForward: no match" - -- | Calculate liveness going backwards, -- filling in when regs die, and what regs are live across each instruction From git at git.haskell.org Thu Dec 3 22:00:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 3 Dec 2015 22:00:48 +0000 (UTC) Subject: [commit: ghc] master: Fix haddock syntax (7b29b0b) Message-ID: <20151203220048.53E593A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7b29b0b1e8efac68fd4151cb5a44c4290a3e9d57/ghc >--------------------------------------------------------------- commit 7b29b0b1e8efac68fd4151cb5a44c4290a3e9d57 Author: Ben Gamari Date: Thu Dec 3 13:43:16 2015 -0500 Fix haddock syntax Sadly we can't annotate the elements of a tuple >--------------------------------------------------------------- 7b29b0b1e8efac68fd4151cb5a44c4290a3e9d57 compiler/deSugar/Check.hs | 11 ++++++++--- 1 file changed, 8 insertions(+), 3 deletions(-) diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs index 8ca0b54..382112c 100644 --- a/compiler/deSugar/Check.hs +++ b/compiler/deSugar/Check.hs @@ -117,9 +117,14 @@ data ValSetAbs -- Reprsents a set of value vector abstractions | Constraint [PmConstraint] ValSetAbs -- ^ Extend Delta | Cons ValAbs ValSetAbs -- ^ map (ucon u) vs -type PmResult = ( [[LPat Id]] -- ^ redundant clauses - , [[LPat Id]] -- ^ clauses with inaccessible rhs - , [([PmExpr], [ComplexEq])] ) -- ^ missing +-- | Pattern check result +-- +-- * redundant clauses +-- * clauses with inaccessible RHS +-- * missing +type PmResult = ( [[LPat Id]] + , [[LPat Id]] + , [([PmExpr], [ComplexEq])] ) {- %************************************************************************ From git at git.haskell.org Thu Dec 3 22:00:50 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 3 Dec 2015 22:00:50 +0000 (UTC) Subject: [commit: ghc] master: Revert "Create empty dump files when there was nothing to dump" (c5597bb) Message-ID: <20151203220050.F3A433A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c5597bb6da612e0578290c3bccdac089d6519e19/ghc >--------------------------------------------------------------- commit c5597bb6da612e0578290c3bccdac089d6519e19 Author: Ben Gamari Date: Thu Dec 3 14:59:18 2015 +0100 Revert "Create empty dump files when there was nothing to dump" This reverts commit 8cba907ad404ba4005558b5a8966390159938172 which broke `-ddump-to-file`. >--------------------------------------------------------------- c5597bb6da612e0578290c3bccdac089d6519e19 compiler/main/DriverPipeline.hs | 7 +- compiler/main/DynFlags.hs | 4 +- compiler/main/ErrUtils.hs | 90 ++++++++------------------ testsuite/tests/driver/Makefile | 39 ----------- testsuite/tests/driver/T10320-with-rule.hs | 9 --- testsuite/tests/driver/T10320-without-rules.hs | 4 -- testsuite/tests/driver/all.T | 10 --- 7 files changed, 30 insertions(+), 133 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c5597bb6da612e0578290c3bccdac089d6519e19 From git at git.haskell.org Thu Dec 3 22:00:53 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 3 Dec 2015 22:00:53 +0000 (UTC) Subject: [commit: ghc] master: Bump hoopl submodule (40fc353) Message-ID: <20151203220053.993EA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/40fc353650d44472203153b04302a3614a0552eb/ghc >--------------------------------------------------------------- commit 40fc353650d44472203153b04302a3614a0552eb Author: Ben Gamari Date: Thu Dec 3 15:20:18 2015 -0500 Bump hoopl submodule To fix redundant patterns. >--------------------------------------------------------------- 40fc353650d44472203153b04302a3614a0552eb libraries/hoopl | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/hoopl b/libraries/hoopl index 84255f0..5405469 160000 --- a/libraries/hoopl +++ b/libraries/hoopl @@ -1 +1 @@ -Subproject commit 84255f0fe07f3fd1f5bc96e60b64c582394edcf1 +Subproject commit 5405469b2357580a653ceb41c15c33091b2d1a06 From git at git.haskell.org Fri Dec 4 06:51:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 4 Dec 2015 06:51:59 +0000 (UTC) Subject: [commit: ghc] master: Improve performance for PM check on literals (Fixes #11160 and #11161) (ae4398d) Message-ID: <20151204065159.7AE233A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ae4398d64655b43606386dddb01637bbfcf0171e/ghc >--------------------------------------------------------------- commit ae4398d64655b43606386dddb01637bbfcf0171e Author: George Karachalias Date: Fri Dec 4 07:11:55 2015 +0100 Improve performance for PM check on literals (Fixes #11160 and #11161) Two changes: 1. Instead of generating constraints of the form (x ~ e) (as we do in the paper), generate constraints of the form (e ~ e). The term oracle (`tmOracle` in deSugar/TmOracle.hs) is not really efficient and in the presence of many (x ~ e) constraints behaves quadratically. For literals, constraints of the form (False ~ (x ~ lit)) are pretty common, so if we start with { y ~ False, y ~ (x ~ lit) } we end up givng to the solver (a) twice as many constraints as we need and (b) half of them trigger the solver's weakness. This fixes #11160. 2. Treat two overloaded literals that look different as different. This is not entirely correct but it is what both the previous and the current check did. I had the ambitious plan to do the *right thing* (equality between overloaded literals is undecidable in the general case) and just use this assumption when issuing the warnings. It seems to generate much more constraints than I expected (breaks #11161) so I just do it immediately now instead of generating everything and filtering afterwards. Even if it is not (strictly speaking) correct, we have the following: * Gives the "expected" warnings (the ones Ocaml or the previous algorithm would give) and, * Most importantly, it is safe. Unless a catch-all clause exists, a match against literals is always non-exhaustive. So, effectively this affects only what is shown to the user (and, evidently, performance!). >--------------------------------------------------------------- ae4398d64655b43606386dddb01637bbfcf0171e compiler/deSugar/Check.hs | 128 ++++++++-------------- compiler/deSugar/PmExpr.hs | 24 ++--- compiler/deSugar/TmOracle.hs | 247 +++---------------------------------------- 3 files changed, 70 insertions(+), 329 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ae4398d64655b43606386dddb01637bbfcf0171e From git at git.haskell.org Fri Dec 4 07:29:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 4 Dec 2015 07:29:15 +0000 (UTC) Subject: [commit: ghc] master: Remove unused import in deSugar/TmOracle.hs (99d01e1) Message-ID: <20151204072915.486A03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/99d01e1d82505e168224043d10e7ce116f5617ae/ghc >--------------------------------------------------------------- commit 99d01e1d82505e168224043d10e7ce116f5617ae Author: George Karachalias Date: Fri Dec 4 08:28:00 2015 +0100 Remove unused import in deSugar/TmOracle.hs >--------------------------------------------------------------- 99d01e1d82505e168224043d10e7ce116f5617ae compiler/deSugar/TmOracle.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/compiler/deSugar/TmOracle.hs b/compiler/deSugar/TmOracle.hs index 3731f80..c0c1480 100644 --- a/compiler/deSugar/TmOracle.hs +++ b/compiler/deSugar/TmOracle.hs @@ -32,7 +32,6 @@ import TcHsSyn import MonadUtils import Util -import Data.Maybe (isJust) import qualified Data.Map as Map {- From git at git.haskell.org Fri Dec 4 09:12:06 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 4 Dec 2015 09:12:06 +0000 (UTC) Subject: [commit: ghc] master: Use Autoconf's AC_USE_SYSTEM_EXTENSIONS (7af29da) Message-ID: <20151204091206.A022B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7af29da05d2e5a5e311a5f73f20d0f232035973b/ghc >--------------------------------------------------------------- commit 7af29da05d2e5a5e311a5f73f20d0f232035973b Author: Herbert Valerio Riedel Date: Fri Dec 4 09:15:29 2015 +0100 Use Autoconf's AC_USE_SYSTEM_EXTENSIONS This takes care of setting feature test macros (i.e. let Autoconf decide when those can be set safely) to allow subsequent Autoconf tests to better detect available OS features. This also includes a submodule update of unix which enables the use of `AC_USE_SYSTEM_EXTENSIONS` in there as well. Specifically, this takes care of setting `_GNU_SOURCE` (which allows to remove two occurences where it's set manually) and `_ALL_SOURCE` (which fixes issues on AIX). See also https://www.gnu.org/software/autoconf/manual/autoconf-2.69/html_node/Posix-Variants.html for details. At some point we may want to reconsider the purpose of "rts/PosixSource.h" and rely more on Autoconf instead. >--------------------------------------------------------------- 7af29da05d2e5a5e311a5f73f20d0f232035973b configure.ac | 3 +++ libraries/base/configure.ac | 5 +++++ libraries/unix | 2 +- rts/Linker.c | 7 ------- rts/posix/OSThreads.c | 6 ------ 5 files changed, 9 insertions(+), 14 deletions(-) diff --git a/configure.ac b/configure.ac index 3889cea..57d877a 100644 --- a/configure.ac +++ b/configure.ac @@ -58,6 +58,9 @@ dnl #define SIZEOF_CHAR 0 dnl recently. AC_PREREQ([2.60]) +dnl make extensions visible to allow feature-tests to detect them lateron +AC_USE_SYSTEM_EXTENSIONS + # ------------------------------------------------------------------------- # Prepare to generate the following header files # diff --git a/libraries/base/configure.ac b/libraries/base/configure.ac index 85b2f2e..99474a6 100644 --- a/libraries/base/configure.ac +++ b/libraries/base/configure.ac @@ -3,6 +3,11 @@ AC_INIT([Haskell base package], [1.0], [libraries at haskell.org], [base]) # Safety check: Ensure that we are in the correct source directory. AC_CONFIG_SRCDIR([include/HsBase.h]) +AC_PREREQ([2.60]) + +dnl make extensions visible to allow feature-tests to detect them lateron +AC_USE_SYSTEM_EXTENSIONS + AC_CONFIG_HEADERS([include/HsBaseConfig.h include/EventConfig.h]) AC_CANONICAL_BUILD diff --git a/libraries/unix b/libraries/unix index 137fa1b..5740003 160000 --- a/libraries/unix +++ b/libraries/unix @@ -1 +1 @@ -Subproject commit 137fa1b06a79a9baa0d5fcf2ec11f964c3423f6a +Subproject commit 5740003e06f0c585460501514f3352f5e105c98c diff --git a/rts/Linker.c b/rts/Linker.c index 51142c5..f728f0e 100644 --- a/rts/Linker.c +++ b/rts/Linker.c @@ -10,13 +10,6 @@ #include "PosixSource.h" #endif -/* Linux needs _GNU_SOURCE to get RTLD_DEFAULT from and - MREMAP_MAYMOVE from . - */ -#if defined(__linux__) || defined(__GLIBC__) -#define _GNU_SOURCE 1 -#endif - #include "Rts.h" #include "HsFFI.h" diff --git a/rts/posix/OSThreads.c b/rts/posix/OSThreads.c index 8c1beda..91f9523 100644 --- a/rts/posix/OSThreads.c +++ b/rts/posix/OSThreads.c @@ -7,12 +7,6 @@ * * --------------------------------------------------------------------------*/ -#if defined(__linux__) || defined(__GLIBC__) -/* We want GNU extensions in DEBUG mode for mutex error checking */ -/* We also want the affinity API, which requires _GNU_SOURCE */ -#define _GNU_SOURCE -#endif - #include "PosixSource.h" #if defined(freebsd_HOST_OS) From git at git.haskell.org Fri Dec 4 09:12:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 4 Dec 2015 09:12:09 +0000 (UTC) Subject: [commit: ghc] master: RTS: Rename InCall.stat struct field to .rstat (cd9f3bf) Message-ID: <20151204091209.46D733A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cd9f3bf9b8068fc52bb61bc3badcc1c753fbd14b/ghc >--------------------------------------------------------------- commit cd9f3bf9b8068fc52bb61bc3badcc1c753fbd14b Author: Herbert Valerio Riedel Date: Fri Dec 4 10:10:55 2015 +0100 RTS: Rename InCall.stat struct field to .rstat On AIX, C system headers can redirect the token `stat` via #define stat stat64 to provide large-file support. Simply avoiding the use of `stat` as an identifier eschews macro-replacement. Differential Revision: https://phabricator.haskell.org/D1566 >--------------------------------------------------------------- cd9f3bf9b8068fc52bb61bc3badcc1c753fbd14b rts/RtsAPI.c | 4 ++-- rts/Schedule.c | 12 ++++++------ rts/Task.c | 2 +- rts/Task.h | 2 +- 4 files changed, 10 insertions(+), 10 deletions(-) diff --git a/rts/RtsAPI.c b/rts/RtsAPI.c index 2b3ad74..c64d8af 100644 --- a/rts/RtsAPI.c +++ b/rts/RtsAPI.c @@ -516,7 +516,7 @@ void rts_evalLazyIO_ (/* inout */ Capability **cap, void rts_checkSchedStatus (char* site, Capability *cap) { - SchedulerStatus rc = cap->running_task->incall->stat; + SchedulerStatus rc = cap->running_task->incall->rstat; switch (rc) { case Success: return; @@ -544,7 +544,7 @@ rts_checkSchedStatus (char* site, Capability *cap) SchedulerStatus rts_getSchedStatus (Capability *cap) { - return cap->running_task->incall->stat; + return cap->running_task->incall->rstat; } Capability * diff --git a/rts/Schedule.c b/rts/Schedule.c index abbc363..e3dd881 100644 --- a/rts/Schedule.c +++ b/rts/Schedule.c @@ -1293,19 +1293,19 @@ scheduleHandleThreadFinished (Capability *cap STG_UNUSED, Task *task, StgTSO *t) // NOTE: return val is stack->sp[1] (see StgStartup.hc) *(task->incall->ret) = (StgClosure *)task->incall->tso->stackobj->sp[1]; } - task->incall->stat = Success; + task->incall->rstat = Success; } else { if (task->incall->ret) { *(task->incall->ret) = NULL; } if (sched_state >= SCHED_INTERRUPTING) { if (heap_overflow) { - task->incall->stat = HeapExhausted; + task->incall->rstat = HeapExhausted; } else { - task->incall->stat = Interrupted; + task->incall->rstat = Interrupted; } } else { - task->incall->stat = Killed; + task->incall->rstat = Killed; } } #ifdef DEBUG @@ -2351,7 +2351,7 @@ scheduleWaitThread (StgTSO* tso, /*[out]*/HaskellObj* ret, Capability **pcap) task->incall->tso = tso; task->incall->ret = ret; - task->incall->stat = NoStatus; + task->incall->rstat = NoStatus; appendToRunQueue(cap,tso); @@ -2360,7 +2360,7 @@ scheduleWaitThread (StgTSO* tso, /*[out]*/HaskellObj* ret, Capability **pcap) cap = schedule(cap,task); - ASSERT(task->incall->stat != NoStatus); + ASSERT(task->incall->rstat != NoStatus); ASSERT_FULL_CAPABILITY_INVARIANTS(cap,task); debugTrace(DEBUG_sched, "bound thread (%lu) finished", (unsigned long)id); diff --git a/rts/Task.c b/rts/Task.c index be72c1b..82f7780 100644 --- a/rts/Task.c +++ b/rts/Task.c @@ -264,7 +264,7 @@ newInCall (Task *task) incall->task = task; incall->suspended_tso = NULL; incall->suspended_cap = NULL; - incall->stat = NoStatus; + incall->rstat = NoStatus; incall->ret = NULL; incall->next = NULL; incall->prev = NULL; diff --git a/rts/Task.h b/rts/Task.h index 58798bd..817a99a 100644 --- a/rts/Task.h +++ b/rts/Task.h @@ -94,7 +94,7 @@ typedef struct InCall_ { // without owning a Capability in the // first place. - SchedulerStatus stat; // return status + SchedulerStatus rstat; // return status StgClosure ** ret; // return value struct Task_ *task; From git at git.haskell.org Fri Dec 4 09:43:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 4 Dec 2015 09:43:34 +0000 (UTC) Subject: [commit: ghc] master: On AIX we need -D_BSD defined in (6ef351d) Message-ID: <20151204094334.C6ED23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6ef351df6172f0795e77323fa2ca45b3ae670502/ghc >--------------------------------------------------------------- commit 6ef351df6172f0795e77323fa2ca45b3ae670502 Author: Herbert Valerio Riedel Date: Fri Dec 4 10:40:42 2015 +0100 On AIX we need -D_BSD defined in As otherwise includes which breaks compilation of .hc files >--------------------------------------------------------------- 6ef351df6172f0795e77323fa2ca45b3ae670502 includes/Stg.h | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/includes/Stg.h b/includes/Stg.h index f09fc00..899e685 100644 --- a/includes/Stg.h +++ b/includes/Stg.h @@ -48,6 +48,11 @@ // on Linux # define _BSD_SOURCE +// On AIX we need _BSD defined, otherwise includes +# if defined(_AIX) +# define _BSD 1 +# endif + // '_BSD_SOURCE' is deprecated since glibc-2.20 // in favour of '_DEFAULT_SOURCE' # define _DEFAULT_SOURCE From git at git.haskell.org Fri Dec 4 10:08:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 4 Dec 2015 10:08:35 +0000 (UTC) Subject: [commit: ghc] master: PmExpr: Fix CPP unacceptable too clang's CPP (d40f5b7) Message-ID: <20151204100835.819B63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d40f5b78708273255b3d433ed6a225f674c7238e/ghc >--------------------------------------------------------------- commit d40f5b78708273255b3d433ed6a225f674c7238e Author: Ben Gamari Date: Fri Dec 4 05:05:06 2015 -0500 PmExpr: Fix CPP unacceptable too clang's CPP >--------------------------------------------------------------- d40f5b78708273255b3d433ed6a225f674c7238e compiler/deSugar/PmExpr.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/deSugar/PmExpr.hs b/compiler/deSugar/PmExpr.hs index f426bb4..78a51e6 100644 --- a/compiler/deSugar/PmExpr.hs +++ b/compiler/deSugar/PmExpr.hs @@ -357,7 +357,7 @@ pprPmExprCon con args list = list_elements args list_elements [x,y] - | PmExprCon c es <- y, nilDataCon == c = ASSERT (null es) [x,y] + | PmExprCon c es <- y, nilDataCon == c = ASSERT(null es) [x,y] | PmExprCon c es <- y, consDataCon == c = x : list_elements es | otherwise = [x,y] list_elements list = pprPanic "list_elements:" (ppr list) From git at git.haskell.org Fri Dec 4 11:48:52 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 4 Dec 2015 11:48:52 +0000 (UTC) Subject: [commit: ghc] master: Use builtin ISO 8859-1 decoder in mkTextEncoding (36a208f) Message-ID: <20151204114852.09E4E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/36a208f44df4b3c1480e4b873efca75f6adae3b4/ghc >--------------------------------------------------------------- commit 36a208f44df4b3c1480e4b873efca75f6adae3b4 Author: Herbert Valerio Riedel Date: Fri Dec 4 12:15:23 2015 +0100 Use builtin ISO 8859-1 decoder in mkTextEncoding We already do this for UTF8/16/32, so it seems obvious do the same for the closely related popular ISO 8859-1 encoding, and avoid iconv issues on some platforms (such as AIX which which bundles a broken `libiconv` by default) This fixes #11096 >--------------------------------------------------------------- 36a208f44df4b3c1480e4b873efca75f6adae3b4 libraries/base/GHC/IO/Encoding.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/libraries/base/GHC/IO/Encoding.hs b/libraries/base/GHC/IO/Encoding.hs index a690717..18b5432 100644 --- a/libraries/base/GHC/IO/Encoding.hs +++ b/libraries/base/GHC/IO/Encoding.hs @@ -245,6 +245,8 @@ mkTextEncoding' cfm enc = "UTF32" -> return $ UTF32.mkUTF32 cfm "UTF32LE" -> return $ UTF32.mkUTF32le cfm "UTF32BE" -> return $ UTF32.mkUTF32be cfm + -- ISO8859-1 we can handle ourselves as well + "ISO88591" -> return $ Latin1.mkLatin1 cfm #if defined(mingw32_HOST_OS) 'C':'P':n | [(cp,"")] <- reads n -> return $ CodePage.mkCodePageEncoding cfm cp _ -> unknownEncodingErr (enc ++ codingFailureModeSuffix cfm) From git at git.haskell.org Fri Dec 4 12:07:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 4 Dec 2015 12:07:26 +0000 (UTC) Subject: [commit: ghc] master: Check: More Clang/CPP wibbles (befc4e4) Message-ID: <20151204120726.0C2403A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/befc4e4c4c76fd89a092240935d9f508de2ee664/ghc >--------------------------------------------------------------- commit befc4e4c4c76fd89a092240935d9f508de2ee664 Author: Ben Gamari Date: Fri Dec 4 13:07:16 2015 +0100 Check: More Clang/CPP wibbles >--------------------------------------------------------------- befc4e4c4c76fd89a092240935d9f508de2ee664 compiler/deSugar/Check.hs | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs index 55dcfc2..dcf3b23 100644 --- a/compiler/deSugar/Check.hs +++ b/compiler/deSugar/Check.hs @@ -370,12 +370,12 @@ translateConPatVec univ_tys ex_tvs c (RecCon (HsRecFields fs _)) -- The data constructor was not defined using record syntax. For the -- pattern to be in record syntax it should be empty (e.g. Just {}). -- So just like the previous case. - | null orig_lbls = ASSERT (null matched_lbls) mkPatternVarsSM arg_tys + | null orig_lbls = ASSERT(null matched_lbls) mkPatternVarsSM arg_tys -- Some of the fields appear, in the original order (there may be holes). -- Generate a simple constructor pattern and make up fresh variables for -- the rest of the fields | matched_lbls `subsetOf` orig_lbls - = ASSERT (length orig_lbls == length arg_tys) + = ASSERT(length orig_lbls == length arg_tys) let translateOne (lbl, ty) = case lookup lbl matched_pats of Just p -> translatePat p Nothing -> mkPatternVarsSM [ty] @@ -616,7 +616,7 @@ process_guards us gs -- * Basic utilities patternType :: Pattern -> Type -patternType (PmGuard pv _) = ASSERT (patVecArity pv == 1) (patternType p) +patternType (PmGuard pv _) = ASSERT(patVecArity pv == 1) (patternType p) where Just p = find ((==1) . patternArity) pv patternType (NonGuard pat) = pmPatType pat @@ -826,8 +826,8 @@ splitConstraints (c : rest) = case c of TyConstraint cs -> (cs ++ ty_cs, tm_cs, bot_cs) TmConstraint e1 e2 -> (ty_cs, (e1,e2):tm_cs, bot_cs) - BtConstraint cs -> ASSERT (isNothing bot_cs) -- NB: Only one x ~ _|_ - (ty_cs, tm_cs, Just cs) + BtConstraint cs -> ASSERT(isNothing bot_cs) -- NB: Only one x ~ _|_ + (ty_cs, tm_cs, Just cs) where (ty_cs, tm_cs, bot_cs) = splitConstraints rest From git at git.haskell.org Fri Dec 4 12:57:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 4 Dec 2015 12:57:54 +0000 (UTC) Subject: [commit: ghc] master: Bump allocations for T783 (e9220da) Message-ID: <20151204125754.B3BE53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e9220daf7dbbd1ee084296a0d486a62aca7f1dcf/ghc >--------------------------------------------------------------- commit e9220daf7dbbd1ee084296a0d486a62aca7f1dcf Author: Ben Gamari Date: Fri Dec 4 05:30:39 2015 -0500 Bump allocations for T783 The new pattern match checker increased allocations by over 100%. Tracking in #11162. >--------------------------------------------------------------- e9220daf7dbbd1ee084296a0d486a62aca7f1dcf testsuite/tests/perf/compiler/all.T | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index bbcb631..27a0b7b 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -424,7 +424,7 @@ test('T783', # 2014-09-03: 223377364 (Windows) better specialisation, raft of core-to-core optimisations # 2014-12-22: 235002220 (Windows) not sure why - (wordsize(64), 526230456, 10)]), + (wordsize(64), 1134085384, 10)]), # prev: 349263216 (amd64/Linux) # 07/08/2012: 384479856 (amd64/Linux) # 29/08/2012: 436927840 (amd64/Linux) @@ -449,6 +449,8 @@ test('T783', # (simplifying the switch plan code path for simple checks, #10677) # 2015-08-28: 526230456 (amd64/Linux) # (D757: Emit Typeable instances at site of type definition) + # 2015-12-04: 1134085384 (amd64/Linux) + # (D1535: Major overhaul of pattern match checker, #11162) extra_hc_opts('-static') ], compile,['']) From git at git.haskell.org Fri Dec 4 12:57:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 4 Dec 2015 12:57:57 +0000 (UTC) Subject: [commit: ghc] master: T5642 is broken (dc33e4c) Message-ID: <20151204125757.57FD53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/dc33e4c65dc1587c265c698473f35f9843673cba/ghc >--------------------------------------------------------------- commit dc33e4c65dc1587c265c698473f35f9843673cba Author: Ben Gamari Date: Fri Dec 4 07:56:33 2015 -0500 T5642 is broken This appears to be due to the new exhaustiveness checker. See #11163. >--------------------------------------------------------------- dc33e4c65dc1587c265c698473f35f9843673cba testsuite/tests/perf/compiler/all.T | 1 + 1 file changed, 1 insertion(+) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index 27a0b7b..ede30b6 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -513,6 +513,7 @@ test('T5321FD', test('T5642', [ only_ways(['normal']), + expect_broken(11163), compiler_stats_num_field('bytes allocated', [(wordsize(32), 641085256, 10), # sample from x86/Linux From git at git.haskell.org Fri Dec 4 13:30:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 4 Dec 2015 13:30:26 +0000 (UTC) Subject: [commit: ghc] master: T5642: Skip it entirely (96e67c0) Message-ID: <20151204133026.349B53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/96e67c014e9b8022599bbe19f67d1635f4955ce0/ghc >--------------------------------------------------------------- commit 96e67c014e9b8022599bbe19f67d1635f4955ce0 Author: Ben Gamari Date: Fri Dec 4 14:30:09 2015 +0100 T5642: Skip it entirely It uses so much memory that it would be unsafe to even allow it to run as it may jeopardize the stability of the build-bots. >--------------------------------------------------------------- 96e67c014e9b8022599bbe19f67d1635f4955ce0 testsuite/tests/perf/compiler/all.T | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index ede30b6..3303a35 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -513,7 +513,7 @@ test('T5321FD', test('T5642', [ only_ways(['normal']), - expect_broken(11163), + skip(), # See Trac #11163 compiler_stats_num_field('bytes allocated', [(wordsize(32), 641085256, 10), # sample from x86/Linux From git at git.haskell.org Fri Dec 4 14:06:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 4 Dec 2015 14:06:15 +0000 (UTC) Subject: [commit: ghc] master: Make callToPats deterministic in SpecConstr (5b2b7e3) Message-ID: <20151204140615.CD4023A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5b2b7e338c822c34f86e8bd3ff442a979711d1fe/ghc >--------------------------------------------------------------- commit 5b2b7e338c822c34f86e8bd3ff442a979711d1fe Author: Bartosz Nitka Date: Wed Dec 2 06:20:55 2015 -0800 Make callToPats deterministic in SpecConstr This fixes a non-determinism bug where where depending on the order of uniques allocated, the specialized workers would have different order of arguments. Compare: ``` $s$wgo_s1CN :: Int# -> Int -> Int# [LclId, Arity=2, Str=DmdType ] $s$wgo_s1CN = \ (sc_s1CI :: Int#) (sc_s1CJ :: Int) -> case tagToEnum# @ Bool (<=# sc_s1CI 0#) of _ [Occ=Dead] { False -> $wgo_s1BU (Just @ Int (I# (-# sc_s1CI 1#))) (Just @ Int sc_s1CJ); True -> 0# } ``` vs ``` $s$wgo_s18mTj :: Int -> Int# -> Int# [LclId, Arity=2, Str=DmdType ] $s$wgo_s18mTj = \ (sc_s18mTn :: Int) (sc_s18mTo :: Int#) -> case tagToEnum# @ Bool (<=# sc_s18mTo 0#) of _ [Occ=Dead] { False -> $wgo_s18mUc (Just @ Int (I# (-# sc_s18mTo 1#))) (Just @ Int sc_s18mTn); True -> 0# } ``` Test Plan: I've added a new testcase ./validate Reviewers: simonmar, simonpj, austin, goldfire, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1508 GHC Trac Issues: #4012 >--------------------------------------------------------------- 5b2b7e338c822c34f86e8bd3ff442a979711d1fe compiler/specialise/SpecConstr.hs | 10 ++++-- .../determinism/simplCore/should_compile/Makefile | 13 +++++++ .../determinism/simplCore/should_compile/all.T | 4 +++ .../simplCore/should_compile/determ006.stdout | 2 ++ .../simplCore/should_compile/spec-inline-determ.hs | 40 ++++++++++++++++++++++ .../tests/simplCore/should_compile/T4908.stderr | 18 +++++----- .../tests/simplCore/should_compile/T7865.stdout | 2 +- .../simplCore/should_compile/spec-inline.stderr | 26 +++++++------- 8 files changed, 90 insertions(+), 25 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 5b2b7e338c822c34f86e8bd3ff442a979711d1fe From git at git.haskell.org Fri Dec 4 14:21:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 4 Dec 2015 14:21:09 +0000 (UTC) Subject: [commit: ghc] master: Case-of-empty-alts is trivial (Trac #11155) (1c9fd3f) Message-ID: <20151204142109.49E293A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1c9fd3f1c5522372fcaf250c805b959e8090a62c/ghc >--------------------------------------------------------------- commit 1c9fd3f1c5522372fcaf250c805b959e8090a62c Author: Simon Peyton Jones Date: Thu Dec 3 12:57:54 2015 +0000 Case-of-empty-alts is trivial (Trac #11155) As you'll see from Trac #11155, the code generator was confused by a binding let x = y in .... Why did that happen? Because of a (case y of {}) expression on the RHS. The right thing is just to expand what a "trivial" expression is. See Note [Empty case is trivial] in CoreUtils. >--------------------------------------------------------------- 1c9fd3f1c5522372fcaf250c805b959e8090a62c compiler/coreSyn/CorePrep.hs | 20 +++++++++++--------- compiler/coreSyn/CoreUtils.hs | 20 +++++++++++++++++++- testsuite/tests/simplCore/should_compile/Makefile | 6 ++++++ testsuite/tests/simplCore/should_compile/T11155.hs | 11 +++++++++++ testsuite/tests/simplCore/should_compile/all.T | 5 ++++- 5 files changed, 51 insertions(+), 11 deletions(-) diff --git a/compiler/coreSyn/CorePrep.hs b/compiler/coreSyn/CorePrep.hs index fdf25d6..999ca54 100644 --- a/compiler/coreSyn/CorePrep.hs +++ b/compiler/coreSyn/CorePrep.hs @@ -847,15 +847,17 @@ of the scope of a `seq`, or dropped the `seq` altogether. cpe_ExprIsTrivial :: CoreExpr -> Bool -- Version that doesn't consider an scc annotation to be trivial. -cpe_ExprIsTrivial (Var _) = True -cpe_ExprIsTrivial (Type _) = True -cpe_ExprIsTrivial (Coercion _) = True -cpe_ExprIsTrivial (Lit _) = True -cpe_ExprIsTrivial (App e arg) = isTypeArg arg && cpe_ExprIsTrivial e -cpe_ExprIsTrivial (Tick t e) = not (tickishIsCode t) && cpe_ExprIsTrivial e -cpe_ExprIsTrivial (Cast e _) = cpe_ExprIsTrivial e -cpe_ExprIsTrivial (Lam b body) | isTyVar b = cpe_ExprIsTrivial body -cpe_ExprIsTrivial _ = False +cpe_ExprIsTrivial (Var _) = True +cpe_ExprIsTrivial (Type _) = True +cpe_ExprIsTrivial (Coercion _) = True +cpe_ExprIsTrivial (Lit _) = True +cpe_ExprIsTrivial (App e arg) = not (isRuntimeArg arg) && cpe_ExprIsTrivial e +cpe_ExprIsTrivial (Lam b e) = not (isRuntimeVar b) && cpe_ExprIsTrivial e +cpe_ExprIsTrivial (Tick t e) = not (tickishIsCode t) && cpe_ExprIsTrivial e +cpe_ExprIsTrivial (Cast e _) = cpe_ExprIsTrivial e +cpe_ExprIsTrivial (Case e _ _ []) = cpe_ExprIsTrivial e + -- See Note [Empty case is trivial] in CoreUtils +cpe_ExprIsTrivial _ = False {- -- ----------------------------------------------------------------------------- diff --git a/compiler/coreSyn/CoreUtils.hs b/compiler/coreSyn/CoreUtils.hs index 889e239..5c1c986 100644 --- a/compiler/coreSyn/CoreUtils.hs +++ b/compiler/coreSyn/CoreUtils.hs @@ -733,11 +733,28 @@ saturating them. Note [Tick trivial] ~~~~~~~~~~~~~~~~~~~ - Ticks are only trivial if they are pure annotations. If we treat "tick x" as trivial, it will be inlined inside lambdas and the entry count will be skewed, for example. Furthermore "scc x" will turn into just "x" in mkTick. + +Note [Empty case is trivial] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +The expression (case (x::Int) Bool of {}) is just a type-changing +case used when we are sure that 'x' will not return. See +Note [Empty case alternatives] in CoreSyn. + +If the scrutinee is trivial, then so is the whole expression; and the +CoreToSTG pass in fact drops the case expression leaving only the +scrutinee. + +Having more trivial expressions is good. Moreover, if we don't treat +it as trivial we may land up with let-bindings like + let v = case x of {} in ... +and after CoreToSTG that gives + let v = x in ... +and that confuses the code generator (Trac #11155). So best to kill +it off at source. -} exprIsTrivial :: CoreExpr -> Bool @@ -750,6 +767,7 @@ exprIsTrivial (Tick t e) = not (tickishIsCode t) && exprIsTrivial e -- See Note [Tick trivial] exprIsTrivial (Cast e _) = exprIsTrivial e exprIsTrivial (Lam b body) = not (isRuntimeVar b) && exprIsTrivial body +exprIsTrivial (Case e _ _ []) = exprIsTrivial e -- See Note [Empty case is trivial] exprIsTrivial _ = False {- diff --git a/testsuite/tests/simplCore/should_compile/Makefile b/testsuite/tests/simplCore/should_compile/Makefile index 8c6ec45..eb6d742 100644 --- a/testsuite/tests/simplCore/should_compile/Makefile +++ b/testsuite/tests/simplCore/should_compile/Makefile @@ -6,6 +6,12 @@ T8832: $(RM) -f T8832.o T8832.hi '$(TEST_HC)' $(TEST_HC_OPTS) $(T8832_WORDSIZE_OPTS) -O -c -ddump-simpl T8832.hs | grep '^[a-zA-Z0-9]\+ =' +T11155: + $(RM) -f T11155.o T11155.hi + '$(TEST_HC)' $(TEST_HC_OPTS) -c T11155.hs + -nm T11155.o | grep 'stg_ap_0_upd' + # Expecting no output from the grep + T8274: $(RM) -f T8274.o T8274.hi '$(TEST_HC)' $(TEST_HC_OPTS) -O -c -ddump-simpl T8274.hs | grep '#' diff --git a/testsuite/tests/simplCore/should_compile/T11155.hs b/testsuite/tests/simplCore/should_compile/T11155.hs new file mode 100644 index 0000000..b57bbe9 --- /dev/null +++ b/testsuite/tests/simplCore/should_compile/T11155.hs @@ -0,0 +1,11 @@ +{-# OPTIONS_GHC -O -fno-full-laziness #-} +module T11155 where + +foo :: Bool +{-# NOINLINE foo #-} +foo = error "rk" + +bar x = let t :: Char + t = case foo of { True -> 'v'; False -> 'y' } + in [t] + diff --git a/testsuite/tests/simplCore/should_compile/all.T b/testsuite/tests/simplCore/should_compile/all.T index c99b8f2..f9388c9 100644 --- a/testsuite/tests/simplCore/should_compile/all.T +++ b/testsuite/tests/simplCore/should_compile/all.T @@ -224,4 +224,7 @@ test('T10083', run_command, ['$MAKE -s --no-print-directory T10083']) test('T10689', normal, compile, ['']) -test('T10689a', normal, compile, ['']) +test('T11155', + normal, + run_command, + ['$MAKE -s --no-print-directory T11155']) From git at git.haskell.org Fri Dec 4 14:21:12 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 4 Dec 2015 14:21:12 +0000 (UTC) Subject: [commit: ghc] master: Add derived constraints for wildcard signatures (28035c0) Message-ID: <20151204142112.C55443A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/28035c0900f8d535e0b03d4c2aa0c79ba728436d/ghc >--------------------------------------------------------------- commit 28035c0900f8d535e0b03d4c2aa0c79ba728436d Author: Simon Peyton Jones Date: Thu Dec 3 13:03:07 2015 +0000 Add derived constraints for wildcard signatures This fixes Trac #11016 See Note [Add deriveds for signature contexts] in TcSimplify] >--------------------------------------------------------------- 28035c0900f8d535e0b03d4c2aa0c79ba728436d compiler/typecheck/TcSimplify.hs | 90 +++++++++++++--------- .../tests/partial-sigs/should_compile/T11016.hs | 9 +++ .../partial-sigs/should_compile/T11016.stderr | 11 +++ testsuite/tests/partial-sigs/should_compile/all.T | 1 + 4 files changed, 76 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 28035c0900f8d535e0b03d4c2aa0c79ba728436d From git at git.haskell.org Fri Dec 4 14:21:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 4 Dec 2015 14:21:15 +0000 (UTC) Subject: [commit: ghc] master: Wibbles only (1cb3c8c) Message-ID: <20151204142115.706F03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1cb3c8c2e8bc7d5dd8123f6473ae9b1a6060408b/ghc >--------------------------------------------------------------- commit 1cb3c8c2e8bc7d5dd8123f6473ae9b1a6060408b Author: Simon Peyton Jones Date: Fri Dec 4 11:58:05 2015 +0000 Wibbles only >--------------------------------------------------------------- 1cb3c8c2e8bc7d5dd8123f6473ae9b1a6060408b compiler/typecheck/TcBinds.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/compiler/typecheck/TcBinds.hs b/compiler/typecheck/TcBinds.hs index d171b0c..bf6c833 100644 --- a/compiler/typecheck/TcBinds.hs +++ b/compiler/typecheck/TcBinds.hs @@ -757,11 +757,11 @@ mkInferredPolyId qtvs inferred_theta poly_name mb_sig mono_ty inferred_theta (tyVarsOfType mono_ty') mb_sig ; let qtvs' = filter (`elemVarSet` my_tvs) qtvs -- Maintain original order - ; let inferred_poly_ty = mkSigmaTy qtvs' theta' mono_ty' - msg = mk_inf_msg poly_name inferred_poly_ty + inferred_poly_ty = mkSigmaTy qtvs' theta' mono_ty' - ; traceTc "mkInferredPolyId" (vcat [ppr poly_name, ppr qtvs, ppr my_tvs, ppr theta', ppr inferred_poly_ty]) - ; addErrCtxtM msg $ + ; traceTc "mkInferredPolyId" (vcat [ppr poly_name, ppr qtvs, ppr my_tvs, ppr theta' + , ppr inferred_poly_ty]) + ; addErrCtxtM (mk_inf_msg poly_name inferred_poly_ty) $ checkValidType (InfSigCtxt poly_name) inferred_poly_ty ; return (mkLocalId poly_name inferred_poly_ty) } From git at git.haskell.org Fri Dec 4 14:21:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 4 Dec 2015 14:21:18 +0000 (UTC) Subject: [commit: ghc] master: Make -dppr-debug show contents of (TypeError ...) (822141b) Message-ID: <20151204142118.10AB33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/822141b95174f068872fd4e491da764139ce626f/ghc >--------------------------------------------------------------- commit 822141b95174f068872fd4e491da764139ce626f Author: Simon Peyton Jones Date: Fri Dec 4 11:59:08 2015 +0000 Make -dppr-debug show contents of (TypeError ...) Just for debugging >--------------------------------------------------------------- 822141b95174f068872fd4e491da764139ce626f compiler/types/TypeRep.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/compiler/types/TypeRep.hs b/compiler/types/TypeRep.hs index 384f1ef..f13ca8a 100644 --- a/compiler/types/TypeRep.hs +++ b/compiler/types/TypeRep.hs @@ -790,7 +790,9 @@ pprTyTcApp p tc tys if gopt Opt_PrintExplicitKinds dflags then pprTcApp p ppr_type tc tys else pprTyList p ty1 ty2 - | tc `hasKey` errorMessageTypeErrorFamKey = text "(TypeError ...)" + | not opt_PprStyle_Debug + , tc `hasKey` errorMessageTypeErrorFamKey + = text "(TypeError ...)" -- Suppress detail unles you _really_ want to see it | otherwise = pprTcApp p ppr_type tc tys From git at git.haskell.org Fri Dec 4 14:21:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 4 Dec 2015 14:21:21 +0000 (UTC) Subject: [commit: ghc] master: Fix egregious error in eta-reduction of data families (1160dc5) Message-ID: <20151204142121.55AED3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1160dc516f8b27249d819665883409ee270a743f/ghc >--------------------------------------------------------------- commit 1160dc516f8b27249d819665883409ee270a743f Author: Simon Peyton Jones Date: Fri Dec 4 12:08:37 2015 +0000 Fix egregious error in eta-reduction of data families This terrible and long-standing bug was shown up by Trac #11148. We are trying to eta-reduce a data family instance, so that we can then derive Functor or Generic. But we were assuming, for absolutely not reason whatsoever, that the type variables were lined up in a convenient order. The fact that it ever worked was a fluke. This patch fixes it properly. Main change is in eta_reduce in TcInstDcls.tcDataFamInstDecl >--------------------------------------------------------------- 1160dc516f8b27249d819665883409ee270a743f compiler/typecheck/TcInstDcls.hs | 92 +++++++++-------------- compiler/types/FamInstEnv.hs | 60 ++++++++++++--- testsuite/tests/deriving/should_compile/Makefile | 10 ++- testsuite/tests/deriving/should_compile/T11148.hs | 11 +++ testsuite/tests/deriving/should_compile/all.T | 2 + 5 files changed, 109 insertions(+), 66 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1160dc516f8b27249d819665883409ee270a743f From git at git.haskell.org Fri Dec 4 14:21:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 4 Dec 2015 14:21:23 +0000 (UTC) Subject: [commit: ghc] master: Minor refactoring of user type errors (31b482b) Message-ID: <20151204142123.EFDBC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/31b482bfa68ec8524c4039a33ba55f0aaf02dc0b/ghc >--------------------------------------------------------------- commit 31b482bfa68ec8524c4039a33ba55f0aaf02dc0b Author: Simon Peyton Jones Date: Fri Dec 4 12:11:43 2015 +0000 Minor refactoring of user type errors * Remove unused Kind result of getUserTypeErrorMsg * Rename isUserErrorTy --> userTypeError_maybe >--------------------------------------------------------------- 31b482bfa68ec8524c4039a33ba55f0aaf02dc0b compiler/typecheck/TcErrors.hs | 4 ++-- compiler/typecheck/TcRnTypes.hs | 6 +++--- compiler/types/Type.hs | 11 ++++++----- 3 files changed, 11 insertions(+), 10 deletions(-) diff --git a/compiler/typecheck/TcErrors.hs b/compiler/typecheck/TcErrors.hs index 156b1ff..ad389b2 100644 --- a/compiler/typecheck/TcErrors.hs +++ b/compiler/typecheck/TcErrors.hs @@ -499,8 +499,8 @@ mkUserTypeError ctxt ct = mkErrorMsgFromCt ctxt ct $ important $ pprUserTypeErrorTy $ case getUserTypeErrorMsg ct of - Just (_,msg) -> msg - Nothing -> pprPanic "mkUserTypeError" (ppr ct) + Just msg -> msg + Nothing -> pprPanic "mkUserTypeError" (ppr ct) mkGroupReporter :: (ReportErrCtxt -> [Ct] -> TcM ErrMsg) diff --git a/compiler/typecheck/TcRnTypes.hs b/compiler/typecheck/TcRnTypes.hs index f66399d..0e8f682 100644 --- a/compiler/typecheck/TcRnTypes.hs +++ b/compiler/typecheck/TcRnTypes.hs @@ -1661,14 +1661,14 @@ isTypeHoleCt _ = False -- 1. TypeError msg -- 2. TypeError msg ~ Something (and the other way around) -- 3. C (TypeError msg) (for any parameter of class constraint) -getUserTypeErrorMsg :: Ct -> Maybe (Kind, Type) +getUserTypeErrorMsg :: Ct -> Maybe Type getUserTypeErrorMsg ct | Just (_,t1,t2) <- getEqPredTys_maybe ctT = oneOf [t1,t2] | Just (_,ts) <- getClassPredTys_maybe ctT = oneOf ts - | otherwise = isUserErrorTy ctT + | otherwise = userTypeError_maybe ctT where ctT = ctPred ct - oneOf xs = msum (map isUserErrorTy xs) + oneOf xs = msum (map userTypeError_maybe xs) isUserTypeErrorCt :: Ct -> Bool isUserTypeErrorCt ct = case getUserTypeErrorMsg ct of diff --git a/compiler/types/Type.hs b/compiler/types/Type.hs index 13ac503..f7493f3 100644 --- a/compiler/types/Type.hs +++ b/compiler/types/Type.hs @@ -39,7 +39,7 @@ module Type ( mkNumLitTy, isNumLitTy, mkStrLitTy, isStrLitTy, - isUserErrorTy, pprUserTypeErrorTy, + userTypeError_maybe, pprUserTypeErrorTy, coAxNthLHS, @@ -460,10 +460,11 @@ isStrLitTy _ = Nothing -- | Is this type a custom user error? -- If so, give us the kind and the error message. -isUserErrorTy :: Type -> Maybe (Kind,Type) -isUserErrorTy t = do (tc,[k,msg]) <- splitTyConApp_maybe t - guard (tyConName tc == errorMessageTypeErrorFamName) - return (k,msg) +userTypeError_maybe :: Type -> Maybe Type +userTypeError_maybe t + = do { (tc, [_kind, msg]) <- splitTyConApp_maybe t + ; guard (tyConName tc == errorMessageTypeErrorFamName) + ; return msg } -- | Render a type corresponding to a user type error into a SDoc. pprUserTypeErrorTy :: Type -> SDoc From git at git.haskell.org Fri Dec 4 14:21:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 4 Dec 2015 14:21:26 +0000 (UTC) Subject: [commit: ghc] master: Tidy user type errors in checkValidType (67565a7) Message-ID: <20151204142126.AC0543A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/67565a72f5bcd2edcb5775dc3879708f9d302fa8/ghc >--------------------------------------------------------------- commit 67565a72f5bcd2edcb5775dc3879708f9d302fa8 Author: Simon Peyton Jones Date: Fri Dec 4 12:23:33 2015 +0000 Tidy user type errors in checkValidType Trac #11144 showed that we need to tidy the type in the error message generated in TcValidity.checkUserTypeError. This is still unsatisfactory. checkValidType was originally supposed to be called only on types gotten directly from user-written HsTypes. So its error messages do no tidying. But TcBinds calls it checkValidType on an /inferred/ type, which may need tidying. Still this at least fixes the bad error message in CustomTypeErrors02, which was the original ticket. Some other small refactorings: * Remove unused Kind result of getUserTypeErrorMsg * Rename isUserErrorTy --> userTypeError_maybe >--------------------------------------------------------------- 67565a72f5bcd2edcb5775dc3879708f9d302fa8 compiler/typecheck/TcBinds.hs | 16 ++++++---------- compiler/typecheck/TcValidity.hs | 19 ++++++++++++++++--- .../typecheck/should_fail/CustomTypeErrors02.stderr | 2 +- 3 files changed, 23 insertions(+), 14 deletions(-) diff --git a/compiler/typecheck/TcBinds.hs b/compiler/typecheck/TcBinds.hs index bf6c833..6575082 100644 --- a/compiler/typecheck/TcBinds.hs +++ b/compiler/typecheck/TcBinds.hs @@ -707,7 +707,7 @@ mkExport prag_fn qtvs theta mono_info@(poly_name, mb_sig, mono_id) _other -> checkNoErrs $ mkInferredPolyId qtvs theta poly_name mb_sig mono_ty - -- The checkNoErrors ensures that if the type is ambiguous + -- The checkNoErrs ensures that if the type is ambiguous -- we don't carry on to the impedence matching, and generate -- a duplicate ambiguity error. There is a similar -- checkNoErrs for complete type signatures too. @@ -718,9 +718,8 @@ mkExport prag_fn qtvs theta mono_info@(poly_name, mb_sig, mono_id) -- tcPrags requires a zonked poly_id -- See Note [Impedence matching] - -- NB: we have already done checkValidType on the type - -- for a complete sig, when we checked the sig; - -- otherwise in mkInferredPolyIe + -- NB: we have already done checkValidType, including an ambiguity check, + -- on the type; either when we checked the sig or in mkInferredPolyId ; let sel_poly_ty = mkSigmaTy qtvs theta mono_ty poly_ty = idType poly_id ; wrap <- if sel_poly_ty `eqType` poly_ty @@ -763,6 +762,7 @@ mkInferredPolyId qtvs inferred_theta poly_name mb_sig mono_ty , ppr inferred_poly_ty]) ; addErrCtxtM (mk_inf_msg poly_name inferred_poly_ty) $ checkValidType (InfSigCtxt poly_name) inferred_poly_ty + -- See Note [Validity of inferred types] ; return (mkLocalId poly_name inferred_poly_ty) } @@ -884,16 +884,12 @@ simply adds the inferred type to the program source, it'll compile fine. See #8883. Examples that might fail: + - the type might be ambiguous + - an inferred theta that requires type equalities e.g. (F a ~ G b) or multi-parameter type classes - an inferred type that includes unboxed tuples -However we don't do the ambiguity check (checkValidType omits it for -InfSigCtxt) because the impedance-matching stage, which follows -immediately, will do it and we don't want two error messages. -Moreover, because of the impedance matching stage, the ambiguity-check -suggestion of -XAllowAmbiguiousTypes will not work. - Note [Impedence matching] ~~~~~~~~~~~~~~~~~~~~~~~~~ diff --git a/compiler/typecheck/TcValidity.hs b/compiler/typecheck/TcValidity.hs index 04bbd46..8422ba4 100644 --- a/compiler/typecheck/TcValidity.hs +++ b/compiler/typecheck/TcValidity.hs @@ -231,19 +231,32 @@ wantAmbiguityCheck ctxt -- E.g. type family T a :: * -- T :: forall k. k -> * -- Then :k T should work in GHCi, not complain that -- (T k) is ambiguous! --- InfSigCtxt {} -> False -- See Note [Validity of inferred types] in TcBinds _ -> True checkUserTypeError :: Type -> TcM () +-- Check to see if the type signature mentions "TypeError blah" +-- anywhere in it, and fail if so. +-- +-- Very unsatisfactorily (Trac #11144) we need to tidy the type +-- because it may have come from an /inferred/ signature, not a +-- user-supplied one. This is really only a half-baked fix; +-- the other errors in checkValidType don't do tidying, and so +-- may give bad error messages when given an inferred type. checkUserTypeError = check where check ty - | Just (_,msg) <- isUserErrorTy ty = failWithTc (pprUserTypeErrorTy msg) + | Just msg <- userTypeError_maybe ty = fail_with msg | Just (_,ts) <- splitTyConApp_maybe ty = mapM_ check ts | Just (t1,t2) <- splitAppTy_maybe ty = check t1 >> check t2 + | Just (_,t1) <- splitForAllTy_maybe ty = check t1 | otherwise = return () + fail_with msg = do { env0 <- tcInitTidyEnv + ; let (env1, tidy_msg) = tidyOpenType env0 msg + ; failWithTcM (env1, pprUserTypeErrorTy tidy_msg) } + + {- ************************************************************************ * * @@ -280,7 +293,7 @@ This might not necessarily show up in kind checking. -} checkValidType :: UserTypeCtxt -> Type -> TcM () --- Checks that the type is valid for the given context +-- Checks that a user-written type is valid for the given context -- Assumes arguemt is fully zonked -- Not used for instance decls; checkValidInstance instead checkValidType ctxt ty diff --git a/testsuite/tests/typecheck/should_fail/CustomTypeErrors02.stderr b/testsuite/tests/typecheck/should_fail/CustomTypeErrors02.stderr index 464c62d..0b8be13 100644 --- a/testsuite/tests/typecheck/should_fail/CustomTypeErrors02.stderr +++ b/testsuite/tests/typecheck/should_fail/CustomTypeErrors02.stderr @@ -1,6 +1,6 @@ CustomTypeErrors02.hs:17:1: error: - ? The type 'a_aEN -> a_aEN' cannot be represented as an integer. + ? The type 'a0 -> a0' cannot be represented as an integer. ? When checking the inferred type err :: (TypeError ...) From git at git.haskell.org Fri Dec 4 14:21:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 4 Dec 2015 14:21:29 +0000 (UTC) Subject: [commit: ghc] master: Comments only (43a5970) Message-ID: <20151204142129.54C2E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/43a5970a4f721138145f55e90bd910f3723abc3c/ghc >--------------------------------------------------------------- commit 43a5970a4f721138145f55e90bd910f3723abc3c Author: Simon Peyton Jones Date: Fri Dec 4 12:24:49 2015 +0000 Comments only >--------------------------------------------------------------- 43a5970a4f721138145f55e90bd910f3723abc3c compiler/typecheck/TcSMonad.hs | 13 +++++-------- 1 file changed, 5 insertions(+), 8 deletions(-) diff --git a/compiler/typecheck/TcSMonad.hs b/compiler/typecheck/TcSMonad.hs index 8ddb488..0c5564b 100644 --- a/compiler/typecheck/TcSMonad.hs +++ b/compiler/typecheck/TcSMonad.hs @@ -662,8 +662,8 @@ Definition [Can-rewrite relation] A "can-rewrite" relation between flavours, written f1 >= f2, is a binary relation with the following properties - R1. >= is transitive - R2. If f1 >= f, and f2 >= f, + (R1) >= is transitive + (R2) If f1 >= f, and f2 >= f, then either f1 >= f2 or f2 >= f1 Lemma. If f1 >= f then f1 >= f1 @@ -690,7 +690,7 @@ See Note [Flavours with roles]. Theorem: S(f,a) is well defined as a function. Proof: Suppose (a -f1-> t1) and (a -f2-> t2) are both in S, and f1 >= f and f2 >= f - Then by (R2) f1 >= f2 or f2 >= f1, which contradicts (WF) + Then by (R2) f1 >= f2 or f2 >= f1, which contradicts (WF1) Notation: repeated application. S^0(f,t) = t @@ -702,9 +702,6 @@ A generalised substitution S is "inert" iff (IG1) there is an n such that for every f,t, S^n(f,t) = S^(n+1)(f,t) - (IG2) if (b -f-> t) in S, and f >= f, then S(f,t) = t - that is, each individual binding is "self-stable" - By (IG1) we define S*(f,t) to be the result of exahaustively applying S(f,_) to t. @@ -719,8 +716,8 @@ guarantee that this recursive use will terminate. Note [Extending the inert equalities] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -This is the main theorem! - +Theorem [Stability under extension] + This is the main theorem! Suppose we have a "work item" a -fw-> t and an inert generalised substitution S, From git at git.haskell.org Fri Dec 4 15:12:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 4 Dec 2015 15:12:39 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Rename pmcheck/T7669 to pmcheck/T7669a (caa6851) Message-ID: <20151204151239.A698F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/caa68516449c205ba4affe1d31b9bffbded09b57/ghc >--------------------------------------------------------------- commit caa68516449c205ba4affe1d31b9bffbded09b57 Author: Ben Gamari Date: Fri Dec 4 09:31:53 2015 -0500 testsuite: Rename pmcheck/T7669 to pmcheck/T7669a This was a duplicate. >--------------------------------------------------------------- caa68516449c205ba4affe1d31b9bffbded09b57 testsuite/tests/pmcheck/should_compile/T7669.stderr | 0 testsuite/tests/pmcheck/should_compile/{T7669.hs => T7669a.hs} | 0 .../tests/pmcheck/should_compile/T7669a.stderr | 0 testsuite/tests/pmcheck/should_compile/all.T | 2 +- 4 files changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/pmcheck/should_compile/T7669.stderr b/testsuite/tests/pmcheck/should_compile/T7669.stderr deleted file mode 100644 index e69de29..0000000 diff --git a/testsuite/tests/pmcheck/should_compile/T7669.hs b/testsuite/tests/pmcheck/should_compile/T7669a.hs similarity index 100% rename from testsuite/tests/pmcheck/should_compile/T7669.hs rename to testsuite/tests/pmcheck/should_compile/T7669a.hs diff --git a/libraries/base/tests/IO/misc001.stdout b/testsuite/tests/pmcheck/should_compile/T7669a.stderr similarity index 100% copy from libraries/base/tests/IO/misc001.stdout copy to testsuite/tests/pmcheck/should_compile/T7669a.stderr diff --git a/testsuite/tests/pmcheck/should_compile/all.T b/testsuite/tests/pmcheck/should_compile/all.T index 3aac879..8ff797a 100644 --- a/testsuite/tests/pmcheck/should_compile/all.T +++ b/testsuite/tests/pmcheck/should_compile/all.T @@ -18,7 +18,7 @@ test('T3927b',only_compiler_types(['ghc']), compile, ['-fwarn-incomplete-pattern test('T3927', only_compiler_types(['ghc']), compile, ['-fwarn-incomplete-patterns -fwarn-overlapping-patterns']) test('T4139', only_compiler_types(['ghc']), compile, ['-fwarn-incomplete-patterns -fwarn-overlapping-patterns']) test('T6124', only_compiler_types(['ghc']), compile, ['-fwarn-incomplete-patterns -fwarn-overlapping-patterns']) -test('T7669', only_compiler_types(['ghc']), compile, ['-fwarn-incomplete-patterns -fwarn-overlapping-patterns']) +test('T7669a', only_compiler_types(['ghc']), compile, ['-fwarn-incomplete-patterns -fwarn-overlapping-patterns']) test('T8970', only_compiler_types(['ghc']), compile, ['-fwarn-incomplete-patterns -fwarn-overlapping-patterns']) test('T9951b',only_compiler_types(['ghc']), compile, ['-fwarn-incomplete-patterns -fwarn-overlapping-patterns']) test('T9951', only_compiler_types(['ghc']), compile, ['-fwarn-incomplete-patterns -fwarn-overlapping-patterns']) From git at git.haskell.org Fri Dec 4 15:12:42 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 4 Dec 2015 15:12:42 +0000 (UTC) Subject: [commit: ghc] master: T5642: Fix skip usage (16aae60) Message-ID: <20151204151242.45F9F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/16aae6083c44856a03b25df0a6d9cc8d647963dc/ghc >--------------------------------------------------------------- commit 16aae6083c44856a03b25df0a6d9cc8d647963dc Author: Ben Gamari Date: Fri Dec 4 09:29:59 2015 -0500 T5642: Fix skip usage >--------------------------------------------------------------- 16aae6083c44856a03b25df0a6d9cc8d647963dc testsuite/tests/perf/compiler/all.T | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index 3303a35..57b8810 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -513,7 +513,7 @@ test('T5321FD', test('T5642', [ only_ways(['normal']), - skip(), # See Trac #11163 + skip, # See Trac #11163 compiler_stats_num_field('bytes allocated', [(wordsize(32), 641085256, 10), # sample from x86/Linux From git at git.haskell.org Fri Dec 4 15:12:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 4 Dec 2015 15:12:44 +0000 (UTC) Subject: [commit: ghc] master: Update peak_megabytes_allocated for T9675 (d4bf863) Message-ID: <20151204151244.DDE7E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d4bf86322a50d5fee550040d15e376fe53ff629b/ghc >--------------------------------------------------------------- commit d4bf86322a50d5fee550040d15e376fe53ff629b Author: Ben Gamari Date: Fri Dec 4 09:55:58 2015 -0500 Update peak_megabytes_allocated for T9675 Interestingly enough this decreased with the new pattern checker. I'm not entirely sure why at the moment as the test is merely a large record with a bunch of selectors. I wouldn't have thought this would tax the pattern checker particularly much but oh well. >--------------------------------------------------------------- d4bf86322a50d5fee550040d15e376fe53ff629b testsuite/tests/perf/compiler/all.T | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index 57b8810..1ebc134 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -617,13 +617,14 @@ test('T9675', # 2015-07-11 15341228 (x86/Linux, 64-bit machine) use +RTS -G1 ]), compiler_stats_num_field('peak_megabytes_allocated', # Note [residency] - [(wordsize(64), 105, 15), + [(wordsize(64), 88, 15), # 2014-10-13 66 # 2014-10-13 58 seq the DmdEnv in seqDmdType as well # 2014-10-13 49 different machines giving different results... # 2014-10-13 53 use the mean # 2015-06-15 44 reduced for some reason # 2015-06-21 105 switch to `+RTS -G1` + # 2015-12-04 88 new pattern checker (D1535) (wordsize(32), 56, 15) # 2015-07-11 56 (x86/Linux, 64-bit machine) use +RTS -G1 ]), From git at git.haskell.org Fri Dec 4 16:31:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 4 Dec 2015 16:31:27 +0000 (UTC) Subject: [commit: ghc] master: Add linter to check for binaries accidentally added to repository (020375d) Message-ID: <20151204163127.280EF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/020375d1e723339a95b86d0d3b8a8214b1cc144a/ghc >--------------------------------------------------------------- commit 020375d1e723339a95b86d0d3b8a8214b1cc144a Author: Ben Gamari Date: Fri Dec 4 13:14:27 2015 +0100 Add linter to check for binaries accidentally added to repository This should catch mistakes like a703fbce20969e6f02e74fee76c0a9e22b513426. Adds an arcanist-external-json-linter submodule, which should eventually be mirrored on haskell.org resources. Test Plan: Validate Reviewers: thomie, hvr, austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D1515 >--------------------------------------------------------------- 020375d1e723339a95b86d0d3b8a8214b1cc144a .arc-linters/arcanist-external-json-linter | 1 + .arc-linters/check-binaries.py | 20 ++++++++++++++++++++ .arcconfig | 6 +++++- .arclint | 4 ++++ .gitmodules | 3 +++ 5 files changed, 33 insertions(+), 1 deletion(-) diff --git a/.arc-linters/arcanist-external-json-linter b/.arc-linters/arcanist-external-json-linter new file mode 160000 index 0000000..85ece0f --- /dev/null +++ b/.arc-linters/arcanist-external-json-linter @@ -0,0 +1 @@ +Subproject commit 85ece0f8653e7b1e7de6024d372cfeaf36ab5fa9 diff --git a/.arc-linters/check-binaries.py b/.arc-linters/check-binaries.py new file mode 100755 index 0000000..ae00756 --- /dev/null +++ b/.arc-linters/check-binaries.py @@ -0,0 +1,20 @@ +#!/usr/bin/env python + +# A linter to warn when binary files are added to the repository + +import sys +import os +import json + +path = sys.argv[1] +warnings = [] +if os.path.isfile(path): + with open(path) as f: + if '\0' in f.read(8000): + warning = { + 'severity': 'warning', + 'message': 'This file appears to be a binary file; does it really belong in the repository?' + } + warnings.append(warning) + +print json.dumps(warnings) diff --git a/.arcconfig b/.arcconfig index b9c3932..c886789 100644 --- a/.arcconfig +++ b/.arcconfig @@ -1,5 +1,9 @@ { "project.name" : "ghc", "repository.callsign" : "GHC", - "phabricator.uri" : "https://phabricator.haskell.org" + "phabricator.uri" : "https://phabricator.haskell.org", + + "load": [ + ".arc-linters/arcanist-external-json-linter" + ] } diff --git a/.arclint b/.arclint index 8f83776..1b13507 100644 --- a/.arclint +++ b/.arclint @@ -52,6 +52,10 @@ "severity": { "2": "disabled" } + }, + "check-binaries": { + "type": "external-json", + "external-json.script": "python .arc-linters/check-binaries.py" } }, diff --git a/.gitmodules b/.gitmodules index 662f6d6..0d88e01 100644 --- a/.gitmodules +++ b/.gitmodules @@ -115,3 +115,6 @@ path = libffi-tarballs url = ../libffi-tarballs.git ignore = none +[submodule ".arc-linters/arcanist-external-json-linter"] + path = .arc-linters/arcanist-external-json-linter + url = https://github.com/bgamari/arcanist-external-json-linter.git From git at git.haskell.org Fri Dec 4 16:31:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 4 Dec 2015 16:31:30 +0000 (UTC) Subject: [commit: ghc] master: lint: Add linter to catch uses of ASSERT macro that Clang dislikes (901cab1) Message-ID: <20151204163130.1E2073A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/901cab10609dc9795e57163834512373530fc4a5/ghc >--------------------------------------------------------------- commit 901cab10609dc9795e57163834512373530fc4a5 Author: Ben Gamari Date: Fri Dec 4 13:25:26 2015 +0100 lint: Add linter to catch uses of ASSERT macro that Clang dislikes In particular Clang rejects uses of CPP macros where the argument list is separated by a space from the macro name. Warn when we see ASSERT used in this way. >--------------------------------------------------------------- 901cab10609dc9795e57163834512373530fc4a5 .arc-linters/check-cpp.py | 37 +++++++++++++++++++++++++++++++++++++ .arclint | 5 +++++ 2 files changed, 42 insertions(+) diff --git a/.arc-linters/check-cpp.py b/.arc-linters/check-cpp.py new file mode 100755 index 0000000..3794ca2 --- /dev/null +++ b/.arc-linters/check-cpp.py @@ -0,0 +1,37 @@ +#!/usr/bin/env python + +# A linter to warn for ASSERT macros which are separated from their argument +# list by a space, which Clang's CPP barfs on + +import sys +import logging +import os +import json +import re + + +def setup_logging(): + logger = logging.getLogger() + hdlr = logging.FileHandler('linter.log', 'w') + logger.addHandler(hdlr) + logger.setLevel(logging.DEBUG) + return logger + +logger = setup_logging() +#logger.debug(sys.argv) + +path = sys.argv[1] +warnings = [] +if os.path.isfile(path): + with open(path) as f: + for lineno, line in enumerate(f): + if re.search('ASSERT \(', line) is not None: + warning = { + 'severity': 'warning', + 'message': 'CPP macros should not have a space between the macro name and their argument list', + 'line': lineno+1, + } + warnings.append(warning) + +logger.debug(warnings) +print json.dumps(warnings) diff --git a/.arclint b/.arclint index 1b13507..ef43856 100644 --- a/.arclint +++ b/.arclint @@ -56,6 +56,11 @@ "check-binaries": { "type": "external-json", "external-json.script": "python .arc-linters/check-binaries.py" + }, + "bad-assert-clang-cpp": { + "type": "external-json", + "include": ["(\\.(l?hs|x|y\\.pp)(\\.in)?$)"], + "external-json.script": "python .arc-linters/check-cpp.py" } }, From git at git.haskell.org Fri Dec 4 20:37:52 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 4 Dec 2015 20:37:52 +0000 (UTC) Subject: [commit: ghc] master: StgCmmMonad: Implement Outputable instance for Sequel for debugging (c865c42) Message-ID: <20151204203752.99A553A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c865c425a37b0bc52f4dead9d70eb0ee2bc287d6/ghc >--------------------------------------------------------------- commit c865c425a37b0bc52f4dead9d70eb0ee2bc287d6 Author: ?mer Sinan A?acan Date: Fri Dec 4 15:36:47 2015 -0500 StgCmmMonad: Implement Outputable instance for Sequel for debugging Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1563 >--------------------------------------------------------------- c865c425a37b0bc52f4dead9d70eb0ee2bc287d6 compiler/codeGen/StgCmmMonad.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/compiler/codeGen/StgCmmMonad.hs b/compiler/codeGen/StgCmmMonad.hs index 7ddbcd6..dd82b7f 100644 --- a/compiler/codeGen/StgCmmMonad.hs +++ b/compiler/codeGen/StgCmmMonad.hs @@ -227,6 +227,10 @@ data Sequel -- may allocate (e.g. it's a foreign call or -- allocating primOp) +instance Outputable Sequel where + ppr (Return b) = ptext (sLit "Return") <+> ppr b + ppr (AssignTo regs b) = ptext (sLit "AssignTo") <+> ppr regs <+> ppr b + -- See Note [sharing continuations] below data ReturnKind = AssignedDirectly From git at git.haskell.org Fri Dec 4 22:07:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 4 Dec 2015 22:07:21 +0000 (UTC) Subject: [commit: ghc] master: libdw: enable support only on i386 and amd64 (e2c518e) Message-ID: <20151204220721.5F85D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e2c518e6a751b7a16c704198a14dcc688b020038/ghc >--------------------------------------------------------------- commit e2c518e6a751b7a16c704198a14dcc688b020038 Author: Sergei Trofimovich Date: Fri Dec 4 22:07:13 2015 +0000 libdw: enable support only on i386 and amd64 Summary: Currently libdw requires per-arch implementation of set_initial_registers() function. Otherwise build fails with linkage error (seen on sparc): rts/dist/build/libHSrts_thr-ghc7.11.20151129.so: undefined reference to `set_initial_registers' collect2: error: ld returned 1 exit status `gcc' failed in phase `Linker'. (Exit code: 1) make[1]: *** [ghc/stage2/build/tmp/ghc-stage2] Error 1 Converted link-time error to compile-time error, added arch whitelist. Signed-off-by: Sergei Trofimovich Reviewers: austin, thomie, bgamari Reviewed By: bgamari Differential Revision: https://phabricator.haskell.org/D1567 >--------------------------------------------------------------- e2c518e6a751b7a16c704198a14dcc688b020038 mk/config.mk.in | 6 +++--- rts/Libdw.c | 5 +++-- 2 files changed, 6 insertions(+), 5 deletions(-) diff --git a/mk/config.mk.in b/mk/config.mk.in index 967c751..d7cd05b 100644 --- a/mk/config.mk.in +++ b/mk/config.mk.in @@ -371,9 +371,9 @@ UseSystemLibFFI=@UseSystemLibFFI@ FFILibDir=@FFILibDir@ FFIIncludeDir=@FFIIncludeDir@ - -# Include support for DWARF unwinding -GhcRtsWithLibdw = @HaveLibdw@ +# GHC needs arch-specific tweak at least in +# rts/Libdw.c:set_initial_registers() +GhcRtsWithLibdw=$(strip $(if $(filter $(TargetArch_CPP),i386 x86_64), at HaveLibdw@,NO)) ################################################################################ # diff --git a/rts/Libdw.c b/rts/Libdw.c index 1ef51b2..8c3c581 100644 --- a/rts/Libdw.c +++ b/rts/Libdw.c @@ -299,8 +299,7 @@ static bool set_initial_registers(Dwfl_Thread *thread, ); return dwfl_thread_state_registers(thread, 0, 17, regs); } -#endif -#ifdef i386_HOST_ARCH +#elif defined(i386_HOST_ARCH) static bool set_initial_registers(Dwfl_Thread *thread, void *arg STG_UNUSED) { Dwarf_Word regs[9]; @@ -321,6 +320,8 @@ static bool set_initial_registers(Dwfl_Thread *thread, ); return dwfl_thread_state_registers(thread, 0, 9, regs); } +#else +# error "Please implement set_initial_registers() for your arch" #endif static const Dwfl_Thread_Callbacks thread_cbs = { From git at git.haskell.org Sat Dec 5 00:54:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 5 Dec 2015 00:54:26 +0000 (UTC) Subject: [commit: ghc] master: pmcheck: Comments about term equality representation (81cf200) Message-ID: <20151205005426.DED153A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/81cf200902628a6539572774ecc66678e133daaf/ghc >--------------------------------------------------------------- commit 81cf200902628a6539572774ecc66678e133daaf Author: George Karachalias Date: Sat Dec 5 01:13:33 2015 +0100 pmcheck: Comments about term equality representation >--------------------------------------------------------------- 81cf200902628a6539572774ecc66678e133daaf compiler/deSugar/Check.hs | 63 ++++++++++++++++++++++++++++++++++++++++++++ compiler/deSugar/TmOracle.hs | 3 ++- 2 files changed, 65 insertions(+), 1 deletion(-) diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs index dcf3b23..25b8480 100644 --- a/compiler/deSugar/Check.hs +++ b/compiler/deSugar/Check.hs @@ -72,6 +72,7 @@ The algorithm used is described in the paper: type PmM a = DsM a data PmConstraint = TmConstraint PmExpr PmExpr -- ^ Term equalities: e ~ e + -- See Note [Representation of Term Equalities] | TyConstraint [EvVar] -- ^ Type equalities | BtConstraint Id -- ^ Strictness constraints: x ~ _|_ @@ -1122,6 +1123,7 @@ uMatcher us gvsa (p@(PmLit l)) ps (PmVar x) vsa (non_match_cs `mkConstraint` (VA (PmVar x) `mkCons` vsa)) where match_cs = [ TmConstraint (PmExprVar x) (PmExprLit l)] + -- See Note [Representation of Term Equalities] non_match_cs = [ TmConstraint falsePmExpr (PmExprEq (PmExprVar x) (PmExprLit l)) ] @@ -1362,3 +1364,64 @@ ppr_uncovered (expr_vec, complex) where sdoc_vec = mapM pprPmExprWithParens expr_vec (vec,cs) = runPmPprM sdoc_vec (filterComplex complex) + +{- Note [Representation of Term Equalities] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +In the paper, term constraints always take the form (x ~ e). Of course, a more +general constraint of the form (e1 ~ e1) can always be transformed to an +equivalent set of the former constraints, by introducing a fresh, intermediate +variable: { y ~ e1, y ~ e1 }. Yet, implementing this representation gave rise +to #11160 (incredibly bad performance for literal pattern matching). Two are +the main sources of this problem (the actual problem is how these two interact +with each other): + +1. Pattern matching on literals generates twice as many constraints as needed. + Consider the following (tests/ghci/should_run/ghcirun004): + + foo :: Int -> Int + foo 1 = 0 + ... + foo 5000 = 4999 + + The covered and uncovered set *should* look like: + U0 = { x |> {} } + + C1 = { 1 |> { x ~ 1 } } + U1 = { x |> { False ~ (x ~ 1) } } + ... + C10 = { 10 |> { False ~ (x ~ 1), .., False ~ (x ~ 9), x ~ 10 } } + U10 = { x |> { False ~ (x ~ 1), .., False ~ (x ~ 9), False ~ (x ~ 10) } } + ... + + If replace { False ~ (x ~ 1) }, with { y ~ False, y ~ (x ~ 1) } + we get twice as many constraints. Also note that half of them are just the + substitution [x |-> False]. + +2. The term oracle (`tmOracle` in deSugar/TmOracle) uses equalities of the form + (x ~ e) as substitutions [x |-> e]. More specifically, function + `extendSubstAndSolve` applies such substitutions in the residual constraints + and partitions them in the affected and non-affected ones, which are the new + worklist. Essentially, this gives quadradic behaviour on the number of the + residual constraints. (This would not be the case if the term oracle used + mutable variables but, since we use it to handle disjunctions on value set + abstractions (`Union` case), we chose a pure, incremental interface). + +Now the problem becomes apparent (e.g. for clause 300): + * Set U300 contains 300 substituting constraints [y_i |-> False] and 300 + constraints that we know that will not reduce (stay in the worklist). + * To check for consistency, we apply the substituting constraints ONE BY ONE + (since `tmOracle` is called incrementally, it does not have all of them + available at once). Hence, we go through the (non-progressing) constraints + over and over, achieving over-quadradic behaviour. + +If instead we allow constraints of the form (e ~ e), + * All uncovered sets Ui contain no substituting constraints and i + non-progressing constraints of the form (False ~ (x ~ lit)) so the oracle + behaves linearly. + * All covered sets Ci contain exactly (i-1) non-progressing constraints and + a single substituting constraint. So the term oracle goes through the + constraints only once. + +The performance improvement becomes even more important when more arguments are +involved. +-} diff --git a/compiler/deSugar/TmOracle.hs b/compiler/deSugar/TmOracle.hs index c0c1480..9224336 100644 --- a/compiler/deSugar/TmOracle.hs +++ b/compiler/deSugar/TmOracle.hs @@ -136,7 +136,8 @@ extendSubstAndSolve x e (standby, (unhandled, env)) where -- Apply the substitution to the worklist and partition them to the ones -- that had some progress and the rest. Then, recurse over the ones that - -- had some progress. + -- had some progress. Careful about performance: + -- See Note [Representation of Term Equalities] in deSugar/Check.hs (changed, unchanged) = partitionWith (substComplexEq x e) standby new_incr_state = (unchanged, (unhandled, Map.insert x e env)) From git at git.haskell.org Sat Dec 5 00:54:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 5 Dec 2015 00:54:29 +0000 (UTC) Subject: [commit: ghc] master: pmcheck: Comments about undecidability of literal equality (406444b) Message-ID: <20151205005429.8006B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/406444b5f4173c20567abc3a3577a58a8ade10d4/ghc >--------------------------------------------------------------- commit 406444b5f4173c20567abc3a3577a58a8ade10d4 Author: George Karachalias Date: Sat Dec 5 01:52:58 2015 +0100 pmcheck: Comments about undecidability of literal equality >--------------------------------------------------------------- 406444b5f4173c20567abc3a3577a58a8ade10d4 compiler/deSugar/Check.hs | 3 ++ compiler/deSugar/PmExpr.hs | 75 +++++++++++++++++++++++++++++++++++++++----- compiler/deSugar/TmOracle.hs | 2 ++ 3 files changed, 73 insertions(+), 7 deletions(-) diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs index 25b8480..386652a 100644 --- a/compiler/deSugar/Check.hs +++ b/compiler/deSugar/Check.hs @@ -1048,6 +1048,7 @@ cMatcher us gvsa (p@(PmCon { pm_con_con = c1, pm_con_args = args1 })) ps -- CLitLit cMatcher us gvsa (PmLit l1) ps (va@(PmLit l2)) vsa = case eqPmLit l1 l2 of + -- See Note [Undecidable Equality for Overloaded Literals] True -> VA va `mkCons` covered us gvsa ps vsa -- match False -> Empty -- mismatch @@ -1101,6 +1102,7 @@ uMatcher us gvsa ( p@(PmCon { pm_con_con = c1, pm_con_args = args1 })) ps -- ULitLit uMatcher us gvsa (PmLit l1) ps (va@(PmLit l2)) vsa = case eqPmLit l1 l2 of + -- See Note [Undecidable Equality for Overloaded Literals] True -> VA va `mkCons` uncovered us gvsa ps vsa -- match False -> VA va `mkCons` vsa -- mismatch @@ -1161,6 +1163,7 @@ dMatcher us gvsa (p@(PmCon { pm_con_con = c1, pm_con_args = args1 })) ps -- DLitLit dMatcher us gvsa (PmLit l1) ps (va@(PmLit l2)) vsa = case eqPmLit l1 l2 of + -- See Note [Undecidable Equality for Overloaded Literals] True -> VA va `mkCons` divergent us gvsa ps vsa -- match False -> Empty -- mismatch diff --git a/compiler/deSugar/PmExpr.hs b/compiler/deSugar/PmExpr.hs index 78a51e6..16528d4 100644 --- a/compiler/deSugar/PmExpr.hs +++ b/compiler/deSugar/PmExpr.hs @@ -62,18 +62,79 @@ data PmExpr = PmExprVar Id data PmLit = PmSLit HsLit -- simple | PmOLit Bool {- is it negated? -} (HsOverLit Id) -- overloaded --- | PmLit equality. If both literals are overloaded, the equality check may be --- inconclusive. Since an overloaded PmLit represents a function application --- (e.g. fromInteger 5), if two literals look the same they are the same but --- if they don't, whether they are depends on the implementation of the --- from-function. Yet, for the purposes of the check, we check syntactically --- only (it is safe anyway, since literals always need a catch-all to be --- considered to be exhaustive). +-- | Equality between literals for pattern match checking. eqPmLit :: PmLit -> PmLit -> Bool eqPmLit (PmSLit l1) (PmSLit l2) = l1 == l2 eqPmLit (PmOLit b1 l1) (PmOLit b2 l2) = b1 == b2 && l1 == l2 + -- See Note [Undecidable Equality for Overloaded Literals] eqPmLit _ _ = False +{- Note [Undecidable Equality for Overloaded Literals] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Equality on overloaded literals is undecidable in the general case. Consider +the following example: + + instance Num Bool where + ... + fromInteger 0 = False -- C-like representation of booleans + fromInteger _ = True + + f :: Bool -> () + f 1 = () -- Clause A + f 2 = () -- Clause B + +Clause B is redundant but to detect this, we should be able to solve the +constraint: False ~ (fromInteger 2 ~ fromInteger 1) which means that we +have to look through function `fromInteger`, whose implementation could +be anything. This poses difficulties for: + +1. The expressive power of the check. + We cannot expect a reasonable implementation of pattern matching to detect + that fromInteger 2 ~ fromInteger 1 is True, unless we unfold function + fromInteger. This puts termination at risk and is undecidable in the + general case. + +2. Performance. + Having an unresolved constraint False ~ (fromInteger 2 ~ fromInteger 1) + lying around could become expensive really fast. Ticket #11161 illustrates + how heavy use of overloaded literals can generate plenty of those + constraints, effectively undermining the term oracle's performance. + +3. Error nessages/Warnings. + What should our message for `f` above be? A reasonable approach would be + to issue: + + Pattern matches are (potentially) redundant: + f 2 = ... under the assumption that 1 == 2 + + but seems to complex and confusing for the user. + +We choose to treat overloaded literals that look different as different. The +impact of this is the following: + + * Redundancy checking is rather conservative, since it cannot see that clause + B above is redundant. + + * We have instant equality check for overloaded literals (we do not rely on + the term oracle which is rather expensive, both in terms of performance and + memory). This significantly improves the performance of functions `covered` + `uncovered` and `divergent` in deSugar/Check.hs and effectively addresses + #11161. + + * The warnings issued are simpler. + + * We do not play on the safe side, strictly speaking. The assumption that + 1 /= 2 makes the redundancy check more conservative but at the same time + makes its dual (exhaustiveness check) unsafe. This we can live with, mainly + for two reasons: + 1. At the moment we do not use the results of the check during compilation + where this would be a disaster (could result in runtime errors even if + our function was deemed exhaustive). + 2. Pattern matcing on literals can never be considered exhaustive unless we + have a catch-all clause. Hence, this assumption affects mainly the + appearance of the warnings and is, in practice safe. +-} + nubPmLit :: [PmLit] -> [PmLit] nubPmLit = nubBy eqPmLit diff --git a/compiler/deSugar/TmOracle.hs b/compiler/deSugar/TmOracle.hs index 9224336..5d7a61a 100644 --- a/compiler/deSugar/TmOracle.hs +++ b/compiler/deSugar/TmOracle.hs @@ -105,6 +105,7 @@ solveComplexEq solver_state@(standby, (unhandled, env)) eq@(e1, e2) = case eq of (_,PmExprOther _) -> Just (standby, (True, env)) (PmExprLit l1, PmExprLit l2) -> case eqPmLit l1 l2 of + -- See Note [Undecidable Equality for Overloaded Literals] True -> Just solver_state False -> Nothing @@ -165,6 +166,7 @@ simplifyEqExpr e1 e2 = case (e1, e2) of -- Literals (PmExprLit l1, PmExprLit l2) -> case eqPmLit l1 l2 of + -- See Note [Undecidable Equality for Overloaded Literals] True -> (truePmExpr, True) False -> (falsePmExpr, True) From git at git.haskell.org Sat Dec 5 06:13:06 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 5 Dec 2015 06:13:06 +0000 (UTC) Subject: [commit: ghc] master: Fix broken linters when using python3 (8f28797) Message-ID: <20151205061306.D87DE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8f2879794a75aad64b5998227c81c2ef569be35f/ghc >--------------------------------------------------------------- commit 8f2879794a75aad64b5998227c81c2ef569be35f Author: David Kraeutmann Date: Sat Dec 5 00:13:08 2015 -0600 Fix broken linters when using python3 Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D1574 >--------------------------------------------------------------- 8f2879794a75aad64b5998227c81c2ef569be35f .arc-linters/check-binaries.py | 2 +- .arc-linters/check-cpp.py | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/.arc-linters/check-binaries.py b/.arc-linters/check-binaries.py index ae00756..9125985 100755 --- a/.arc-linters/check-binaries.py +++ b/.arc-linters/check-binaries.py @@ -17,4 +17,4 @@ if os.path.isfile(path): } warnings.append(warning) -print json.dumps(warnings) +print(json.dumps(warnings)) diff --git a/.arc-linters/check-cpp.py b/.arc-linters/check-cpp.py index 3794ca2..c58da09 100755 --- a/.arc-linters/check-cpp.py +++ b/.arc-linters/check-cpp.py @@ -34,4 +34,4 @@ if os.path.isfile(path): warnings.append(warning) logger.debug(warnings) -print json.dumps(warnings) +print(json.dumps(warnings)) From git at git.haskell.org Sat Dec 5 08:21:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 5 Dec 2015 08:21:40 +0000 (UTC) Subject: [commit: ghc] master: Use git.h.o copy of arcanist-external-json-linter (c714f8f) Message-ID: <20151205082140.DF0A33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c714f8fd4288e86f2e0541512afef7e216c98699/ghc >--------------------------------------------------------------- commit c714f8fd4288e86f2e0541512afef7e216c98699 Author: Herbert Valerio Riedel Date: Sat Dec 5 09:15:57 2015 +0100 Use git.h.o copy of arcanist-external-json-linter It shouldn't have been possible to reference an external Git submodule not hosted on git.haskell.org as we can't otherwise ensure gitlink integrity. But it turns out the validation hook scripts in place didn't reject 020375d1e723339a95b86d0d3b8a8214b1cc144a, so here we are... This commit changes ghc.git to use our own fork/copy of https://github.com/bgamari/arcanist-external-json-linter hosted on git.haskell.org >--------------------------------------------------------------- c714f8fd4288e86f2e0541512afef7e216c98699 .gitmodules | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.gitmodules b/.gitmodules index 0d88e01..73ce0d1 100644 --- a/.gitmodules +++ b/.gitmodules @@ -117,4 +117,4 @@ ignore = none [submodule ".arc-linters/arcanist-external-json-linter"] path = .arc-linters/arcanist-external-json-linter - url = https://github.com/bgamari/arcanist-external-json-linter.git + url = ../arcanist-external-json-linter.git From git at git.haskell.org Sat Dec 5 08:57:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 5 Dec 2015 08:57:54 +0000 (UTC) Subject: [commit: ghc] master: Temporarily disable external-json linters (a14296c) Message-ID: <20151205085754.8B18A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a14296c2660521db8ba965065687e45cee4e3401/ghc >--------------------------------------------------------------- commit a14296c2660521db8ba965065687e45cee4e3401 Author: Herbert Valerio Riedel Date: Sat Dec 5 09:55:50 2015 +0100 Temporarily disable external-json linters This temporarily disables the external json linters introduced via 020375d1e723339a95b86d0d3b8a8214b1cc144a and 901cab10609dc9795e57163834512373530fc4a5. The new linters break the differential validation in Harbormaster because the submodules are not cloned early enough (i.e. before `arc` is called by the script). >--------------------------------------------------------------- a14296c2660521db8ba965065687e45cee4e3401 .arcconfig | 6 +----- .arclint | 9 --------- 2 files changed, 1 insertion(+), 14 deletions(-) diff --git a/.arcconfig b/.arcconfig index c886789..b9c3932 100644 --- a/.arcconfig +++ b/.arcconfig @@ -1,9 +1,5 @@ { "project.name" : "ghc", "repository.callsign" : "GHC", - "phabricator.uri" : "https://phabricator.haskell.org", - - "load": [ - ".arc-linters/arcanist-external-json-linter" - ] + "phabricator.uri" : "https://phabricator.haskell.org" } diff --git a/.arclint b/.arclint index ef43856..8f83776 100644 --- a/.arclint +++ b/.arclint @@ -52,15 +52,6 @@ "severity": { "2": "disabled" } - }, - "check-binaries": { - "type": "external-json", - "external-json.script": "python .arc-linters/check-binaries.py" - }, - "bad-assert-clang-cpp": { - "type": "external-json", - "include": ["(\\.(l?hs|x|y\\.pp)(\\.in)?$)"], - "external-json.script": "python .arc-linters/check-cpp.py" } }, From git at git.haskell.org Sat Dec 5 10:13:52 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 5 Dec 2015 10:13:52 +0000 (UTC) Subject: [commit: ghc] master: Enable non-canonical Monad instance warnings for stage1/2 (51d08d8) Message-ID: <20151205101352.6295D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/51d08d82b7681d23d89e6c240ec4dcfd8801edb1/ghc >--------------------------------------------------------------- commit 51d08d82b7681d23d89e6c240ec4dcfd8801edb1 Author: Herbert Valerio Riedel Date: Sat Dec 5 09:59:01 2015 +0100 Enable non-canonical Monad instance warnings for stage1/2 This makes use of the new facility introduced via 14d0f7f1221db758cd06a69f53803d9d0150164a which allows to have certain flags passed only to the non-bootstrapping GHC. This is needed because sometimes we can't assume the existence of a certain flag in the bootstrapping compiler which was only added recently to GHC HEAD. This also updates the haddock submodule to fix a few remaining noncanonical instance definitions. Differential Revision: https://phabricator.haskell.org/D1571 >--------------------------------------------------------------- 51d08d82b7681d23d89e6c240ec4dcfd8801edb1 mk/warnings.mk | 2 ++ utils/haddock | 2 +- 2 files changed, 3 insertions(+), 1 deletion(-) diff --git a/mk/warnings.mk b/mk/warnings.mk index d604f9a..f8db8fd 100644 --- a/mk/warnings.mk +++ b/mk/warnings.mk @@ -32,6 +32,8 @@ SRC_CC_WARNING_OPTS += -Wno-unknown-pragmas endif +SRC_HC_WARNING_OPTS_STAGE1 += -fwarn-noncanonical-monad-instances +SRC_HC_WARNING_OPTS_STAGE2 += -fwarn-noncanonical-monad-instances ###################################################################### diff --git a/utils/haddock b/utils/haddock index 42b2cfc..a6deefa 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit 42b2cfc595f1ee62d1c1b8513c5df1d92709c06a +Subproject commit a6deefad581cbeb62048826bc1d626c41a0dd56c From git at git.haskell.org Sat Dec 5 10:41:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 5 Dec 2015 10:41:32 +0000 (UTC) Subject: [commit: ghc] master: ghc.mk: cleanup: use tab consistently (314bc99) Message-ID: <20151205104132.CC8C23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/314bc99abfdf7dc6ece5813fdc2e4e1f1fdeb291/ghc >--------------------------------------------------------------- commit 314bc99abfdf7dc6ece5813fdc2e4e1f1fdeb291 Author: Sergei Trofimovich Date: Fri Dec 4 22:28:35 2015 +0000 ghc.mk: cleanup: use tab consistently Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- 314bc99abfdf7dc6ece5813fdc2e4e1f1fdeb291 utils/mkUserGuidePart/ghc.mk | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/mkUserGuidePart/ghc.mk b/utils/mkUserGuidePart/ghc.mk index 87c9d65..86492e1 100644 --- a/utils/mkUserGuidePart/ghc.mk +++ b/utils/mkUserGuidePart/ghc.mk @@ -42,7 +42,7 @@ utils/mkUserGuidePart_GENERATED_FLAGS_SETS := \ utils/mkUserGuidePart_GENERATED_RST_SOURCES := \ $(addprefix docs/users_guide/flags-,$(addsuffix .gen.rst,$(utils/mkUserGuidePart_GENERATED_FLAGS_SETS))) \ docs/users_guide/what_glasgow_exts_does.gen.rst \ - docs/man/all-flags.gen.rst + docs/man/all-flags.gen.rst utils/mkUserGuidePart_USES_CABAL = YES utils/mkUserGuidePart_PACKAGE = mkUserGuidePart From git at git.haskell.org Sat Dec 5 10:41:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 5 Dec 2015 10:41:35 +0000 (UTC) Subject: [commit: ghc] master: ghc.mk: don't run mkUserGuidePart more than once (d6512c7) Message-ID: <20151205104135.7278D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d6512c740c653d2a58a7fc73b777e50d02f786b1/ghc >--------------------------------------------------------------- commit d6512c740c653d2a58a7fc73b777e50d02f786b1 Author: Sergei Trofimovich Date: Sat Dec 5 00:03:05 2015 +0000 ghc.mk: don't run mkUserGuidePart more than once When building 'html' and 'man' manuals build system reports mkUserGuide is ran more than once (up to 3 times in parallel). See Note [Blessed make target file] for more details. Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- d6512c740c653d2a58a7fc73b777e50d02f786b1 utils/mkUserGuidePart/ghc.mk | 42 +++++++++++++++++++++++++++++++++++++++--- 1 file changed, 39 insertions(+), 3 deletions(-) diff --git a/utils/mkUserGuidePart/ghc.mk b/utils/mkUserGuidePart/ghc.mk index 86492e1..3a654da 100644 --- a/utils/mkUserGuidePart/ghc.mk +++ b/utils/mkUserGuidePart/ghc.mk @@ -39,11 +39,18 @@ utils/mkUserGuidePart_GENERATED_FLAGS_SETS := \ verbosity \ warnings -utils/mkUserGuidePart_GENERATED_RST_SOURCES := \ +# See Note [Blessed make target file] +utils/mkUserGuidePart_GENERATED_RST_SOURCES_BLESSED_FILE := \ + docs/users_guide/what_glasgow_exts_does.gen.rst + +utils/mkUserGuidePart_GENERATED_RST_SOURCES_OTHER_FILES := \ $(addprefix docs/users_guide/flags-,$(addsuffix .gen.rst,$(utils/mkUserGuidePart_GENERATED_FLAGS_SETS))) \ - docs/users_guide/what_glasgow_exts_does.gen.rst \ docs/man/all-flags.gen.rst +utils/mkUserGuidePart_GENERATED_RST_SOURCES := \ + $(utils/mkUserGuidePart_GENERATED_RST_SOURCES_BLESSED_FILE) \ + $(utils/mkUserGuidePart_GENERATED_RST_SOURCES_OTHER_FILES) + utils/mkUserGuidePart_USES_CABAL = YES utils/mkUserGuidePart_PACKAGE = mkUserGuidePart utils/mkUserGuidePart_dist_PROGNAME = mkUserGuidePart @@ -52,7 +59,36 @@ utils/mkUserGuidePart_dist_INSTALL_INPLACE = YES $(eval $(call build-prog,utils/mkUserGuidePart,dist,2)) $(eval $(call clean-target,utils/mkUserGuidePart,gen,$(utils/mkUserGuidePart_GENERATED_RST_SOURCES))) -$(utils/mkUserGuidePart_GENERATED_RST_SOURCES) : $(mkUserGuidePart_INPLACE) +$(utils/mkUserGuidePart_GENERATED_RST_SOURCES_OTHER_FILES) : + +$(utils/mkUserGuidePart_GENERATED_RST_SOURCES_BLESSED_FILE) : $(utils/mkUserGuidePart_GENERATED_RST_SOURCES_OTHER_FILES) $(mkUserGuidePart_INPLACE) $(mkUserGuidePart_INPLACE) + $(TOUCH_CMD) $@ all_utils/mkUserGuidePart: $(mkUserGuidePart_INPLACE) + +# Note [Blessed make target file] +# +# make cannot express nicely a single build rule +# with multiple targets: +# +# > all: a b +# > a b: +# > touch a b +# +# This code will run 'touch' rule twice when parallel +# make is used: +# > $ make -j +# > touch a b +# > touch a b +# +# But there is a workaround for it: +# We pick a single file of a group and depend on it +# as an ultimate target. We also need to make sure +# that file has latest timestamp in the group: +# +# > all: a b +# > b: +# > a: b +# > touch a b +# > touch $@ From git at git.haskell.org Sat Dec 5 10:41:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 5 Dec 2015 10:41:38 +0000 (UTC) Subject: [commit: ghc] master: ghc.mk: fix docs re-rebuilding (13ab2c6) Message-ID: <20151205104138.1F5143A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/13ab2c64a7e98bab391222dbd015ea3a4b91a9ed/ghc >--------------------------------------------------------------- commit 13ab2c64a7e98bab391222dbd015ea3a4b91a9ed Author: Sergei Trofimovich Date: Sat Dec 5 10:05:54 2015 +0000 ghc.mk: fix docs re-rebuilding The problem: $ make # no changes in sources $ make The problem was due to wrong assumption about what files exactly are generated by mkUserGuidePart. Build system expected the following files to be created: docs/man/all-flags.gen.rst flags-recompilating-checking.gen.rst but mkUserGuidePart generated: docs/users_guide/all-flags.gen.rst flags-recompilation-checking.gen.rst Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- 13ab2c64a7e98bab391222dbd015ea3a4b91a9ed utils/mkUserGuidePart/ghc.mk | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/utils/mkUserGuidePart/ghc.mk b/utils/mkUserGuidePart/ghc.mk index 3a654da..069634b 100644 --- a/utils/mkUserGuidePart/ghc.mk +++ b/utils/mkUserGuidePart/ghc.mk @@ -32,7 +32,6 @@ utils/mkUserGuidePart_GENERATED_FLAGS_SETS := \ plugin \ profiling \ program-coverage \ - recompilating-checking \ recompilation-checking \ redirecting-output \ temporary-files \ @@ -45,7 +44,7 @@ utils/mkUserGuidePart_GENERATED_RST_SOURCES_BLESSED_FILE := \ utils/mkUserGuidePart_GENERATED_RST_SOURCES_OTHER_FILES := \ $(addprefix docs/users_guide/flags-,$(addsuffix .gen.rst,$(utils/mkUserGuidePart_GENERATED_FLAGS_SETS))) \ - docs/man/all-flags.gen.rst + docs/users_guide/all-flags.gen.rst utils/mkUserGuidePart_GENERATED_RST_SOURCES := \ $(utils/mkUserGuidePart_GENERATED_RST_SOURCES_BLESSED_FILE) \ From git at git.haskell.org Sat Dec 5 16:09:58 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 5 Dec 2015 16:09:58 +0000 (UTC) Subject: [commit: ghc] wip/T11028-2: Refactor ConDecl (b43b6b0) Message-ID: <20151205160958.6459C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T11028-2 Link : http://ghc.haskell.org/trac/ghc/changeset/b43b6b0c97e9f88331d04224e80b9a659606db4c/ghc >--------------------------------------------------------------- commit b43b6b0c97e9f88331d04224e80b9a659606db4c Author: Alan Zimmerman Date: Mon Nov 23 22:59:27 2015 +0200 Refactor ConDecl Summary: The ConDecl type in HsDecls is an uneasy compromise. For the most part, HsSyn directly reflects the syntax written by the programmer; and that gives just the right "pegs" on which to hang Alan's API annotations. But ConDecl doesn't properly reflect the syntax of Haskell-98 and GADT-style data type declarations. To be concrete, here's a draft new data type data ConDecl name | ConDeclGADT { con_names :: [Located name] , con_type :: LHsSigType name -- The type after the ?::? , con_doc :: Maybe LHsDocString } | ConDeclH98 { con_name :: Located name , con_qvars :: Maybe (LHsQTyVars name) -- User-written forall (if any), and its implicit -- kind variables -- Non-Nothing needs -XExistentialQuantification , con_cxt :: Maybe (LHsContext name) -- ^ User-written context (if any) , con_details :: HsConDeclDetails name -- ^ Arguments , con_doc :: Maybe LHsDocString -- ^ A possible Haddock comment. } deriving (Typeable) Note that For GADTs, just keep a type. That's what the user writes. NB:HsType can represent records on the LHS of an arrow: { x:Int,y:Bool} -> T con_qvars and con_cxt are both Maybe because they are both optional (the forall and the context of an existential data type For ConDeclGADT the type variables of the data type do not scope over the con_type; whereas for ConDeclH98 they do scope over con_cxt and con_details. Test Plan: ./validate Reviewers: simonpj, austin, goldfire, bgamari Subscribers: goldfire, thomie, mpickering Differential Revision: https://phabricator.haskell.org/D1558 GHC Trac Issues: #11028 >--------------------------------------------------------------- b43b6b0c97e9f88331d04224e80b9a659606db4c compiler/deSugar/DsMeta.hs | 98 ++++++++--- compiler/hsSyn/Convert.hs | 22 ++- compiler/hsSyn/HsDecls.hs | 152 +++++++--------- compiler/hsSyn/HsLit.hs | 1 - compiler/hsSyn/HsTypes.hs | 4 +- compiler/hsSyn/HsUtils.hs | 26 ++- compiler/parser/Parser.y | 12 +- compiler/parser/RdrHsSyn.hs | 73 +++----- compiler/rename/RnEnv.hs | 4 +- compiler/rename/RnNames.hs | 13 +- compiler/rename/RnSource.hs | 120 +++++-------- compiler/rename/RnTypes.hs | 22 ++- compiler/typecheck/TcHsType.hs | 9 +- compiler/typecheck/TcRnDriver.hs | 2 +- compiler/typecheck/TcTyClsDecls.hs | 193 +++++++++++++++------ testsuite/tests/ghc-api/annotations/T10399.stdout | 2 - testsuite/tests/ghc-api/annotations/all.T | 2 +- testsuite/tests/ghc-api/landmines/landmines.stdout | 2 +- testsuite/tests/rename/should_compile/T5331.stderr | 2 +- testsuite/tests/rename/should_fail/T7943.stderr | 6 +- utils/haddock | 2 +- 21 files changed, 427 insertions(+), 340 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b43b6b0c97e9f88331d04224e80b9a659606db4c From git at git.haskell.org Sat Dec 5 16:10:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 5 Dec 2015 16:10:00 +0000 (UTC) Subject: [commit: ghc] wip/T11028-2's head updated: Refactor ConDecl (b43b6b0) Message-ID: <20151205161000.D73503A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T11028-2' now includes: 218fdf9 Make the order of fixities in the iface file deterministic 741f837 Implement more deterministic operations and document them 52b02e6 Comments only (isIrrefutablePat) b564731 Comments (TcSMonad) d00cdf2 Revert "ghci: Add support for prompt functions" 1caff20 StgSyn: Remove unused SRT constructor c75948b Move Stg-specific code from DynFlags to SimplStg d4d54b4 Remove *.xml from gitignore a12e47b Avoid panic due to partial ieName 8cba907 Create empty dump files when there was nothing to dump 0d1a2d2 ErrUtils: Spruce up Haddocks e7929ba Update bytestring submodule d25f3c0 users_guide/glasgow_exts.rst: fix link markup 8a50610 Major Overhaul of Pattern Match Checking (Fixes #595) 43a31fe testsuite: haddock.compiler: Bump expected allocations a034031 extending_ghc.rst: fix broken link (Trac #10950) c5597bb Revert "Create empty dump files when there was nothing to dump" 7b29b0b Fix haddock syntax 0dd61fe Kill redundant patterns 934b3a0 Update test output 40fc353 Bump hoopl submodule ae4398d Improve performance for PM check on literals (Fixes #11160 and #11161) 99d01e1 Remove unused import in deSugar/TmOracle.hs 7af29da Use Autoconf's AC_USE_SYSTEM_EXTENSIONS cd9f3bf RTS: Rename InCall.stat struct field to .rstat 6ef351d On AIX we need -D_BSD defined in d40f5b7 PmExpr: Fix CPP unacceptable too clang's CPP 36a208f Use builtin ISO 8859-1 decoder in mkTextEncoding befc4e4 Check: More Clang/CPP wibbles e9220da Bump allocations for T783 dc33e4c T5642 is broken 96e67c0 T5642: Skip it entirely 5b2b7e3 Make callToPats deterministic in SpecConstr 1c9fd3f Case-of-empty-alts is trivial (Trac #11155) 28035c0 Add derived constraints for wildcard signatures 1cb3c8c Wibbles only 822141b Make -dppr-debug show contents of (TypeError ...) 1160dc5 Fix egregious error in eta-reduction of data families 31b482b Minor refactoring of user type errors 67565a7 Tidy user type errors in checkValidType 43a5970 Comments only 16aae60 T5642: Fix skip usage caa6851 testsuite: Rename pmcheck/T7669 to pmcheck/T7669a d4bf863 Update peak_megabytes_allocated for T9675 020375d Add linter to check for binaries accidentally added to repository 901cab1 lint: Add linter to catch uses of ASSERT macro that Clang dislikes c865c42 StgCmmMonad: Implement Outputable instance for Sequel for debugging e2c518e libdw: enable support only on i386 and amd64 81cf200 pmcheck: Comments about term equality representation 406444b pmcheck: Comments about undecidability of literal equality 8f28797 Fix broken linters when using python3 c714f8f Use git.h.o copy of arcanist-external-json-linter a14296c Temporarily disable external-json linters 51d08d8 Enable non-canonical Monad instance warnings for stage1/2 314bc99 ghc.mk: cleanup: use tab consistently d6512c7 ghc.mk: don't run mkUserGuidePart more than once 13ab2c6 ghc.mk: fix docs re-rebuilding b43b6b0 Refactor ConDecl From git at git.haskell.org Sat Dec 5 18:15:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 5 Dec 2015 18:15:41 +0000 (UTC) Subject: [commit: ghc] master: Allow to compile OSMem.c when MEM_NORESERVE is not available (5f1e42f) Message-ID: <20151205181541.DBE113A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5f1e42f22cf29bc1b7150e06b2711fa7c43c6e5b/ghc >--------------------------------------------------------------- commit 5f1e42f22cf29bc1b7150e06b2711fa7c43c6e5b Author: Herbert Valerio Riedel Date: Sat Dec 5 19:15:19 2015 +0100 Allow to compile OSMem.c when MEM_NORESERVE is not available On some OSes such as AIX `MEM_NORESERVE` is not available. Since this feature is only needed when the new two-step allocator (see #9706) is enabled we can simply turn this into a runtime error to avoid a larger refactoring of this already quite platform-sensitive code. Reviewed By: bgamari, ezyang Differential Revision: https://phabricator.haskell.org/D1568 >--------------------------------------------------------------- 5f1e42f22cf29bc1b7150e06b2711fa7c43c6e5b rts/posix/OSMem.c | 7 +++++++ 1 file changed, 7 insertions(+) diff --git a/rts/posix/OSMem.c b/rts/posix/OSMem.c index 274d5ad..60e684f 100644 --- a/rts/posix/OSMem.c +++ b/rts/posix/OSMem.c @@ -151,7 +151,14 @@ my_mmap (void *addr, W_ size, int operation) else prot = PROT_NONE; if (operation == MEM_RESERVE) +# if defined(MAP_NORESERVE) flags = MAP_NORESERVE; +# else +# ifdef USE_LARGE_ADDRESS_SPACE +# error USE_LARGE_ADDRESS_SPACE needs MAP_NORESERVE +# endif + errorBelch("my_mmap(,,MEM_RESERVE) not supported on this platform"); +# endif else if (operation == MEM_COMMIT) flags = MAP_FIXED; else From git at git.haskell.org Sun Dec 6 10:55:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 6 Dec 2015 10:55:55 +0000 (UTC) Subject: [commit: ghc] master: Make ghc.mk compatible with pedantic /bin/sh impls (df67940) Message-ID: <20151206105555.132263A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/df6794035f1e4397d89896f329525e5368b7d1cc/ghc >--------------------------------------------------------------- commit df6794035f1e4397d89896f329525e5368b7d1cc Author: Herbert Valerio Riedel Date: Sun Dec 6 11:52:35 2015 +0100 Make ghc.mk compatible with pedantic /bin/sh impls This fixes `for`-loops introduced via 64761ce9a899954a12d8e3ae8b400c5ad9648137 which can result in `for i in ;` which some `/bin/sh` implementations don't like. >--------------------------------------------------------------- df6794035f1e4397d89896f329525e5368b7d1cc ghc.mk | 10 ++++++---- 1 file changed, 6 insertions(+), 4 deletions(-) diff --git a/ghc.mk b/ghc.mk index 9dd1c91..4aea480 100644 --- a/ghc.mk +++ b/ghc.mk @@ -875,17 +875,17 @@ install_bins: $(INSTALL_BINS) $(INSTALL_SCRIPTS) for i in $(INSTALL_BINS); do \ $(INSTALL_PROGRAM) $(INSTALL_BIN_OPTS) $$i "$(DESTDIR)$(bindir)" ; \ done +ifneq "$(INSTALL_SCRIPTS)" "" for i in $(INSTALL_SCRIPTS); do \ $(INSTALL_SCRIPT) $(INSTALL_OPTS) $$i "$(DESTDIR)$(bindir)" ; \ done +endif install_libs: $(INSTALL_LIBS) $(call installLibsTo, $(INSTALL_LIBS), "$(DESTDIR)$(ghclibdir)") install_libexecs: $(INSTALL_LIBEXECS) -ifeq "$(INSTALL_LIBEXECS)" "" - @: -else +ifneq "$(INSTALL_LIBEXECS)" "" $(INSTALL_DIR) "$(DESTDIR)$(ghclibexecdir)/bin" for i in $(INSTALL_LIBEXECS); do \ $(INSTALL_PROGRAM) $(INSTALL_BIN_OPTS) $$i "$(DESTDIR)$(ghclibexecdir)/bin"; \ @@ -900,9 +900,11 @@ install_topdirs: $(INSTALL_TOPDIR_BINS) $(INSTALL_TOPDIR_SCRIPTS) for i in $(INSTALL_TOPDIR_BINS); do \ $(INSTALL_PROGRAM) $(INSTALL_BIN_OPTS) $$i "$(DESTDIR)$(topdir)"; \ done +ifneq "$(INSTALL_TOPDIR_SCRIPTS)" "" for i in $(INSTALL_TOPDIR_SCRIPTS); do \ $(INSTALL_SCRIPT) $(INSTALL_OPTS) $$i "$(DESTDIR)$(topdir)"; \ done +endif install_docs: $(INSTALL_DOCS) $(INSTALL_DIR) "$(DESTDIR)$(docdir)" @@ -922,7 +924,7 @@ ifneq "$(INSTALL_LIBRARY_DOCS)" "" $(INSTALL_SCRIPT) $(INSTALL_OPTS) libraries/gen_contents_index "$(DESTDIR)$(docdir)/html/libraries/" endif ifneq "$(INSTALL_HTML_DOC_DIRS)" "" - # We need to filter out the directories so install doesn't choke on them +# We need to filter out the directories so install doesn't choke on them for i in $(INSTALL_HTML_DOC_DIRS); do \ $(INSTALL_DIR) "$(DESTDIR)$(docdir)/html/`basename $$i`"; \ for f in $$i/*; do \ From git at git.haskell.org Sun Dec 6 12:34:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 6 Dec 2015 12:34:29 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T11168' created Message-ID: <20151206123429.123133A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T11168 Referencing: ec70219fe3e996b032c7d7095fd4910746747c01 From git at git.haskell.org Sun Dec 6 12:34:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 6 Dec 2015 12:34:31 +0000 (UTC) Subject: [commit: ghc] wip/T11168: Tweak use of AC_USE_SYSTEM_EXTENSIONS (ec70219) Message-ID: <20151206123431.C60253A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T11168 Link : http://ghc.haskell.org/trac/ghc/changeset/ec70219fe3e996b032c7d7095fd4910746747c01/ghc >--------------------------------------------------------------- commit ec70219fe3e996b032c7d7095fd4910746747c01 Author: Herbert Valerio Riedel Date: Sun Dec 6 13:34:34 2015 +0100 Tweak use of AC_USE_SYSTEM_EXTENSIONS This is a follow-up to 7af29da05d2e5a5e311a5f73f20d0f232035973b >--------------------------------------------------------------- ec70219fe3e996b032c7d7095fd4910746747c01 configure.ac | 6 +++--- libraries/base/configure.ac | 5 ++--- libraries/integer-gmp/configure.ac | 2 ++ 3 files changed, 7 insertions(+), 6 deletions(-) diff --git a/configure.ac b/configure.ac index 57d877a..c8708ae 100644 --- a/configure.ac +++ b/configure.ac @@ -58,9 +58,6 @@ dnl #define SIZEOF_CHAR 0 dnl recently. AC_PREREQ([2.60]) -dnl make extensions visible to allow feature-tests to detect them lateron -AC_USE_SYSTEM_EXTENSIONS - # ------------------------------------------------------------------------- # Prepare to generate the following header files # @@ -462,6 +459,9 @@ export CC MAYBE_OVERRIDE_STAGE0([gcc],[CC_STAGE0]) MAYBE_OVERRIDE_STAGE0([ar],[AR_STAGE0]) +dnl make extensions visible to allow feature-tests to detect them lateron +AC_USE_SYSTEM_EXTENSIONS + dnl ** figure out how to invoke the C preprocessor (i.e. `gcc -E`) AC_PROG_CPP diff --git a/libraries/base/configure.ac b/libraries/base/configure.ac index 99474a6..5607213 100644 --- a/libraries/base/configure.ac +++ b/libraries/base/configure.ac @@ -5,9 +5,6 @@ AC_CONFIG_SRCDIR([include/HsBase.h]) AC_PREREQ([2.60]) -dnl make extensions visible to allow feature-tests to detect them lateron -AC_USE_SYSTEM_EXTENSIONS - AC_CONFIG_HEADERS([include/HsBaseConfig.h include/EventConfig.h]) AC_CANONICAL_BUILD @@ -18,6 +15,8 @@ AC_ARG_WITH([cc], [C compiler], [CC=$withval]) AC_PROG_CC() +dnl make extensions visible to allow feature-tests to detect them lateron +AC_USE_SYSTEM_EXTENSIONS AC_MSG_CHECKING(for WINDOWS platform) case $host in diff --git a/libraries/integer-gmp/configure.ac b/libraries/integer-gmp/configure.ac index 0bd9188..067217e 100644 --- a/libraries/integer-gmp/configure.ac +++ b/libraries/integer-gmp/configure.ac @@ -10,6 +10,8 @@ AC_ARG_WITH([cc], [C compiler], [CC=$withval]) AC_PROG_CC() +dnl make extensions visible to allow feature-tests to detect them lateron +AC_USE_SYSTEM_EXTENSIONS dnl-------------------------------------------------------------------- From git at git.haskell.org Sun Dec 6 15:38:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 6 Dec 2015 15:38:46 +0000 (UTC) Subject: [commit: ghc] master: Implement new `-fwarn-noncanonical-monoid-instances` (986ceb1) Message-ID: <20151206153846.3279E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/986ceb1679b501414b996c520b08ce929a40f94c/ghc >--------------------------------------------------------------- commit 986ceb1679b501414b996c520b08ce929a40f94c Author: Herbert Valerio Riedel Date: Sun Dec 6 16:08:21 2015 +0100 Implement new `-fwarn-noncanonical-monoid-instances` This is similiar to the `-fwarn-noncanonical-monad-instances` warning implemented via #11128, but applies to `Semigroup`/`Monoid` instead and the `(<>)`/`mappend` methods (of which `mappend` is planned to move out of `Monoid` at some point in the future being redundant and thus error-prone). This warning is contained in `-Wcompat` but not in `-Wall`. This addresses #11150 Reviewed By: quchen Differential Revision: https://phabricator.haskell.org/D1553 >--------------------------------------------------------------- 986ceb1679b501414b996c520b08ce929a40f94c compiler/main/DynFlags.hs | 6 +- compiler/rename/RnSource.hs | 148 +++++++++++++++------ docs/users_guide/using-warnings.rst | 26 +++- .../tests/wcompat-warnings/WCompatWarningsNotOn.hs | 12 ++ .../tests/wcompat-warnings/WCompatWarningsOff.hs | 12 ++ .../tests/wcompat-warnings/WCompatWarningsOn.hs | 12 ++ .../wcompat-warnings/WCompatWarningsOn.stderr | 16 ++- .../tests/wcompat-warnings/WCompatWarningsOnOff.hs | 12 ++ utils/mkUserGuidePart/Options/Warnings.hs | 8 ++ 9 files changed, 205 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 986ceb1679b501414b996c520b08ce929a40f94c From git at git.haskell.org Sun Dec 6 16:37:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 6 Dec 2015 16:37:25 +0000 (UTC) Subject: [commit: ghc] wip/T11168: Tweak use of AC_USE_SYSTEM_EXTENSIONS (45c98da) Message-ID: <20151206163725.379063A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T11168 Link : http://ghc.haskell.org/trac/ghc/changeset/45c98daf98efecf0b28171f5d75c1182c5c12ee0/ghc >--------------------------------------------------------------- commit 45c98daf98efecf0b28171f5d75c1182c5c12ee0 Author: Herbert Valerio Riedel Date: Sun Dec 6 13:34:34 2015 +0100 Tweak use of AC_USE_SYSTEM_EXTENSIONS This is a follow-up to 7af29da05d2e5a5e311a5f73f20d0f232035973b >--------------------------------------------------------------- 45c98daf98efecf0b28171f5d75c1182c5c12ee0 configure.ac | 6 +++--- libraries/base/configure.ac | 5 ++--- libraries/integer-gmp/configure.ac | 2 ++ libraries/unix | 2 +- 4 files changed, 8 insertions(+), 7 deletions(-) diff --git a/configure.ac b/configure.ac index 57d877a..c8708ae 100644 --- a/configure.ac +++ b/configure.ac @@ -58,9 +58,6 @@ dnl #define SIZEOF_CHAR 0 dnl recently. AC_PREREQ([2.60]) -dnl make extensions visible to allow feature-tests to detect them lateron -AC_USE_SYSTEM_EXTENSIONS - # ------------------------------------------------------------------------- # Prepare to generate the following header files # @@ -462,6 +459,9 @@ export CC MAYBE_OVERRIDE_STAGE0([gcc],[CC_STAGE0]) MAYBE_OVERRIDE_STAGE0([ar],[AR_STAGE0]) +dnl make extensions visible to allow feature-tests to detect them lateron +AC_USE_SYSTEM_EXTENSIONS + dnl ** figure out how to invoke the C preprocessor (i.e. `gcc -E`) AC_PROG_CPP diff --git a/libraries/base/configure.ac b/libraries/base/configure.ac index 99474a6..5607213 100644 --- a/libraries/base/configure.ac +++ b/libraries/base/configure.ac @@ -5,9 +5,6 @@ AC_CONFIG_SRCDIR([include/HsBase.h]) AC_PREREQ([2.60]) -dnl make extensions visible to allow feature-tests to detect them lateron -AC_USE_SYSTEM_EXTENSIONS - AC_CONFIG_HEADERS([include/HsBaseConfig.h include/EventConfig.h]) AC_CANONICAL_BUILD @@ -18,6 +15,8 @@ AC_ARG_WITH([cc], [C compiler], [CC=$withval]) AC_PROG_CC() +dnl make extensions visible to allow feature-tests to detect them lateron +AC_USE_SYSTEM_EXTENSIONS AC_MSG_CHECKING(for WINDOWS platform) case $host in diff --git a/libraries/integer-gmp/configure.ac b/libraries/integer-gmp/configure.ac index 0bd9188..067217e 100644 --- a/libraries/integer-gmp/configure.ac +++ b/libraries/integer-gmp/configure.ac @@ -10,6 +10,8 @@ AC_ARG_WITH([cc], [C compiler], [CC=$withval]) AC_PROG_CC() +dnl make extensions visible to allow feature-tests to detect them lateron +AC_USE_SYSTEM_EXTENSIONS dnl-------------------------------------------------------------------- diff --git a/libraries/unix b/libraries/unix index 5740003..147630c 160000 --- a/libraries/unix +++ b/libraries/unix @@ -1 +1 @@ -Subproject commit 5740003e06f0c585460501514f3352f5e105c98c +Subproject commit 147630c7c76bd9b947524ef140d21b9e81967c6e From git at git.haskell.org Sun Dec 6 20:11:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 6 Dec 2015 20:11:17 +0000 (UTC) Subject: [commit: ghc] master: Tweak use of AC_USE_SYSTEM_EXTENSIONS (8b42214) Message-ID: <20151206201117.341FE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8b422142421c751d2c7fa7840afa61f923afdbe1/ghc >--------------------------------------------------------------- commit 8b422142421c751d2c7fa7840afa61f923afdbe1 Author: Herbert Valerio Riedel Date: Sun Dec 6 13:34:34 2015 +0100 Tweak use of AC_USE_SYSTEM_EXTENSIONS This makes sure that `AC_USE_SYSTEM_EXTENSIONS` (which implies `AC_PROG_CC`) is called after the `AC_ARG_WITH([cc],,)` invocation, so that the proper CC setting is in scope. Otherwise this can break cross-compilation. This also needs to pull in a submodule update for `unix` This is a follow-up commit to 7af29da05d2e5a5e311a5f73f20d0f232035973b which hopefully fixes #11168 >--------------------------------------------------------------- 8b422142421c751d2c7fa7840afa61f923afdbe1 configure.ac | 6 +++--- libraries/base/configure.ac | 8 +++----- libraries/integer-gmp/configure.ac | 4 +++- libraries/unix | 2 +- 4 files changed, 10 insertions(+), 10 deletions(-) diff --git a/configure.ac b/configure.ac index 57d877a..c8708ae 100644 --- a/configure.ac +++ b/configure.ac @@ -58,9 +58,6 @@ dnl #define SIZEOF_CHAR 0 dnl recently. AC_PREREQ([2.60]) -dnl make extensions visible to allow feature-tests to detect them lateron -AC_USE_SYSTEM_EXTENSIONS - # ------------------------------------------------------------------------- # Prepare to generate the following header files # @@ -462,6 +459,9 @@ export CC MAYBE_OVERRIDE_STAGE0([gcc],[CC_STAGE0]) MAYBE_OVERRIDE_STAGE0([ar],[AR_STAGE0]) +dnl make extensions visible to allow feature-tests to detect them lateron +AC_USE_SYSTEM_EXTENSIONS + dnl ** figure out how to invoke the C preprocessor (i.e. `gcc -E`) AC_PROG_CPP diff --git a/libraries/base/configure.ac b/libraries/base/configure.ac index 99474a6..3d372d7 100644 --- a/libraries/base/configure.ac +++ b/libraries/base/configure.ac @@ -1,13 +1,9 @@ +AC_PREREQ([2.60]) AC_INIT([Haskell base package], [1.0], [libraries at haskell.org], [base]) # Safety check: Ensure that we are in the correct source directory. AC_CONFIG_SRCDIR([include/HsBase.h]) -AC_PREREQ([2.60]) - -dnl make extensions visible to allow feature-tests to detect them lateron -AC_USE_SYSTEM_EXTENSIONS - AC_CONFIG_HEADERS([include/HsBaseConfig.h include/EventConfig.h]) AC_CANONICAL_BUILD @@ -18,6 +14,8 @@ AC_ARG_WITH([cc], [C compiler], [CC=$withval]) AC_PROG_CC() +dnl make extensions visible to allow feature-tests to detect them lateron +AC_USE_SYSTEM_EXTENSIONS AC_MSG_CHECKING(for WINDOWS platform) case $host in diff --git a/libraries/integer-gmp/configure.ac b/libraries/integer-gmp/configure.ac index 0bd9188..4e3df11 100644 --- a/libraries/integer-gmp/configure.ac +++ b/libraries/integer-gmp/configure.ac @@ -1,5 +1,5 @@ +AC_PREREQ(2.60) AC_INIT([Haskell integer (GMP)], [1.0], [libraries at haskell.org], [integer]) -AC_PREREQ(2.52) # Safety check: Ensure that we are in the correct source directory. AC_CONFIG_SRCDIR([cbits/wrappers.c]) @@ -10,6 +10,8 @@ AC_ARG_WITH([cc], [C compiler], [CC=$withval]) AC_PROG_CC() +dnl make extensions visible to allow feature-tests to detect them lateron +AC_USE_SYSTEM_EXTENSIONS dnl-------------------------------------------------------------------- diff --git a/libraries/unix b/libraries/unix index 5740003..147630c 160000 --- a/libraries/unix +++ b/libraries/unix @@ -1 +1 @@ -Subproject commit 5740003e06f0c585460501514f3352f5e105c98c +Subproject commit 147630c7c76bd9b947524ef140d21b9e81967c6e From git at git.haskell.org Mon Dec 7 07:10:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 7 Dec 2015 07:10:29 +0000 (UTC) Subject: [commit: ghc] master: Update hoopl submodule (be92c28) Message-ID: <20151207071029.A5CF93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/be92c288839e0bfcf0b15e3bb4136d60f8ef2575/ghc >--------------------------------------------------------------- commit be92c288839e0bfcf0b15e3bb4136d60f8ef2575 Author: Jan Stolarek Date: Mon Dec 7 08:08:30 2015 +0100 Update hoopl submodule Hoopl changes required to implement #10982 >--------------------------------------------------------------- be92c288839e0bfcf0b15e3bb4136d60f8ef2575 libraries/hoopl | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/hoopl b/libraries/hoopl index 5405469..b4f4761 160000 --- a/libraries/hoopl +++ b/libraries/hoopl @@ -1 +1 @@ -Subproject commit 5405469b2357580a653ceb41c15c33091b2d1a06 +Subproject commit b4f47611084f9e22aeecb4d49659e900848e157e From git at git.haskell.org Mon Dec 7 11:14:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 7 Dec 2015 11:14:38 +0000 (UTC) Subject: [commit: ghc] master: linters/check-cpp: Don't produce debug log (f5127c8) Message-ID: <20151207111438.2E14D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f5127c81ccb4d65f794b2b43fd3ad9b59c9a89d1/ghc >--------------------------------------------------------------- commit f5127c81ccb4d65f794b2b43fd3ad9b59c9a89d1 Author: Ben Gamari Date: Mon Dec 7 10:53:44 2015 +0100 linters/check-cpp: Don't produce debug log >--------------------------------------------------------------- f5127c81ccb4d65f794b2b43fd3ad9b59c9a89d1 .arc-linters/check-cpp.py | 13 ++++++++----- 1 file changed, 8 insertions(+), 5 deletions(-) diff --git a/.arc-linters/check-cpp.py b/.arc-linters/check-cpp.py index c58da09..1d07b4e 100755 --- a/.arc-linters/check-cpp.py +++ b/.arc-linters/check-cpp.py @@ -9,16 +9,19 @@ import os import json import re - -def setup_logging(): - logger = logging.getLogger() +def setup_logging(logger): + """ + ``arc lint`` makes it quite tricky to catch debug output from linters. + Log to a file to work around this. + """ hdlr = logging.FileHandler('linter.log', 'w') logger.addHandler(hdlr) logger.setLevel(logging.DEBUG) return logger -logger = setup_logging() -#logger.debug(sys.argv) +logger = logging.getLogger() +#setup_logging(logger) +logger.debug(sys.argv) path = sys.argv[1] warnings = [] From git at git.haskell.org Mon Dec 7 11:14:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 7 Dec 2015 11:14:40 +0000 (UTC) Subject: [commit: ghc] master: Documentation: escape characters in template-haskell Haddocks (3ea4fb7) Message-ID: <20151207111440.DF3FA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3ea4fb746a4dbd9248586ed212c7afccb2df3338/ghc >--------------------------------------------------------------- commit 3ea4fb746a4dbd9248586ed212c7afccb2df3338 Author: RyanGlScott Date: Mon Dec 7 11:06:23 2015 +0100 Documentation: escape characters in template-haskell Haddocks Reviewers: hvr, austin, goldfire, bgamari Reviewed By: goldfire, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1578 >--------------------------------------------------------------- 3ea4fb746a4dbd9248586ed212c7afccb2df3338 .../template-haskell/Language/Haskell/TH/Syntax.hs | 20 ++++++++++---------- 1 file changed, 10 insertions(+), 10 deletions(-) diff --git a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs index 4d30a9d..ca6219e 100644 --- a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs +++ b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs @@ -908,7 +908,7 @@ nameBase (Name occ _) = occString occ -- -- ==== __Examples__ -- --- >>> nameModule ''Data.Either.Either" +-- >>> nameModule ''Data.Either.Either -- Just "Data.Either" -- >>> nameModule (mkName "foo") -- Nothing @@ -923,7 +923,7 @@ nameModule _ = Nothing -- -- ==== __Examples__ -- --- >>> namePackage ''Data.Either.Either" +-- >>> namePackage ''Data.Either.Either -- Just "base" -- >>> namePackage (mkName "foo") -- Nothing @@ -1343,10 +1343,10 @@ data Lit = CharL Char -- | Pattern in Haskell given in @{}@ data Pat - = LitP Lit -- ^ @{ 5 or 'c' }@ + = LitP Lit -- ^ @{ 5 or \'c\' }@ | VarP Name -- ^ @{ x }@ | TupP [Pat] -- ^ @{ (p1,p2) }@ - | UnboxedTupP [Pat] -- ^ @{ (# p1,p2 #) }@ + | UnboxedTupP [Pat] -- ^ @{ (\# p1,p2 \#) }@ | ConP Name [Pat] -- ^ @data T1 = C1 t1 t2; {C1 p1 p1} = e@ | InfixP Pat Name Pat -- ^ @foo ({x :+ y}) = e@ | UInfixP Pat Name Pat -- ^ @foo ({x :+ y}) = e@ @@ -1376,7 +1376,7 @@ data Clause = Clause [Pat] Body [Dec] data Exp = VarE Name -- ^ @{ x }@ | ConE Name -- ^ @data T1 = C1 t1 t2; p = {C1} e1 e2 @ - | LitE Lit -- ^ @{ 5 or 'c'}@ + | LitE Lit -- ^ @{ 5 or \'c\'}@ | AppE Exp Exp -- ^ @{ f x }@ | InfixE (Maybe Exp) Exp (Maybe Exp) -- ^ @{x + y} or {(x+)} or {(+ x)} or {(+)}@ @@ -1393,10 +1393,10 @@ data Exp | ParensE Exp -- ^ @{ (e) }@ -- -- See "Language.Haskell.TH.Syntax#infix" - | LamE [Pat] Exp -- ^ @{ \ p1 p2 -> e }@ - | LamCaseE [Match] -- ^ @{ \case m1; m2 }@ + | LamE [Pat] Exp -- ^ @{ \\ p1 p2 -> e }@ + | LamCaseE [Match] -- ^ @{ \\case m1; m2 }@ | TupE [Exp] -- ^ @{ (e1,e2) } @ - | UnboxedTupE [Exp] -- ^ @{ (# e1,e2 #) } @ + | UnboxedTupE [Exp] -- ^ @{ (\# e1,e2 \#) } @ | CondE Exp Exp Exp -- ^ @{ if e1 then e2 else e3 }@ | MultiIfE [(Guard, Exp)] -- ^ @{ if | g1 -> e1 | g2 -> e2 }@ | LetE [Dec] Exp -- ^ @{ let x=e1; y=e2 in e3 }@ @@ -1470,7 +1470,7 @@ data Dec | InfixD Fixity Name -- ^ @{ infix 3 foo }@ -- | pragmas - | PragmaD Pragma -- ^ @{ {\-# INLINE [1] foo #-\} }@ + | PragmaD Pragma -- ^ @{ {\-\# INLINE [1] foo \#-\} }@ -- | data families (may also appear in [Dec] of 'ClassD' and 'InstanceD') | DataFamilyD Name [TyVarBndr] @@ -1590,7 +1590,7 @@ data Type = ForallT [TyVarBndr] Cxt Type -- ^ @forall \. \ -> \@ | EqualityT -- ^ @~@ | ListT -- ^ @[]@ From git at git.haskell.org Mon Dec 7 11:14:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 7 Dec 2015 11:14:43 +0000 (UTC) Subject: [commit: ghc] master: Ignore generated linter.log (42a5469) Message-ID: <20151207111443.882C73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/42a5469e52d84a04df33f516fcb74ffa7ed70359/ghc >--------------------------------------------------------------- commit 42a5469e52d84a04df33f516fcb74ffa7ed70359 Author: RyanGlScott Date: Mon Dec 7 11:14:41 2015 +0100 Ignore generated linter.log Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1577 >--------------------------------------------------------------- 42a5469e52d84a04df33f516fcb74ffa7ed70359 .gitignore | 1 + 1 file changed, 1 insertion(+) diff --git a/.gitignore b/.gitignore index b61ba02..82c81c0 100644 --- a/.gitignore +++ b/.gitignore @@ -133,6 +133,7 @@ _darcs/ /libraries/plus.gif /libraries/synopsis.png /libraries/stamp/ +/linter.log /mk/are-validating.mk /mk/build.mk /mk/config.h From git at git.haskell.org Mon Dec 7 11:14:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 7 Dec 2015 11:14:46 +0000 (UTC) Subject: [commit: ghc] master: ghc-pkg: Restore old behavior in colored version; fixes 6119 (3d55e41) Message-ID: <20151207111446.2A13B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3d55e41e72dc32281744c52afea380c1db577ee1/ghc >--------------------------------------------------------------- commit 3d55e41e72dc32281744c52afea380c1db577ee1 Author: Sibi Prabakaran Date: Mon Dec 7 11:16:15 2015 +0100 ghc-pkg: Restore old behavior in colored version; fixes 6119 The behavior is changed to this: ``` ghc-pkg list blahblah /home/sibi/ghc/inplace/lib/package.conf.d (no packages) ``` instead of: ``` ghc-pkg list blahblah /home/sibi/ghc/inplace/lib/package.conf.d ``` Reviewers: austin, thomie, bgamari Reviewed By: thomie, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1575 GHC Trac Issues: #6119 >--------------------------------------------------------------- 3d55e41e72dc32281744c52afea380c1db577ee1 utils/ghc-pkg/Main.hs | 11 +++++++---- 1 file changed, 7 insertions(+), 4 deletions(-) diff --git a/utils/ghc-pkg/Main.hs b/utils/ghc-pkg/Main.hs index 993aa12..b089e7b 100644 --- a/utils/ghc-pkg/Main.hs +++ b/utils/ghc-pkg/Main.hs @@ -1271,10 +1271,13 @@ listPackages verbosity my_flags mPackageName mModuleName = do mapM_ show_normal stack #else let - show_colour withF db = - mconcat $ map (<#> termText "\n") $ - (termText (location db) : - map (termText " " <#>) (map pp_pkg (packages db))) + show_colour withF db at PackageDB{ packages = pkg_confs } = + if null pkg_confs + then termText (location db) <#> termText "\n (no packages)\n" + else + mconcat $ map (<#> termText "\n") $ + (termText (location db) : + map (termText " " <#>) (map pp_pkg pkg_confs)) where pp_pkg p | installedComponentId p `elem` broken = withF Red doc From git at git.haskell.org Mon Dec 7 11:14:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 7 Dec 2015 11:14:49 +0000 (UTC) Subject: [commit: ghc] master: Re-export data family when exporting a data instance without an export list (8cef8af) Message-ID: <20151207111449.827553A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8cef8af3286f3c98f2a02e65371b875d8791b687/ghc >--------------------------------------------------------------- commit 8cef8af3286f3c98f2a02e65371b875d8791b687 Author: David Kraeutmann Date: Mon Dec 7 11:19:28 2015 +0100 Re-export data family when exporting a data instance without an export list Whenever a data instance is exported, the corresponding data family is exported, too. This allows one to write ``` -- Foo.hs module Foo where data family T a -- Bar.hs module Bar where import Foo data instance T Int = MkT -- Baz.hs module Baz where import Bar (T(MkT)) ``` In previous versions of GHC, this required a workaround explicit export list in `Bar`. Reviewers: bgamari, goldfire, austin Reviewed By: bgamari, goldfire Subscribers: goldfire, thomie Differential Revision: https://phabricator.haskell.org/D1573 GHC Trac Issues: #11164 >--------------------------------------------------------------- 8cef8af3286f3c98f2a02e65371b875d8791b687 compiler/rename/RnNames.hs | 26 +++++++++++++++------- docs/users_guide/7.12.1-notes.rst | 23 +++++++++++++++++++ docs/users_guide/glasgow_exts.rst | 8 +++---- testsuite/tests/ghci/scripts/T5417.stdout | 2 ++ .../tests/indexed-types/should_fail/Over.stderr | 8 +++---- testsuite/tests/rename/should_compile/T11164.hs | 3 +++ testsuite/tests/rename/should_compile/T11164a.hs | 4 ++++ testsuite/tests/rename/should_compile/T11164b.hs | 6 +++++ testsuite/tests/rename/should_compile/all.T | 4 ++++ 9 files changed, 68 insertions(+), 16 deletions(-) diff --git a/compiler/rename/RnNames.hs b/compiler/rename/RnNames.hs index b0b79f5..3ee1e69 100644 --- a/compiler/rename/RnNames.hs +++ b/compiler/rename/RnNames.hs @@ -1200,14 +1200,24 @@ exports_from_avail :: Maybe (Located [LIE RdrName]) -> RnM (Maybe [LIE Name], [AvailInfo]) exports_from_avail Nothing rdr_env _imports _this_mod - = -- The same as (module M) where M is the current module name, - -- so that's how we handle it. - let - avails = [ availFromGRE gre - | gre <- globalRdrEnvElts rdr_env - , isLocalGRE gre ] - in - return (Nothing, avails) + -- The same as (module M) where M is the current module name, + -- so that's how we handle it, except we also export the data family + -- when a data instance is exported. + = let avails = [ fix_faminst $ availFromGRE gre + | gre <- globalRdrEnvElts rdr_env + , isLocalGRE gre ] + in return (Nothing, avails) + where + -- #11164: when we define a data instance + -- but not data family, re-export the family + -- Generally, whenever we export a part of a declaration, + -- export the declaration, too. + fix_faminst (AvailTC n ns flds) + | not (n `elem` ns) + = AvailTC n (n:ns) flds + + fix_faminst avail = avail + exports_from_avail (Just (L _ rdr_items)) rdr_env imports this_mod = do (ie_names, _, exports) <- foldlM do_litem emptyExportAccum rdr_items diff --git a/docs/users_guide/7.12.1-notes.rst b/docs/users_guide/7.12.1-notes.rst index 2e0ae6f..21ec1d3 100644 --- a/docs/users_guide/7.12.1-notes.rst +++ b/docs/users_guide/7.12.1-notes.rst @@ -109,6 +109,29 @@ Language -- P is imported import Foo (T(..)) +- Whenever a data instance is exported, the corresponding data family + is exported, too. This allows one to write :: + + -- Foo.hs + module Foo where + + data family T a + + -- Bar.hs + module Bar where + + import Foo + + data instance T Int = MkT + + -- Baz.hs + module Baz where + + import Bar (T(MkT)) + + In previous versions of GHC, this required a workaround via an + explicit export list in Bar. + Compiler diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index 93261a2..7e448be 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -6702,10 +6702,10 @@ Two things to watch out for: data instance D Int = D1 | D2 Module Y exports all the entities defined in Y, namely the data - constructors ``D1`` and ``D2``, *but not the data family* ``D``. That - (annoyingly) means that you cannot selectively import Y selectively, - thus "``import Y( D(D1,D2) )``", because Y does not export ``D``. - Instead you should list the exports explicitly, thus: + constructors ``D1`` and ``D2``, and *implicitly* the data family ``D``, + even though it's defined in X. + This means you can write "``import Y( D(D1,D2) )``" *without* + giving an explicit export list like this: :: diff --git a/testsuite/tests/ghci/scripts/T5417.stdout b/testsuite/tests/ghci/scripts/T5417.stdout index 06329d9..30178a4 100644 --- a/testsuite/tests/ghci/scripts/T5417.stdout +++ b/testsuite/tests/ghci/scripts/T5417.stdout @@ -3,5 +3,7 @@ data instance C.F (B1 a) = B2 a data family D a class C.C1 a where data family C.F a +class C.C1 a where + data family C.F a -- Defined at T5417a.hs:5:5 data instance C.F (B1 a) = B2 a -- Defined at T5417.hs:8:10 diff --git a/testsuite/tests/indexed-types/should_fail/Over.stderr b/testsuite/tests/indexed-types/should_fail/Over.stderr index 180bb95..63b8b30 100644 --- a/testsuite/tests/indexed-types/should_fail/Over.stderr +++ b/testsuite/tests/indexed-types/should_fail/Over.stderr @@ -1,10 +1,10 @@ -OverB.hs:7:15: +OverB.hs:7:15: error: Conflicting family instance declarations: - OverA.C [Int] [a] = CListList2 -- Defined at OverB.hs:7:15 - OverA.C [a] [Int] = C9ListList -- Defined at OverC.hs:7:15 + C [Int] [a] = CListList2 -- Defined at OverB.hs:7:15 + C [a] [Int] = C9ListList -- Defined at OverC.hs:7:15 -OverB.hs:9:15: +OverB.hs:9:15: error: Conflicting family instance declarations: OverA.D [Int] [a] = Int -- Defined at OverB.hs:9:15 OverA.D [a] [Int] = Char -- Defined at OverC.hs:9:15 diff --git a/testsuite/tests/rename/should_compile/T11164.hs b/testsuite/tests/rename/should_compile/T11164.hs new file mode 100644 index 0000000..b1d9a68 --- /dev/null +++ b/testsuite/tests/rename/should_compile/T11164.hs @@ -0,0 +1,3 @@ +module T11164 where + +import T11164b (T) diff --git a/testsuite/tests/rename/should_compile/T11164a.hs b/testsuite/tests/rename/should_compile/T11164a.hs new file mode 100644 index 0000000..f14e96d --- /dev/null +++ b/testsuite/tests/rename/should_compile/T11164a.hs @@ -0,0 +1,4 @@ +{-# LANGUAGE TypeFamilies #-} +module T11164a where + +data family T a diff --git a/testsuite/tests/rename/should_compile/T11164b.hs b/testsuite/tests/rename/should_compile/T11164b.hs new file mode 100644 index 0000000..abe65c4 --- /dev/null +++ b/testsuite/tests/rename/should_compile/T11164b.hs @@ -0,0 +1,6 @@ +{-# LANGUAGE TypeFamilies #-} +module T11164b where + +import T11164a + +data instance T Int = MkT diff --git a/testsuite/tests/rename/should_compile/all.T b/testsuite/tests/rename/should_compile/all.T index c501ecc..05bc250 100644 --- a/testsuite/tests/rename/should_compile/all.T +++ b/testsuite/tests/rename/should_compile/all.T @@ -226,3 +226,7 @@ test('T7969', test('T9127', normal, compile, ['']) test('T4426', normal, compile_fail, ['']) test('T9778', normal, compile, ['-fwarn-unticked-promoted-constructors']) +test('T11164', + extra_clean(['T11164a.hi', 'T11164a.o', + 'T11164b.hi', 'T11164b.o']), + multimod_compile, ['T11164', '-v0']) From git at git.haskell.org Mon Dec 7 11:14:52 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 7 Dec 2015 11:14:52 +0000 (UTC) Subject: [commit: ghc] master: Minor stylistic fixes in glasgow_exts.rst (91e985c) Message-ID: <20151207111452.3585C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/91e985cd99e9f628e7cd01fc5dd0e6f596337446/ghc >--------------------------------------------------------------- commit 91e985cd99e9f628e7cd01fc5dd0e6f596337446 Author: Ben Gamari Date: Mon Dec 7 11:23:50 2015 +0100 Minor stylistic fixes in glasgow_exts.rst >--------------------------------------------------------------- 91e985cd99e9f628e7cd01fc5dd0e6f596337446 docs/users_guide/glasgow_exts.rst | 25 +++++++++++-------------- 1 file changed, 11 insertions(+), 14 deletions(-) diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index 7e448be..f86d716 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -1721,11 +1721,12 @@ comprehensions are explained in the previous chapters the type ``[a]`` with the type ``Monad m => m a`` for monad comprehensions. -Note: Even though most of these examples are using the list monad, monad -comprehensions work for any monad. The ``base`` package offers all -necessary instances for lists, which make ``MonadComprehensions`` -backward compatible to built-in, transform and parallel list -comprehensions. +.. note:: + Even though most of these examples are using the list monad, monad + comprehensions work for any monad. The ``base`` package offers all + necessary instances for lists, which make ``MonadComprehensions`` + backward compatible to built-in, transform and parallel list + comprehensions. More formally, the desugaring is as follows. We write ``D[ e | Q]`` to mean the desugaring of the monad comprehension ``[ e | Q]``: @@ -6690,9 +6691,7 @@ Two things to watch out for: specifications cannot be nested. To specify ``GMap``\ 's data constructors, you have to list it separately. -- Consider this example: - - :: +- Consider this example: :: module X where data family D @@ -6701,13 +6700,11 @@ Two things to watch out for: import X data instance D Int = D1 | D2 - Module Y exports all the entities defined in Y, namely the data + Module ``Y`` exports all the entities defined in ``Y``, namely the data constructors ``D1`` and ``D2``, and *implicitly* the data family ``D``, - even though it's defined in X. - This means you can write "``import Y( D(D1,D2) )``" *without* - giving an explicit export list like this: - - :: + even though it's defined in ``X``. + This means you can write ``import Y( D(D1,D2) )`` *without* + giving an explicit export list like this: :: module Y( D(..) ) where ... or module Y( module Y, D ) where ... From git at git.haskell.org Mon Dec 7 11:14:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 7 Dec 2015 11:14:55 +0000 (UTC) Subject: [commit: ghc] master: Add isImport, isDecl, and isStmt functions to GHC API (2110037) Message-ID: <20151207111455.69F683A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2110037e270c5ea36de63e4d95a3175751338571/ghc >--------------------------------------------------------------- commit 2110037e270c5ea36de63e4d95a3175751338571 Author: Roman Shatsov Date: Mon Dec 7 11:24:36 2015 +0100 Add isImport, isDecl, and isStmt functions to GHC API Reviewers: austin, thomie, bgamari Reviewed By: thomie, bgamari Subscribers: mpickering, thomie Differential Revision: https://phabricator.haskell.org/D1518 GHC Trac Issues: #9015 >--------------------------------------------------------------- 2110037e270c5ea36de63e4d95a3175751338571 compiler/main/GHC.hs | 1 + compiler/main/InteractiveEval.hs | 37 ++++++++++++++++ docs/users_guide/7.12.1-notes.rst | 2 + ghc/GhciMonad.hs | 19 +------- ghc/InteractiveUI.hs | 33 +++++--------- testsuite/.gitignore | 1 + testsuite/tests/ghc-api/Makefile | 7 ++- testsuite/tests/ghc-api/T9015.hs | 59 +++++++++++++++++++++++++ testsuite/tests/ghc-api/T9015.stdout | 86 ++++++++++++++++++++++++++++++++++++ testsuite/tests/ghc-api/all.T | 3 ++ 10 files changed, 207 insertions(+), 41 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 2110037e270c5ea36de63e4d95a3175751338571 From git at git.haskell.org Mon Dec 7 11:14:58 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 7 Dec 2015 11:14:58 +0000 (UTC) Subject: [commit: ghc] master: rts: Remove space before argument list in ASSERTs (d4bcd05) Message-ID: <20151207111458.1F4ED3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d4bcd05d7df3138429abdf43d3e3eb8f6da2dcdf/ghc >--------------------------------------------------------------- commit d4bcd05d7df3138429abdf43d3e3eb8f6da2dcdf Author: Ben Gamari Date: Mon Dec 7 11:33:06 2015 +0100 rts: Remove space before argument list in ASSERTs Test Plan: Validate Reviewers: austin, erikd Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1569 >--------------------------------------------------------------- d4bcd05d7df3138429abdf43d3e3eb8f6da2dcdf rts/Linker.c | 2 +- rts/STM.c | 96 ++++++++++++++++++++++++++++++------------------------------ 2 files changed, 49 insertions(+), 49 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d4bcd05d7df3138429abdf43d3e3eb8f6da2dcdf From git at git.haskell.org Mon Dec 7 12:10:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 7 Dec 2015 12:10:11 +0000 (UTC) Subject: [commit: ghc] master: Use TypeLits in the meta-data encoding of GHC.Generics (700c42b) Message-ID: <20151207121011.F25C23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/700c42b5e0ffd27884e6bdfa9a940e55449cff6f/ghc >--------------------------------------------------------------- commit 700c42b5e0ffd27884e6bdfa9a940e55449cff6f Author: RyanGlScott Date: Mon Dec 7 12:37:50 2015 +0100 Use TypeLits in the meta-data encoding of GHC.Generics Test Plan: Validate. Reviewers: simonpj, goldfire, hvr, dreixel, kosmikus, austin, bgamari Reviewed By: kosmikus, austin, bgamari Subscribers: RyanGlScott, Fuuzetsu, bgamari, thomie, carter, dreixel Differential Revision: https://phabricator.haskell.org/D493 GHC Trac Issues: #9766 >--------------------------------------------------------------- 700c42b5e0ffd27884e6bdfa9a940e55449cff6f compiler/prelude/PrelNames.hs | 59 +- compiler/typecheck/TcDeriv.hs | 76 +- compiler/typecheck/TcGenDeriv.hs | 18 +- compiler/typecheck/TcGenGenerics.hs | 309 ++--- docs/users_guide/glasgow_exts.rst | 31 +- libraries/base/GHC/Generics.hs | 364 +++--- libraries/base/changelog.md | 3 + testsuite/tests/generics/GShow/GShow.hs | 4 +- testsuite/tests/generics/GenDerivOutput.stderr | 211 ++-- testsuite/tests/generics/GenDerivOutput1_0.stderr | 58 +- testsuite/tests/generics/GenDerivOutput1_1.stderr | 290 ++--- .../should_run/overloadedrecflds_generics.hs | 7 +- testsuite/tests/perf/compiler/T5642.hs | 1301 +++++++++----------- testsuite/tests/perf/compiler/all.T | 3 +- 14 files changed, 1198 insertions(+), 1536 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 700c42b5e0ffd27884e6bdfa9a940e55449cff6f From git at git.haskell.org Mon Dec 7 12:10:14 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 7 Dec 2015 12:10:14 +0000 (UTC) Subject: [commit: ghc] master: Refactor ConDecl (51a5e68) Message-ID: <20151207121014.B9F353A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/51a5e68db887adb3565ff2f077267e2b513be562/ghc >--------------------------------------------------------------- commit 51a5e68db887adb3565ff2f077267e2b513be562 Author: Alan Zimmerman Date: Mon Dec 7 12:40:38 2015 +0100 Refactor ConDecl The ConDecl type in HsDecls is an uneasy compromise. For the most part, HsSyn directly reflects the syntax written by the programmer; and that gives just the right "pegs" on which to hang Alan's API annotations. But ConDecl doesn't properly reflect the syntax of Haskell-98 and GADT-style data type declarations. To be concrete, here's a draft new data type ```lang=hs data ConDecl name | ConDeclGADT { con_names :: [Located name] , con_type :: LHsSigType name -- The type after the ?::? , con_doc :: Maybe LHsDocString } | ConDeclH98 { con_name :: Located name , con_qvars :: Maybe (LHsQTyVars name) -- User-written forall (if any), and its implicit -- kind variables -- Non-Nothing needs -XExistentialQuantification , con_cxt :: Maybe (LHsContext name) -- ^ User-written context (if any) , con_details :: HsConDeclDetails name -- ^ Arguments , con_doc :: Maybe LHsDocString -- ^ A possible Haddock comment. } deriving (Typeable) ``` Note that For GADTs, just keep a type. That's what the user writes. NB:HsType can represent records on the LHS of an arrow: { x:Int,y:Bool} -> T con_qvars and con_cxt are both Maybe because they are both optional (the forall and the context of an existential data type For ConDeclGADT the type variables of the data type do not scope over the con_type; whereas for ConDeclH98 they do scope over con_cxt and con_details. Updates haddock submodule. Test Plan: ./validate Reviewers: simonpj, erikd, hvr, goldfire, austin, bgamari Subscribers: erikd, goldfire, thomie, mpickering Differential Revision: https://phabricator.haskell.org/D1558 GHC Trac Issues: #11028 >--------------------------------------------------------------- 51a5e68db887adb3565ff2f077267e2b513be562 compiler/deSugar/DsMeta.hs | 98 ++++++++--- compiler/hsSyn/Convert.hs | 22 ++- compiler/hsSyn/HsDecls.hs | 152 +++++++--------- compiler/hsSyn/HsLit.hs | 1 - compiler/hsSyn/HsTypes.hs | 4 +- compiler/hsSyn/HsUtils.hs | 26 ++- compiler/parser/Parser.y | 12 +- compiler/parser/RdrHsSyn.hs | 73 +++----- compiler/rename/RnEnv.hs | 4 +- compiler/rename/RnNames.hs | 13 +- compiler/rename/RnSource.hs | 120 +++++-------- compiler/rename/RnTypes.hs | 22 ++- compiler/typecheck/TcHsType.hs | 9 +- compiler/typecheck/TcRnDriver.hs | 2 +- compiler/typecheck/TcTyClsDecls.hs | 193 +++++++++++++++------ testsuite/tests/ghc-api/annotations/T10399.stdout | 2 - testsuite/tests/ghc-api/annotations/all.T | 2 +- testsuite/tests/ghc-api/landmines/landmines.stdout | 2 +- testsuite/tests/rename/should_compile/T5331.stderr | 2 +- testsuite/tests/rename/should_fail/T7943.stderr | 6 +- utils/haddock | 2 +- 21 files changed, 427 insertions(+), 340 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 51a5e68db887adb3565ff2f077267e2b513be562 From git at git.haskell.org Mon Dec 7 12:10:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 7 Dec 2015 12:10:18 +0000 (UTC) Subject: [commit: ghc] master: Move checking for missing signatures to RnNames.reportUnusedNames (1bd40c8) Message-ID: <20151207121018.219B23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1bd40c860eb0e8da55b8eff536766a6c802347cc/ghc >--------------------------------------------------------------- commit 1bd40c860eb0e8da55b8eff536766a6c802347cc Author: Eric Seidel Date: Mon Dec 7 12:42:38 2015 +0100 Move checking for missing signatures to RnNames.reportUnusedNames Checking for missing signatures before renaming the export list is prone to errors, so we now perform the check in `reportUnusedNames` at which point everything has been renamed. Test Plan: validate, new test case is T10908 Reviewers: goldfire, simonpj, austin, bgamari Subscribers: thomie Projects: #ghc Differential Revision: https://phabricator.haskell.org/D1561 GHC Trac Issues: #10908 >--------------------------------------------------------------- 1bd40c860eb0e8da55b8eff536766a6c802347cc compiler/rename/RnNames.hs | 63 +++++++++- compiler/typecheck/TcBinds.hs | 24 +++- compiler/typecheck/TcHsSyn.hs | 141 +++++----------------- compiler/typecheck/TcRnDriver.hs | 10 +- testsuite/tests/warnings/should_compile/T10908.hs | 10 ++ testsuite/tests/warnings/should_compile/all.T | 1 + 6 files changed, 130 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 1bd40c860eb0e8da55b8eff536766a6c802347cc From git at git.haskell.org Mon Dec 7 13:07:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 7 Dec 2015 13:07:30 +0000 (UTC) Subject: [commit: ghc] master: ghc-pkg: don't sort packages unnecessarily (151c4b0) Message-ID: <20151207130730.035D23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/151c4b0b6caff2e1af764699c54302933c628861/ghc >--------------------------------------------------------------- commit 151c4b0b6caff2e1af764699c54302933c628861 Author: Thomas Miedema Date: Mon Dec 7 13:22:03 2015 +0100 ghc-pkg: don't sort packages unnecessarily The packages in the package database are already sorted alphabetically by this point (see db_stack_sorted). This is a better fix for #8245, commit 021b1f8. Test Plan: look at output of './inplace/bin/ghc-pkg list [--simple-output]' Reviewers: austin, bgamari, psibi Reviewed By: psibi Differential Revision: https://phabricator.haskell.org/D1579 GHC Trac Issues: #8245 >--------------------------------------------------------------- 151c4b0b6caff2e1af764699c54302933c628861 utils/ghc-pkg/Main.hs | 10 +++------- 1 file changed, 3 insertions(+), 7 deletions(-) diff --git a/utils/ghc-pkg/Main.hs b/utils/ghc-pkg/Main.hs index b089e7b..2820f70 100644 --- a/utils/ghc-pkg/Main.hs +++ b/utils/ghc-pkg/Main.hs @@ -36,7 +36,6 @@ import qualified Control.Exception as Exception import Data.Maybe import Data.Char ( isSpace, toLower ) -import Data.Ord (comparing) #if __GLASGOW_HASKELL__ < 709 import Control.Applicative (Applicative(..)) #endif @@ -1243,12 +1242,10 @@ listPackages verbosity my_flags mPackageName mModuleName = do show_normal PackageDB{ location = db_name, packages = pkg_confs } = do hPutStrLn stdout (db_name ++ ":") - if null pp_pkgs + if null pkg_confs then hPutStrLn stdout " (no packages)" - else hPutStrLn stdout $ unlines (map (" " ++) pp_pkgs) + else hPutStrLn stdout $ unlines (map (" " ++) (map pp_pkg pkg_confs)) where - -- Sort using instance Ord PackageId - pp_pkgs = map pp_pkg . sortBy (comparing installedComponentId) $ pkg_confs pp_pkg p | installedComponentId p `elem` broken = printf "{%s}" doc | exposed p = doc @@ -1305,8 +1302,7 @@ simplePackageList :: [Flag] -> [InstalledPackageInfo] -> IO () simplePackageList my_flags pkgs = do let showPkg = if FlagNamesOnly `elem` my_flags then display . pkgName else display - -- Sort using instance Ord PackageId - strs = map showPkg $ sort $ map sourcePackageId pkgs + strs = map showPkg $ map sourcePackageId pkgs when (not (null pkgs)) $ hPutStrLn stdout $ concat $ intersperse " " strs From git at git.haskell.org Mon Dec 7 13:08:12 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 7 Dec 2015 13:08:12 +0000 (UTC) Subject: [commit: ghc] master: rts: One more Clang-unfriendly CPP usage (04e1c27) Message-ID: <20151207130812.20C853A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/04e1c27943503f2e12b009b91f7bef195766f6d0/ghc >--------------------------------------------------------------- commit 04e1c27943503f2e12b009b91f7bef195766f6d0 Author: Ben Gamari Date: Mon Dec 7 14:08:28 2015 +0100 rts: One more Clang-unfriendly CPP usage >--------------------------------------------------------------- 04e1c27943503f2e12b009b91f7bef195766f6d0 rts/sm/BlockAlloc.c | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/rts/sm/BlockAlloc.c b/rts/sm/BlockAlloc.c index e721fb1..a633726 100644 --- a/rts/sm/BlockAlloc.c +++ b/rts/sm/BlockAlloc.c @@ -835,9 +835,9 @@ checkFreeListSanity(void) // make sure we're fully coalesced if (bd->link != NULL) { - ASSERT (MBLOCK_ROUND_DOWN(bd->link) != - (StgWord8*)MBLOCK_ROUND_DOWN(bd) + - BLOCKS_TO_MBLOCKS(bd->blocks) * MBLOCK_SIZE); + ASSERT(MBLOCK_ROUND_DOWN(bd->link) != + (StgWord8*)MBLOCK_ROUND_DOWN(bd) + + BLOCKS_TO_MBLOCKS(bd->blocks) * MBLOCK_SIZE); } } } From git at git.haskell.org Mon Dec 7 16:34:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 7 Dec 2015 16:34:13 +0000 (UTC) Subject: [commit: ghc] master: Re-use `transformers`'s `MaybeT` rather than our own (0933331) Message-ID: <20151207163413.6CAA13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/09333313f32be975faf9158fcd3648489d78ad82/ghc >--------------------------------------------------------------- commit 09333313f32be975faf9158fcd3648489d78ad82 Author: Herbert Valerio Riedel Date: Mon Dec 7 17:32:23 2015 +0100 Re-use `transformers`'s `MaybeT` rather than our own The now removed `MaybeT` type was originally added back in 2008 via bc845b714132a897032502536fea8cd018ce325b Reviewed By: bgamari Differential Revision: https://phabricator.haskell.org/D1583 >--------------------------------------------------------------- 09333313f32be975faf9158fcd3648489d78ad82 compiler/utils/Maybes.hs | 60 ++++-------------------------------------------- 1 file changed, 4 insertions(+), 56 deletions(-) diff --git a/compiler/utils/Maybes.hs b/compiler/utils/Maybes.hs index 656f40a..ac51070 100644 --- a/compiler/utils/Maybes.hs +++ b/compiler/utils/Maybes.hs @@ -3,7 +3,6 @@ (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 -} -{-# LANGUAGE CPP #-} module Maybes ( module Data.Maybe, @@ -18,11 +17,9 @@ module Maybes ( MaybeT(..), liftMaybeT ) where -import Control.Applicative +import Control.Applicative as A import Control.Monad -#if __GLASGOW_HASKELL__ > 710 -import Control.Monad.Fail -#endif +import Control.Monad.Trans.Maybe import Data.Maybe infixr 4 `orElse` @@ -64,56 +61,7 @@ orElse = flip fromMaybe ************************************************************************ -} -newtype MaybeT m a = MaybeT {runMaybeT :: m (Maybe a)} - -instance Functor m => Functor (MaybeT m) where - fmap f x = MaybeT $ fmap (fmap f) $ runMaybeT x - -#if __GLASGOW_HASKELL__ < 710 --- Pre-AMP change -instance (Monad m, Applicative m) => Applicative (MaybeT m) where -#else -instance (Monad m) => Applicative (MaybeT m) where -#endif - pure = MaybeT . pure . Just - (<*>) = ap - -#if __GLASGOW_HASKELL__ < 710 --- Pre-AMP change -instance (Monad m, Applicative m) => Monad (MaybeT m) where -#else -instance (Monad m) => Monad (MaybeT m) where -#endif - return = pure - x >>= f = MaybeT $ runMaybeT x >>= maybe (pure Nothing) (runMaybeT . f) - fail _ = MaybeT $ pure Nothing - - -#if __GLASGOW_HASKELL__ > 710 -instance Monad m => MonadFail (MaybeT m) where - fail _ = MaybeT $ return Nothing -#endif - -#if __GLASGOW_HASKELL__ < 710 --- Pre-AMP change -instance (Monad m, Applicative m) => Alternative (MaybeT m) where -#else -instance (Monad m) => Alternative (MaybeT m) where -#endif - empty = mzero - (<|>) = mplus - -#if __GLASGOW_HASKELL__ < 710 --- Pre-AMP change -instance (Monad m, Applicative m) => MonadPlus (MaybeT m) where -#else -instance Monad m => MonadPlus (MaybeT m) where -#endif - mzero = MaybeT $ pure Nothing - p `mplus` q = MaybeT $ do ma <- runMaybeT p - case ma of - Just a -> pure (Just a) - Nothing -> runMaybeT q +-- We had our own MaybeT in the past. Now we reuse transformer's MaybeT liftMaybeT :: Monad m => m a -> MaybeT m a liftMaybeT act = MaybeT $ Just `liftM` act @@ -136,7 +84,7 @@ instance Applicative (MaybeErr err) where (<*>) = ap instance Monad (MaybeErr err) where - return = pure + return = A.pure Succeeded v >>= k = k v Failed e >>= _ = Failed e From git at git.haskell.org Mon Dec 7 21:52:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 7 Dec 2015 21:52:31 +0000 (UTC) Subject: [commit: ghc] master: Remove redundant CPP conditionals (b292720) Message-ID: <20151207215231.623943A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b292720c0635fc934424efead8c8f77168e8eac3/ghc >--------------------------------------------------------------- commit b292720c0635fc934424efead8c8f77168e8eac3 Author: Herbert Valerio Riedel Date: Mon Dec 7 22:50:44 2015 +0100 Remove redundant CPP conditionals It makes little sense to have __GLASGOW_HASKELL__ conditional code inside GHCi's source-code, as GHCi is only ever build by the current stage1 GHC, whose version is assumed to be the same as the GHCi version being built. >--------------------------------------------------------------- b292720c0635fc934424efead8c8f77168e8eac3 ghc/GhciMonad.hs | 4 ---- ghc/InteractiveUI.hs | 5 ----- 2 files changed, 9 deletions(-) diff --git a/ghc/GhciMonad.hs b/ghc/GhciMonad.hs index 7dd005b..28c5657 100644 --- a/ghc/GhciMonad.hs +++ b/ghc/GhciMonad.hs @@ -55,10 +55,6 @@ import qualified System.Console.Haskeline as Haskeline import Control.Monad.Trans.Class import Control.Monad.IO.Class -#if __GLASGOW_HASKELL__ < 709 -import Control.Applicative (Applicative(..)) -#endif - ----------------------------------------------------------------------------- -- GHCi monad diff --git a/ghc/InteractiveUI.hs b/ghc/InteractiveUI.hs index f7b3603..24e3c99 100644 --- a/ghc/InteractiveUI.hs +++ b/ghc/InteractiveUI.hs @@ -82,12 +82,7 @@ import Data.List ( find, group, intercalate, intersperse, isPrefixOf, nub, import Data.Maybe import Exception hiding (catch) - -#if __GLASGOW_HASKELL__ >= 709 import Foreign -#else -import Foreign.Safe -#endif import System.Directory import System.Environment From git at git.haskell.org Mon Dec 7 22:16:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 7 Dec 2015 22:16:26 +0000 (UTC) Subject: [commit: ghc] master: Get rid of tcView altogether (834f9a4) Message-ID: <20151207221626.BB0E53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/834f9a46a7493e88c41ac01210bc3fcde7a2c0f9/ghc >--------------------------------------------------------------- commit 834f9a46a7493e88c41ac01210bc3fcde7a2c0f9 Author: ?mer Sinan A?acan Date: Mon Dec 7 11:41:51 2015 -0500 Get rid of tcView altogether This is just a trivial renaming that implements a ToDo mentioned in a comment in Type.hs. Adding Simon as reviewer since he added the ToDo comment. Reviewers: simonpj, austin, goldfire, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1584 >--------------------------------------------------------------- 834f9a46a7493e88c41ac01210bc3fcde7a2c0f9 compiler/typecheck/FamInst.hs | 2 +- compiler/typecheck/TcCanonical.hs | 12 ++++----- compiler/typecheck/TcErrors.hs | 12 ++++----- compiler/typecheck/TcType.hs | 53 +++++++++++++++++++-------------------- compiler/typecheck/TcUnify.hs | 14 +++++------ compiler/typecheck/TcValidity.hs | 4 +-- compiler/types/Type.hs | 18 +++---------- compiler/types/Unify.hs | 12 ++++----- 8 files changed, 58 insertions(+), 69 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 834f9a46a7493e88c41ac01210bc3fcde7a2c0f9 From git at git.haskell.org Tue Dec 8 08:16:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 8 Dec 2015 08:16:54 +0000 (UTC) Subject: [commit: ghc] master: Introduce HasGhciState class and refactor use-sites (2f6e87a) Message-ID: <20151208081654.089293A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2f6e87a494330837c425dab67ba26ee36bd9eacf/ghc >--------------------------------------------------------------- commit 2f6e87a494330837c425dab67ba26ee36bd9eacf Author: Herbert Valerio Riedel Date: Tue Dec 8 08:48:21 2015 +0100 Introduce HasGhciState class and refactor use-sites This allows to reach the GhciState without having to keep track how many Monad transformer layers sit on top of the GHCi monad. While at it, this also refactors code to make more use of the existing `modifyGHCiState` operation. This is a preparatory refactoring for #10874 Differential Revision: https://phabricator.haskell.org/D1582 >--------------------------------------------------------------- 2f6e87a494330837c425dab67ba26ee36bd9eacf ghc/GhciMonad.hs | 20 ++++++++++++----- ghc/InteractiveUI.hs | 63 +++++++++++++++++++++------------------------------- 2 files changed, 39 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 2f6e87a494330837c425dab67ba26ee36bd9eacf From git at git.haskell.org Tue Dec 8 09:17:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 8 Dec 2015 09:17:44 +0000 (UTC) Subject: [commit: libffi-tarballs] branch 'libffi-3.1' created Message-ID: <20151208091744.08BEA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/libffi-tarballs New branch : libffi-3.1 Referencing: b6658e5d73eb0579b3054593de21f329ab491e77 From git at git.haskell.org Tue Dec 8 09:25:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 8 Dec 2015 09:25:11 +0000 (UTC) Subject: [commit: libffi-tarballs] branch 'libffi-3.2.1' created Message-ID: <20151208092511.B27553A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/libffi-tarballs New branch : libffi-3.2.1 Referencing: ec37a68838566cb830c33cb30bfade003a306cff From git at git.haskell.org Tue Dec 8 09:25:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 8 Dec 2015 09:25:13 +0000 (UTC) Subject: [commit: libffi-tarballs] libffi-3.2.1: libffi 3.2.1 was released on November 12, 2014. (ec37a68) Message-ID: <20151208092513.B89FF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/libffi-tarballs On branch : libffi-3.2.1 Link : http://git.haskell.org/libffi-tarballs.git/commitdiff/ec37a68838566cb830c33cb30bfade003a306cff >--------------------------------------------------------------- commit ec37a68838566cb830c33cb30bfade003a306cff Author: Herbert Valerio Riedel Date: Tue Dec 8 10:23:14 2015 +0100 libffi 3.2.1 was released on November 12, 2014. The libffi-3.2.1.tar.gz tarball was retrieved from ftp://sourceware.org/pub/libffi/libffi-3.2.1.tar.gz and has the following checksums md5sum 83b89587607e3eb65c70d361f13bab43 sha1sum 280c265b789e041c02e5c97815793dfc283fb1e6 sha256sum d06ebb8e1d9a22d19e38d63fdb83954253f39bedc5d46232a05645685722ca37 >--------------------------------------------------------------- ec37a68838566cb830c33cb30bfade003a306cff LICENSE | 21 +++++++++++++++++++++ README | 4 ++++ libffi-3.2.1.tar.gz | Bin 0 -> 940837 bytes 3 files changed, 25 insertions(+) diff --git a/LICENSE b/LICENSE new file mode 100644 index 0000000..a66fab4 --- /dev/null +++ b/LICENSE @@ -0,0 +1,21 @@ +libffi - Copyright (c) 1996-2014 Anthony Green, Red Hat, Inc and others. +See source files for details. + +Permission is hereby granted, free of charge, to any person obtaining +a copy of this software and associated documentation files (the +``Software''), to deal in the Software without restriction, including +without limitation the rights to use, copy, modify, merge, publish, +distribute, sublicense, and/or sell copies of the Software, and to +permit persons to whom the Software is furnished to do so, subject to +the following conditions: + +The above copyright notice and this permission notice shall be +included in all copies or substantial portions of the Software. + +THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, +EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF +MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. +IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY +CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, +TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE +SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. diff --git a/README b/README new file mode 100644 index 0000000..042415a --- /dev/null +++ b/README @@ -0,0 +1,4 @@ + +Tarballs come from: + http://sourceware.org/libffi/ + diff --git a/libffi-3.2.1.tar.gz b/libffi-3.2.1.tar.gz new file mode 100644 index 0000000..5c21bb0 Binary files /dev/null and b/libffi-3.2.1.tar.gz differ From git at git.haskell.org Tue Dec 8 10:10:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 8 Dec 2015 10:10:00 +0000 (UTC) Subject: [commit: ghc] master: Associate ErrorCall pattern with ErrorCall type (9f4ca5a) Message-ID: <20151208101000.A87DB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9f4ca5afaccc8a397d8ee91b5423a9c2fcd151ce/ghc >--------------------------------------------------------------- commit 9f4ca5afaccc8a397d8ee91b5423a9c2fcd151ce Author: Herbert Valerio Riedel Date: Tue Dec 8 11:09:48 2015 +0100 Associate ErrorCall pattern with ErrorCall type This way, import Control.Exception (ErrorCall(ErrorCall)) or import Control.Exception (ErrorCall(..)) work as expected, and import the `ErrorCall` compatibility pattern as well. When #5273 was implemented, it wasn't possible yet to associated patterns with their types (see #10653). Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D1588 >--------------------------------------------------------------- 9f4ca5afaccc8a397d8ee91b5423a9c2fcd151ce libraries/base/Control/Exception.hs | 3 +-- libraries/base/Control/Exception/Base.hs | 3 +-- libraries/base/GHC/Exception.hs | 2 +- 3 files changed, 3 insertions(+), 5 deletions(-) diff --git a/libraries/base/Control/Exception.hs b/libraries/base/Control/Exception.hs index 1383972..9c388f4 100644 --- a/libraries/base/Control/Exception.hs +++ b/libraries/base/Control/Exception.hs @@ -1,5 +1,5 @@ {-# LANGUAGE Trustworthy #-} -{-# LANGUAGE NoImplicitPrelude, ExistentialQuantification, PatternSynonyms #-} +{-# LANGUAGE NoImplicitPrelude, ExistentialQuantification #-} ----------------------------------------------------------------------------- -- | @@ -56,7 +56,6 @@ module Control.Exception ( RecSelError(..), RecUpdError(..), ErrorCall(..), - pattern ErrorCall, TypeError(..), -- * Throwing exceptions diff --git a/libraries/base/Control/Exception/Base.hs b/libraries/base/Control/Exception/Base.hs index ba2502f..ece5c69 100644 --- a/libraries/base/Control/Exception/Base.hs +++ b/libraries/base/Control/Exception/Base.hs @@ -1,6 +1,5 @@ {-# LANGUAGE Trustworthy #-} {-# LANGUAGE NoImplicitPrelude, MagicHash #-} -{-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE StandaloneDeriving #-} ----------------------------------------------------------------------------- @@ -39,7 +38,7 @@ module Control.Exception.Base ( RecConError(..), RecSelError(..), RecUpdError(..), - ErrorCall(..), pattern ErrorCall, + ErrorCall(..), TypeError(..), -- #10284, custom error type for deferred type errors -- * Throwing exceptions diff --git a/libraries/base/GHC/Exception.hs b/libraries/base/GHC/Exception.hs index c31a203..e4925c7 100644 --- a/libraries/base/GHC/Exception.hs +++ b/libraries/base/GHC/Exception.hs @@ -24,7 +24,7 @@ module GHC.Exception ( Exception(..) -- Class , throw - , SomeException(..), ErrorCall(..), pattern ErrorCall, ArithException(..) + , SomeException(..), ErrorCall(..,ErrorCall), ArithException(..) , divZeroException, overflowException, ratioZeroDenomException , errorCallException, errorCallWithCallStackException , showCallStack, popCallStack, showSrcLoc From git at git.haskell.org Tue Dec 8 10:16:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 8 Dec 2015 10:16:23 +0000 (UTC) Subject: [commit: ghc] master: Make HasDynFlags more transformers friendly (fd3b845) Message-ID: <20151208101623.2C78B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fd3b845c01aa26b6e5cd12c00af59e5468e21b1b/ghc >--------------------------------------------------------------- commit fd3b845c01aa26b6e5cd12c00af59e5468e21b1b Author: Herbert Valerio Riedel Date: Tue Dec 8 11:11:11 2015 +0100 Make HasDynFlags more transformers friendly Ideally, we'd have the more general instance (MonadTrans t, Monad m, HasDynFlags m) => HasDynFlags (t m) where getDynFlags = lift getDynFlags definition. However, that one would overlap with the `HasDynFlags (GhcT m)` instance. Instead we define instances for a couple of common Monad transformers explicitly in order to avoid nasty overlapping instances. This is a preparatory refactoring for #10874 Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D1581 >--------------------------------------------------------------- fd3b845c01aa26b6e5cd12c00af59e5468e21b1b compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 10 +++++----- compiler/main/DynFlags.hs | 35 +++++++++++++++++++++++++++++++++ compiler/main/GhcMonad.hs | 10 +++------- ghc/InteractiveUI.hs | 2 +- 4 files changed, 44 insertions(+), 13 deletions(-) diff --git a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs index 539e222..0aec7ad 100644 --- a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs +++ b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs @@ -275,7 +275,7 @@ genCall (PrimTarget (MO_AtomicWrite _width)) [] [addr, val] = runStmtsDecls $ do -- some extra parameters. genCall t@(PrimTarget op) [] args | Just align <- machOpMemcpyishAlign op = runStmtsDecls $ do - dflags <- lift $ getDynFlags + dflags <- getDynFlags let isVolTy = [i1] isVolVal = [mkIntLit i1 0] argTy | MO_Memset _ <- op = [i8Ptr, i8, llvmWord dflags, i32] ++ isVolTy @@ -377,7 +377,7 @@ genCall t@(PrimTarget (MO_SubWordC w)) [dstV, dstO] [lhs, rhs] = -- Handle all other foreign calls and prim ops. genCall target res args = runStmtsDecls $ do - dflags <- lift $ getDynFlags + dflags <- getDynFlags -- parameter types let arg_type (_, AddrHint) = i8Ptr @@ -1378,7 +1378,7 @@ genMachOp_slow opt op [x, y] = case op of else do -- Error. Continue anyway so we can debug the generated ll file. - dflags <- lift getDynFlags + dflags <- getDynFlags let style = mkCodeStyle CStyle toString doc = renderWithStyle dflags doc style cmmToStr = (lines . toString . PprCmm.pprExpr) @@ -1422,7 +1422,7 @@ genMachOp_slow opt op [x, y] = case op of vx <- exprToVarW x vy <- exprToVarW y - dflags <- lift getDynFlags + dflags <- getDynFlags let word = getVarType vx let word2 = LMInt $ 2 * (llvmWidthInBits dflags $ getVarType vx) let shift = llvmWidthInBits dflags word @@ -1522,7 +1522,7 @@ genLoad_fast atomic e r n ty = do genLoad_slow :: Atomic -> CmmExpr -> CmmType -> [MetaAnnot] -> LlvmM ExprData genLoad_slow atomic e ty meta = runExprData $ do iptr <- exprToVarW e - dflags <- lift getDynFlags + dflags <- getDynFlags case getVarType iptr of LMPointer _ -> do doExprW (cmmToLlvmType ty) (MExpr meta $ loadInstr iptr) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 3d99a1a..c492a01 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -1,4 +1,5 @@ {-# LANGUAGE CPP #-} +{-# LANGUAGE FlexibleInstances #-} ------------------------------------------------------------------------------- -- @@ -176,6 +177,13 @@ import System.IO.Unsafe ( unsafePerformIO ) import Data.IORef import Control.Arrow ((&&&)) import Control.Monad +import Control.Monad.Trans.Class +import Control.Monad.Trans.Writer +import Control.Monad.Trans.Reader +import qualified Control.Monad.Trans.Maybe as CMT +#if MIN_VERSION_transformers(4,0,0) +import Control.Monad.Trans.Except +#endif import Control.Exception (throwIO) import Data.Bits @@ -186,6 +194,7 @@ import Data.Map (Map) import qualified Data.Map as Map import Data.Set (Set) import qualified Data.Set as Set +import Data.Monoid (Monoid) import Data.Word import System.FilePath import System.Directory @@ -912,6 +921,32 @@ data DynFlags = DynFlags { class HasDynFlags m where getDynFlags :: m DynFlags +{- It would be desirable to have the more generalised + + instance (MonadTrans t, Monad m, HasDynFlags m) => HasDynFlags (t m) where + getDynFlags = lift getDynFlags + +instance definition. However, that definition would overlap with the +`HasDynFlags (GhcT m)` instance. Instead we define instances for a +couple of common Monad transformers explicitly. -} + +instance (Monoid a, Monad m, HasDynFlags m) => HasDynFlags (WriterT a m) where + getDynFlags = lift getDynFlags + +instance (Monad m, HasDynFlags m) => HasDynFlags (ReaderT a m) where + getDynFlags = lift getDynFlags + +instance (Monad m, HasDynFlags m) => HasDynFlags (MaybeT m) where + getDynFlags = liftMaybeT getDynFlags + +instance (Monad m, HasDynFlags m) => HasDynFlags (CMT.MaybeT m) where + getDynFlags = lift getDynFlags + +#if MIN_VERSION_transformers(4,0,0) +instance (Monad m, HasDynFlags m) => HasDynFlags (ExceptT e m) where + getDynFlags = lift getDynFlags +#endif + class ContainsDynFlags t where extractDynFlags :: t -> DynFlags replaceDynFlags :: t -> DynFlags -> t diff --git a/compiler/main/GhcMonad.hs b/compiler/main/GhcMonad.hs index 44f9eff..34d5bcf 100644 --- a/compiler/main/GhcMonad.hs +++ b/compiler/main/GhcMonad.hs @@ -29,6 +29,7 @@ import DynFlags import Exception import ErrUtils +import Control.Monad import Data.IORef -- ----------------------------------------------------------------------------- @@ -184,13 +185,8 @@ instance ExceptionMonad m => ExceptionMonad (GhcT m) where in unGhcT (f g_restore) s -#if __GLASGOW_HASKELL__ < 710 --- Pre-AMP change -instance (ExceptionMonad m, Functor m) => HasDynFlags (GhcT m) where -#else -instance (ExceptionMonad m) => HasDynFlags (GhcT m) where -#endif - getDynFlags = getSessionDynFlags +instance MonadIO m => HasDynFlags (GhcT m) where + getDynFlags = GhcT $ \(Session r) -> liftM hsc_dflags (liftIO $ readIORef r) #if __GLASGOW_HASKELL__ < 710 -- Pre-AMP change diff --git a/ghc/InteractiveUI.hs b/ghc/InteractiveUI.hs index 02a8670..7fd9c8b 100644 --- a/ghc/InteractiveUI.hs +++ b/ghc/InteractiveUI.hs @@ -849,7 +849,7 @@ runOneCommand eh gCmd = do checkInputForLayout :: String -> InputT GHCi (Maybe String) -> InputT GHCi (Maybe String) checkInputForLayout stmt getStmt = do - dflags' <- lift $ getDynFlags + dflags' <- getDynFlags let dflags = xopt_set dflags' Opt_AlternativeLayoutRule st0 <- getGHCiState let buf' = stringToStringBuffer stmt From git at git.haskell.org Tue Dec 8 10:32:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 8 Dec 2015 10:32:51 +0000 (UTC) Subject: [commit: ghc] master: Update libffi-tarballs submodule to libffi 3.1 (re #10238) (7a40a6c) Message-ID: <20151208103251.DCE2F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7a40a6cde92896d7de09919499c66324a2d01771/ghc >--------------------------------------------------------------- commit 7a40a6cde92896d7de09919499c66324a2d01771 Author: Herbert Valerio Riedel Date: Tue Dec 8 10:46:04 2015 +0100 Update libffi-tarballs submodule to libffi 3.1 (re #10238) Reviewers: bgamari, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1589 GHC Trac Issues: #10238 >--------------------------------------------------------------- 7a40a6cde92896d7de09919499c66324a2d01771 libffi-tarballs | 2 +- libffi/ghc.mk | 3 --- libffi/libffi.x86-execstack.patch | 24 ------------------------ 3 files changed, 1 insertion(+), 28 deletions(-) diff --git a/libffi-tarballs b/libffi-tarballs index b6658e5..ec37a68 160000 --- a/libffi-tarballs +++ b/libffi-tarballs @@ -1 +1 @@ -Subproject commit b6658e5d73eb0579b3054593de21f329ab491e77 +Subproject commit ec37a68838566cb830c33cb30bfade003a306cff diff --git a/libffi/ghc.mk b/libffi/ghc.mk index a25dbf0..404cce9 100644 --- a/libffi/ghc.mk +++ b/libffi/ghc.mk @@ -63,9 +63,6 @@ $(libffi_STAMP_CONFIGURE): $(TOUCH_DEP) # will use cygwin symbolic links which cannot be read by mingw gcc. chmod +x libffi/ln - # don't report nonselinux systems as selinux - ( cd libffi/build && "$(PATCH_CMD)" -p0 < ../libffi.x86-execstack.patch; ) - # We need to use -MMD rather than -MD, as otherwise we get paths # like c:/... in the dependency files on Windows, and the extra # colons break make diff --git a/libffi/libffi.x86-execstack.patch b/libffi/libffi.x86-execstack.patch deleted file mode 100644 index baea18f..0000000 --- a/libffi/libffi.x86-execstack.patch +++ /dev/null @@ -1,24 +0,0 @@ - * RWX --- --- usr/lib/ghc-7.10.1/rts/libffi.so.6.0.2 - * RWX --- --- usr/lib/ghc-7.10.1/rts/libffi.so - * RWX --- --- usr/lib/ghc-7.10.1/rts/libffi.so.6 - * !WX --- --- usr/lib/ghc-7.10.1/rts/libCffi.a:win32.o - * !WX --- --- usr/lib/ghc-7.10.1/rts/libCffi_p.a:win32.o - * !WX --- --- usr/lib/ghc-7.10.1/rts/libCffi_l.a:win32.o - * !WX --- --- usr/lib/ghc-7.10.1/rts/libCffi_debug.a:win32.o - * !WX --- --- usr/lib/ghc-7.10.1/rts/libCffi_thr.a:win32.o - * !WX --- --- usr/lib/ghc-7.10.1/rts/libCffi_thr_debug.a:win32.o - * !WX --- --- usr/lib/ghc-7.10.1/rts/libCffi_thr_l.a:win32.o - * !WX --- --- usr/lib/ghc-7.10.1/rts/libCffi_thr_p.a:win32.o - -http://bugs.gentoo.org/511634 -http://sourceware.org/ml/libffi-discuss/2014/msg00058.html - ---- src/x86/win32.S -+++ src/x86/win32.S -@@ -1304,3 +1304,6 @@ - - #endif /* !_MSC_VER */ - -+#if defined __ELF__ && defined __linux__ -+ .section .note.GNU-stack,"", at progbits -+#endif From git at git.haskell.org Tue Dec 8 10:32:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 8 Dec 2015 10:32:54 +0000 (UTC) Subject: [commit: ghc] master: Rename s/7.12.1/8.0.1/ two minor occurences (bb753c5) Message-ID: <20151208103254.947423A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bb753c50a1ca5dbc5c8dc28aabd2b7d40c79e729/ghc >--------------------------------------------------------------- commit bb753c50a1ca5dbc5c8dc28aabd2b7d40c79e729 Author: Herbert Valerio Riedel Date: Tue Dec 8 11:32:48 2015 +0100 Rename s/7.12.1/8.0.1/ two minor occurences [skip ci] >--------------------------------------------------------------- bb753c50a1ca5dbc5c8dc28aabd2b7d40c79e729 libraries/template-haskell/changelog.md | 2 +- utils/mkUserGuidePart/Options/Language.hs | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/libraries/template-haskell/changelog.md b/libraries/template-haskell/changelog.md index e4edf63..8e09a75 100644 --- a/libraries/template-haskell/changelog.md +++ b/libraries/template-haskell/changelog.md @@ -2,7 +2,7 @@ ## 2.11.0.0 *TBA* - * Bundled with GHC 7.12.1 + * Bundled with GHC 8.0.1 * The compiler can now resolve infix operator fixities in types on its own. The `UInfixT` constructor of `Type` is analoguous to `UInfixE` for expressions diff --git a/utils/mkUserGuidePart/Options/Language.hs b/utils/mkUserGuidePart/Options/Language.hs index ab3e20f..0fc3ea5 100644 --- a/utils/mkUserGuidePart/Options/Language.hs +++ b/utils/mkUserGuidePart/Options/Language.hs @@ -65,7 +65,7 @@ languageOptions = "Enable :ref:`Applicative do-notation desugaring `" , flagType = DynamicFlag , flagReverse = "-XNoApplicativeDo" - , flagSince = "7.12.1" + , flagSince = "8.0.1" } , flag { flagName = "-XAutoDeriveTypeable" , flagDescription = From git at git.haskell.org Tue Dec 8 10:45:56 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 8 Dec 2015 10:45:56 +0000 (UTC) Subject: [commit: ghc] master: Fix double MaybeT instance (2cfa5db) Message-ID: <20151208104556.965CA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2cfa5db47dc16caf7cb7be5aed2fbe843cd784a8/ghc >--------------------------------------------------------------- commit 2cfa5db47dc16caf7cb7be5aed2fbe843cd784a8 Author: Herbert Valerio Riedel Date: Tue Dec 8 11:45:38 2015 +0100 Fix double MaybeT instance This is a fixup to fd3b845c01aa26b6e5cd12c00af59e5468e21b1b which didn't take into account 09333313f32be975faf9158fcd3648489d78ad82 having pushed as well. >--------------------------------------------------------------- 2cfa5db47dc16caf7cb7be5aed2fbe843cd784a8 compiler/main/DynFlags.hs | 4 ---- 1 file changed, 4 deletions(-) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index c492a01..bceb51f 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -180,7 +180,6 @@ import Control.Monad import Control.Monad.Trans.Class import Control.Monad.Trans.Writer import Control.Monad.Trans.Reader -import qualified Control.Monad.Trans.Maybe as CMT #if MIN_VERSION_transformers(4,0,0) import Control.Monad.Trans.Except #endif @@ -937,9 +936,6 @@ instance (Monad m, HasDynFlags m) => HasDynFlags (ReaderT a m) where getDynFlags = lift getDynFlags instance (Monad m, HasDynFlags m) => HasDynFlags (MaybeT m) where - getDynFlags = liftMaybeT getDynFlags - -instance (Monad m, HasDynFlags m) => HasDynFlags (CMT.MaybeT m) where getDynFlags = lift getDynFlags #if MIN_VERSION_transformers(4,0,0) From git at git.haskell.org Tue Dec 8 13:55:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 8 Dec 2015 13:55:36 +0000 (UTC) Subject: [commit: ghc] master: Fix typo sneaked in with fd3b845c01aa26b6e5 (2106d86) Message-ID: <20151208135536.12C8F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2106d8641a4f26fa934e092ba88b535cdad5a6fe/ghc >--------------------------------------------------------------- commit 2106d8641a4f26fa934e092ba88b535cdad5a6fe Author: Herbert Valerio Riedel Date: Tue Dec 8 14:54:14 2015 +0100 Fix typo sneaked in with fd3b845c01aa26b6e5 >--------------------------------------------------------------- 2106d8641a4f26fa934e092ba88b535cdad5a6fe compiler/main/DynFlags.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index bceb51f..7818c6b 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -180,7 +180,7 @@ import Control.Monad import Control.Monad.Trans.Class import Control.Monad.Trans.Writer import Control.Monad.Trans.Reader -#if MIN_VERSION_transformers(4,0,0) +#if MIN_VERSION_transformers(0,4,0) import Control.Monad.Trans.Except #endif import Control.Exception (throwIO) @@ -938,7 +938,7 @@ instance (Monad m, HasDynFlags m) => HasDynFlags (ReaderT a m) where instance (Monad m, HasDynFlags m) => HasDynFlags (MaybeT m) where getDynFlags = lift getDynFlags -#if MIN_VERSION_transformers(4,0,0) +#if MIN_VERSION_transformers(0,4,0) instance (Monad m, HasDynFlags m) => HasDynFlags (ExceptT e m) where getDynFlags = lift getDynFlags #endif From git at git.haskell.org Tue Dec 8 13:59:28 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 8 Dec 2015 13:59:28 +0000 (UTC) Subject: [commit: ghc] master: docs/glasgow_exts: Use warning admonition (69c3964) Message-ID: <20151208135928.82BE23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/69c3964a93b2b8359452799c13ab551b67e4c5a5/ghc >--------------------------------------------------------------- commit 69c3964a93b2b8359452799c13ab551b67e4c5a5 Author: Ben Gamari Date: Tue Dec 8 13:14:14 2015 +0100 docs/glasgow_exts: Use warning admonition >--------------------------------------------------------------- 69c3964a93b2b8359452799c13ab551b67e4c5a5 docs/users_guide/glasgow_exts.rst | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index 4fc02f6..d313556 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -11542,8 +11542,8 @@ You can add explicit phase control (:ref:`phase-control`) to do so, the same phase is used for the rewrite rule and the INLINE control of the specialised function. -Warning: you can make GHC diverge by using ``SPECIALISE INLINE`` on an -ordinarily-recursive function. +.. warning:: You can make GHC diverge by using ``SPECIALISE INLINE`` on an + ordinarily-recursive function. ``SPECIALIZE`` for imported functions ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ From git at git.haskell.org Tue Dec 8 15:00:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 8 Dec 2015 15:00:26 +0000 (UTC) Subject: [commit: ghc] master: users_guide: Show sub-sub-sections in ToC (e792711) Message-ID: <20151208150026.964DC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e7927110bd1c1336bb4cb17eb52cf5b6adae3902/ghc >--------------------------------------------------------------- commit e7927110bd1c1336bb4cb17eb52cf5b6adae3902 Author: Ben Gamari Date: Tue Dec 8 15:59:43 2015 +0100 users_guide: Show sub-sub-sections in ToC >--------------------------------------------------------------- e7927110bd1c1336bb4cb17eb52cf5b6adae3902 docs/users_guide/index.rst | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/docs/users_guide/index.rst b/docs/users_guide/index.rst index 1b618d4..3f1f381 100644 --- a/docs/users_guide/index.rst +++ b/docs/users_guide/index.rst @@ -7,7 +7,7 @@ Welcome to the GHC Users Guide Contents: .. toctree:: - :maxdepth: 2 + :maxdepth: 3 :numbered: license From git at git.haskell.org Tue Dec 8 15:05:14 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 8 Dec 2015 15:05:14 +0000 (UTC) Subject: [commit: ghc] master: Comments about polymorphic recursion (6c794c3) Message-ID: <20151208150514.A56763A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6c794c311d5312ba3f92434ee6f35040d3b69353/ghc >--------------------------------------------------------------- commit 6c794c311d5312ba3f92434ee6f35040d3b69353 Author: Simon Peyton Jones Date: Tue Dec 8 13:11:42 2015 +0000 Comments about polymorphic recursion See Trac #11176 >--------------------------------------------------------------- 6c794c311d5312ba3f92434ee6f35040d3b69353 compiler/hsSyn/HsBinds.hs | 54 ++++++++++++++++++++++++++++++++++++------- compiler/typecheck/TcBinds.hs | 5 ++-- 2 files changed, 49 insertions(+), 10 deletions(-) diff --git a/compiler/hsSyn/HsBinds.hs b/compiler/hsSyn/HsBinds.hs index 25ce654..79206d7 100644 --- a/compiler/hsSyn/HsBinds.hs +++ b/compiler/hsSyn/HsBinds.hs @@ -263,7 +263,7 @@ Note [AbsBinds] ~~~~~~~~~~~~~~~ The AbsBinds constructor is used in the output of the type checker, to record *typechecked* and *generalised* bindings. Consider a module M, with this -top-level binding +top-level binding, where there is no type signature for M.reverse, M.reverse [] = [] M.reverse (x:xs) = M.reverse xs ++ [x] @@ -282,8 +282,8 @@ Notice that 'M.reverse' is polymorphic as expected, but there is a local definition for plain 'reverse' which is *monomorphic*. The type variable 'a' scopes over the entire letrec. -That's after desugaring. What about after type checking but before desugaring? -That's where AbsBinds comes in. It looks like this: +That's after desugaring. What about after type checking but before +desugaring? That's where AbsBinds comes in. It looks like this: AbsBinds { abs_tvs = [a] , abs_exports = [ABE { abe_poly = M.reverse :: forall a. [a] -> [a], @@ -305,11 +305,11 @@ you were defining) appears in the abe_poly field of the abs_exports. The bindings in abs_binds are for fresh, local, Ids with a *monomorphic* Id. -If there is a group of mutually recursive functions without type -signatures, we get one AbsBinds with the monomorphic versions of the -bindings in abs_binds, and one element of abe_exports for each -variable bound in the mutually recursive group. This is true even for -pattern bindings. Example: +If there is a group of mutually recursive (see Note [Polymoprhic +recursion]) functions without type signatures, we get one AbsBinds +with the monomorphic versions of the bindings in abs_binds, and one +element of abe_exports for each variable bound in the mutually +recursive group. This is true even for pattern bindings. Example: (f,g) = (\x -> x, f) After type checking we get AbsBinds { abs_tvs = [a] @@ -319,6 +319,44 @@ After type checking we get , abe_mono = g :: a -> a }] , abs_binds = { (f,g) = (\x -> x, f) } +Note [Polymoprhic recursion] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider + Rec { f x = ...(g ef)... + + ; g :: forall a. [a] -> [a] + ; g y = ...(f eg)... } + +These bindings /are/ mutually recursive (f calls g, and g calls f). +But we can use the type signature for g to break the recursion, +like this: + + 1. Add g :: forall a. [a] -> [a] to the type environment + + 2. Typecheck the definition of f, all by itself, + including generalising it to find its most general + type, say f :: forall b. b -> b -> [b] + + 3. Extend the type environment with that type for f + + 4. Typecheck the definition of g, all by itself, + checking that it has the type claimed by its signature + +Steps 2 and 4 each generate a separate AbsBinds, so we end +up with + Rec { AbsBinds { ...for f ... } + ; AbsBinds { ...for g ... } } + +This approach allows both f and to call each other +polymoprhically, even though only g has a signature. + +We get an AbsBinds that encompasses multiple source-program +bindings only when + * Each binding in the group has at least one binder that + lacks a user type signature + * The group forms a strongly connected component + + Note [AbsBinds wrappers] ~~~~~~~~~~~~~~~~~~~~~~~~ Consider diff --git a/compiler/typecheck/TcBinds.hs b/compiler/typecheck/TcBinds.hs index 5c6593a..96aec1e 100644 --- a/compiler/typecheck/TcBinds.hs +++ b/compiler/typecheck/TcBinds.hs @@ -442,6 +442,7 @@ tc_group top_lvl sig_fn prag_fn (Recursive, binds) thing_inside -- strongly-connected-component analysis, this time omitting -- any references to variables with type signatures. -- (This used to be optional, but isn't now.) + -- See Note [Polymorphic recursion] in HsBinds. do { traceTc "tc_group rec" (pprLHsBinds binds) ; when hasPatSyn $ recursivePatSynErr binds ; (binds1, thing) <- go sccs @@ -502,10 +503,10 @@ tc_single top_lvl sig_fn prag_fn lbind thing_inside ; return (binds1, thing) } ------------------------ -mkEdges :: TcSigFun -> LHsBinds Name -> [Node BKey (LHsBind Name)] - type BKey = Int -- Just number off the bindings +mkEdges :: TcSigFun -> LHsBinds Name -> [Node BKey (LHsBind Name)] +-- See Note [Polymorphic recursion] in HsBinds. mkEdges sig_fn binds = [ (bind, key, [key | n <- nameSetElems (bind_fvs (unLoc bind)), Just key <- [lookupNameEnv key_map n], no_sig n ]) From git at git.haskell.org Tue Dec 8 15:05:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 8 Dec 2015 15:05:17 +0000 (UTC) Subject: [commit: ghc] master: Comments only (aa6ae8a) Message-ID: <20151208150517.52FEC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/aa6ae8a45e7216106df3f7a9bf9fbebd1affc4ff/ghc >--------------------------------------------------------------- commit aa6ae8a45e7216106df3f7a9bf9fbebd1affc4ff Author: Simon Peyton Jones Date: Mon Dec 7 12:48:44 2015 +0000 Comments only >--------------------------------------------------------------- aa6ae8a45e7216106df3f7a9bf9fbebd1affc4ff compiler/basicTypes/Var.hs | 28 ++++++++++++++++++++++++---- 1 file changed, 24 insertions(+), 4 deletions(-) diff --git a/compiler/basicTypes/Var.hs b/compiler/basicTypes/Var.hs index 7c4ccfc..dba00d3 100644 --- a/compiler/basicTypes/Var.hs +++ b/compiler/basicTypes/Var.hs @@ -181,11 +181,31 @@ data IdScope -- See Note [GlobalId/LocalId] = GlobalId | LocalId ExportFlag -data ExportFlag - = NotExported -- ^ Not exported: may be discarded as dead code. - | Exported -- ^ Exported: kept alive +data ExportFlag -- See Note [ExportFlag on binders] + = NotExported -- ^ Not exported: may be discarded as dead code. + | Exported -- ^ Exported: kept alive + +{- Note [ExportFlag on binders] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +An ExportFlag of "Exported" on a top-level binder says "keep this +binding alive; do not drop it as dead code". This transitively +keeps alive all the other top-level bindings that this binding refers +to. This property is persisted all the way down the pipeline, so that +the binding will be compiled all the way to object code, and its +symbols will appear in the linker symbol table. + +However, note that this use of "exported" is quite different to the +export list on a Haskell module. Setting the ExportFlag on an Id does +/not/ mean that if you import the module (in Haskell source code you +will see this Id. Of course, things that appear in the export list +of the source Haskell module do indeed have their ExportFlag set. +But many other things, such as dictionary functions, are kept alive +by having their ExportFlag set, even though they are not exported +in the source-code sense. + +We should probably use a different term for ExportFlag, like +KeepAlive. -{- Note [GlobalId/LocalId] ~~~~~~~~~~~~~~~~~~~~~~~ A GlobalId is From git at git.haskell.org Tue Dec 8 15:44:04 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 8 Dec 2015 15:44:04 +0000 (UTC) Subject: [commit: ghc] master: An assortment of typos (d7729c7) Message-ID: <20151208154404.8B4D13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d7729c75c666bfeff2a70869c0613ea429202f11/ghc >--------------------------------------------------------------- commit d7729c75c666bfeff2a70869c0613ea429202f11 Author: Gabor Greif Date: Tue Dec 8 16:43:34 2015 +0100 An assortment of typos >--------------------------------------------------------------- d7729c75c666bfeff2a70869c0613ea429202f11 compiler/basicTypes/Var.hs | 2 +- compiler/deSugar/DsBinds.hs | 2 +- compiler/hsSyn/HsBinds.hs | 6 +++--- compiler/main/HscMain.hs | 2 +- compiler/typecheck/TcRnTypes.hs | 2 +- libraries/base/System/Environment.hs | 2 +- testsuite/tests/typecheck/should_compile/tc191.hs | 2 +- 7 files changed, 9 insertions(+), 9 deletions(-) diff --git a/compiler/basicTypes/Var.hs b/compiler/basicTypes/Var.hs index dba00d3..87658b5 100644 --- a/compiler/basicTypes/Var.hs +++ b/compiler/basicTypes/Var.hs @@ -196,7 +196,7 @@ symbols will appear in the linker symbol table. However, note that this use of "exported" is quite different to the export list on a Haskell module. Setting the ExportFlag on an Id does -/not/ mean that if you import the module (in Haskell source code you +/not/ mean that if you import the module (in Haskell source code) you will see this Id. Of course, things that appear in the export list of the source Haskell module do indeed have their ExportFlag set. But many other things, such as dictionary functions, are kept alive diff --git a/compiler/deSugar/DsBinds.hs b/compiler/deSugar/DsBinds.hs index 0da90f0..724da24 100644 --- a/compiler/deSugar/DsBinds.hs +++ b/compiler/deSugar/DsBinds.hs @@ -521,7 +521,7 @@ Here `tm` is the monomorphic binding for `rhs`. With `Strict`, we want to force `tm`, but NOT `fm` or `gm`. Alas, `tm` isn't in scope in the `in ` part. -The simplest thing is to return it in the polymoprhic +The simplest thing is to return it in the polymorphic tuple `t`, thus: let t = /\a. letrec tm = rhs[fm,gm] diff --git a/compiler/hsSyn/HsBinds.hs b/compiler/hsSyn/HsBinds.hs index 79206d7..cbd45d8 100644 --- a/compiler/hsSyn/HsBinds.hs +++ b/compiler/hsSyn/HsBinds.hs @@ -305,7 +305,7 @@ you were defining) appears in the abe_poly field of the abs_exports. The bindings in abs_binds are for fresh, local, Ids with a *monomorphic* Id. -If there is a group of mutually recursive (see Note [Polymoprhic +If there is a group of mutually recursive (see Note [Polymorphic recursion]) functions without type signatures, we get one AbsBinds with the monomorphic versions of the bindings in abs_binds, and one element of abe_exports for each variable bound in the mutually @@ -319,7 +319,7 @@ After type checking we get , abe_mono = g :: a -> a }] , abs_binds = { (f,g) = (\x -> x, f) } -Note [Polymoprhic recursion] +Note [Polymorphic recursion] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Consider Rec { f x = ...(g ef)... @@ -348,7 +348,7 @@ up with ; AbsBinds { ...for g ... } } This approach allows both f and to call each other -polymoprhically, even though only g has a signature. +polymorphically, even though only g has a signature. We get an AbsBinds that encompasses multiple source-program bindings only when diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs index 401f049..bd0fa19 100644 --- a/compiler/main/HscMain.hs +++ b/compiler/main/HscMain.hs @@ -798,7 +798,7 @@ hscFileFrontEnd mod_summary = do -- Note [Safe Haskell Inference] -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -- Safe Haskell does Safe inference on modules that don't have any specific --- safe haskell mode flag. The basic aproach to this is: +-- safe haskell mode flag. The basic approach to this is: -- * When deciding if we need to do a Safe language check, treat -- an unmarked module as having -XSafe mode specified. -- * For checks, don't throw errors but return them to the caller. diff --git a/compiler/typecheck/TcRnTypes.hs b/compiler/typecheck/TcRnTypes.hs index 0e8f682..b5748f4 100644 --- a/compiler/typecheck/TcRnTypes.hs +++ b/compiler/typecheck/TcRnTypes.hs @@ -1142,7 +1142,7 @@ data TcIdSigInfo data TcIdSigBndr -- See Note [Complete and partial type signatures] = CompleteSig -- A complete signature with no wildards, -- so the complete polymorphic type is known. - TcId -- The polymoprhic Id with that type + TcId -- The polymorphic Id with that type | PartialSig -- A partial type signature (i.e. includes one or more -- wildcards). In this case it doesn't make sense to give diff --git a/libraries/base/System/Environment.hs b/libraries/base/System/Environment.hs index 066329c..b3fbaf8 100644 --- a/libraries/base/System/Environment.hs +++ b/libraries/base/System/Environment.hs @@ -299,7 +299,7 @@ putEnv keyvalue = do -- IMPORTANT: Do not free `s` after calling putenv! -- -- According to SUSv2, the string passed to putenv becomes part of the - -- enviroment. + -- environment. throwErrnoIf_ (/= 0) "putenv" (c_putenv s) foreign import ccall unsafe "putenv" c_putenv :: CString -> IO CInt diff --git a/testsuite/tests/typecheck/should_compile/tc191.hs b/testsuite/tests/typecheck/should_compile/tc191.hs index cf77c05..403ec88 100644 --- a/testsuite/tests/typecheck/should_compile/tc191.hs +++ b/testsuite/tests/typecheck/should_compile/tc191.hs @@ -19,7 +19,7 @@ geq :: Data a => a -> a -> Bool geq x y = geq' x y where -- This type signature no longer works, because it is --- insufficiently polymoprhic. +-- insufficiently polymorphic. -- geq' :: forall a b. (Data a, Data b) => a -> b -> Bool geq' :: GenericQ (GenericQ Bool) geq' x y = (toConstr x == toConstr y) From git at git.haskell.org Tue Dec 8 16:51:08 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 8 Dec 2015 16:51:08 +0000 (UTC) Subject: [commit: ghc] wip/T11067: Merge remote-tracking branch 'origin/master' into wip/T11067 (8e021c4) Message-ID: <20151208165108.B85DD3A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T11067 Link : http://ghc.haskell.org/trac/ghc/changeset/8e021c43c0eea4ca36dbc2867cdc1475cae9a36c/ghc >--------------------------------------------------------------- commit 8e021c43c0eea4ca36dbc2867cdc1475cae9a36c Merge: 96eac39 741f837 Author: Simon Peyton Jones Date: Wed Dec 2 14:31:35 2015 +0000 Merge remote-tracking branch 'origin/master' into wip/T11067 Conflicts: testsuite/tests/indexed-types/should_fail/T1897b.stderr testsuite/tests/partial-sigs/should_compile/ExtraConstraints3.stderr testsuite/tests/partial-sigs/should_compile/WarningWildcardInstantiations.stderr testsuite/tests/partial-sigs/should_fail/InstantiatedNamedWildcardsInConstraints.stderr testsuite/tests/partial-sigs/should_fail/WildcardInstantiations.stderr testsuite/tests/typecheck/should_compile/T9939.stderr testsuite/tests/typecheck/should_fail/CustomTypeErrors02.stderr testsuite/tests/typecheck/should_fail/T8883.stderr >--------------------------------------------------------------- Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 8e021c43c0eea4ca36dbc2867cdc1475cae9a36c From git at git.haskell.org Tue Dec 8 16:51:04 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 8 Dec 2015 16:51:04 +0000 (UTC) Subject: [commit: ghc] wip/T11067: Wibbles to type errors (96eac39) Message-ID: <20151208165104.98A543A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T11067 Link : http://ghc.haskell.org/trac/ghc/changeset/96eac39d7e7ea5099275a4df2319bd9a31de70c7/ghc >--------------------------------------------------------------- commit 96eac39d7e7ea5099275a4df2319bd9a31de70c7 Author: Simon Peyton Jones Date: Wed Dec 2 14:23:52 2015 +0000 Wibbles to type errors >--------------------------------------------------------------- 96eac39d7e7ea5099275a4df2319bd9a31de70c7 testsuite/tests/ado/ado004.stderr | 10 ++-- testsuite/tests/driver/T4437.hs | 4 ++ testsuite/tests/module/mod40.stderr | 16 +++-- .../should_compile/ExtraConstraints1.stderr | 6 +- .../should_compile/ExtraConstraints3.stderr | 38 ++++++------ .../WarningWildcardInstantiations.stderr | 60 +++++++++---------- .../InstantiatedNamedWildcardsInConstraints.stderr | 14 ++--- .../should_fail/WildcardInstantiations.stderr | 70 +++++++++++----------- testsuite/tests/polykinds/T7332.hs | 33 +++++++--- testsuite/tests/typecheck/should_fail/all.T | 4 +- testsuite/tests/typecheck/should_fail/tcfail216.hs | 5 +- .../tests/typecheck/should_fail/tcfail216.stderr | 5 -- testsuite/tests/typecheck/should_fail/tcfail217.hs | 4 ++ .../tests/typecheck/should_fail/tcfail217.stderr | 5 -- 14 files changed, 148 insertions(+), 126 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 96eac39d7e7ea5099275a4df2319bd9a31de70c7 From git at git.haskell.org Tue Dec 8 16:51:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 8 Dec 2015 16:51:11 +0000 (UTC) Subject: [commit: ghc] wip/T11067: Change the superclass story (recursive superclasses) (9acb570) Message-ID: <20151208165111.692763A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T11067 Link : http://ghc.haskell.org/trac/ghc/changeset/9acb5700850af349358b8083f77efc06521f743a/ghc >--------------------------------------------------------------- commit 9acb5700850af349358b8083f77efc06521f743a Author: Simon Peyton Jones Date: Mon Dec 7 15:56:29 2015 +0000 Change the superclass story (recursive superclasses) In-flight >--------------------------------------------------------------- 9acb5700850af349358b8083f77efc06521f743a compiler/typecheck/TcCanonical.hs | 119 ++++++++++++++++++++++++++++++++------ compiler/typecheck/TcErrors.hs | 2 +- compiler/typecheck/TcInteract.hs | 18 +----- compiler/typecheck/TcSimplify.hs | 14 +++-- compiler/typecheck/TcType.hs | 33 ++++++----- 5 files changed, 133 insertions(+), 53 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 9acb5700850af349358b8083f77efc06521f743a From git at git.haskell.org Tue Dec 8 16:51:14 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 8 Dec 2015 16:51:14 +0000 (UTC) Subject: [commit: ghc] wip/T11067: Merge remote-tracking branch 'origin/master' into wip/T11067 (821c043) Message-ID: <20151208165114.A7CDD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T11067 Link : http://ghc.haskell.org/trac/ghc/changeset/821c043a18c38a1b9229054471efa112c642c696/ghc >--------------------------------------------------------------- commit 821c043a18c38a1b9229054471efa112c642c696 Merge: 9acb570 04e1c27 Author: Simon Peyton Jones Date: Mon Dec 7 16:10:43 2015 +0000 Merge remote-tracking branch 'origin/master' into wip/T11067 Conflicts: compiler/utils/Bag.hs utils/haddock >--------------------------------------------------------------- Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 821c043a18c38a1b9229054471efa112c642c696 From git at git.haskell.org Tue Dec 8 16:51:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 8 Dec 2015 16:51:17 +0000 (UTC) Subject: [commit: ghc] wip/T11067: Wibbles (54f42f7) Message-ID: <20151208165117.673C73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T11067 Link : http://ghc.haskell.org/trac/ghc/changeset/54f42f77a02f492976554a81dc922d86b5127de5/ghc >--------------------------------------------------------------- commit 54f42f77a02f492976554a81dc922d86b5127de5 Author: Simon Peyton Jones Date: Tue Dec 8 16:49:22 2015 +0000 Wibbles >--------------------------------------------------------------- 54f42f77a02f492976554a81dc922d86b5127de5 compiler/typecheck/TcCanonical.hs | 12 +++++++----- compiler/typecheck/TcSimplify.hs | 22 +++++++++++----------- compiler/utils/Bag.hs | 2 +- 3 files changed, 19 insertions(+), 17 deletions(-) diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index 427ecfe..10e29fb 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -3,7 +3,7 @@ module TcCanonical( canonicalize, unifyDerived, - makeSuperClasses, addSuperClasses, + makeSuperClasses, mkGivenWithSuperClasses, StopOrContinue(..), stopWith, continueWith ) where @@ -360,10 +360,12 @@ Mind you, now that Wanteds cannot rewrite Derived, I think this particular situation can't happen. -} -addSuperClasses :: CtEvidence -> TcS [Ct] --- Make a Ct from this CtEvidence, but add its superclasses --- if it's a class constraint -addSuperClasses ev = mk_superclasses emptyNameSet ev +mkGivenWithSuperClasses :: CtLoc -> EvId -> TcS [Ct] +-- From a given EvId, make its Ct, plus the Ct's of its superclasses +mkGivenWithSuperClasses loc ev_id + = mk_superclasses emptyNameSet (CtGiven { ctev_evar = ev_id + , ctev_pred = evVarPred ev_id + , ctev_loc = loc }) makeSuperClasses :: Ct -> TcS [Ct] -- Returns superclasses, transitively, see Note [The superclasses story] diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs index 2eb26f8..e14589f 100644 --- a/compiler/typecheck/TcSimplify.hs +++ b/compiler/typecheck/TcSimplify.hs @@ -33,7 +33,7 @@ import PrelNames import TcErrors import TcEvidence import TcInteract -import TcCanonical ( makeSuperClasses, addSuperClasses ) +import TcCanonical ( makeSuperClasses, mkGivenWithSuperClasses ) import TcMType as TcM import TcRnMonad as TcRn import TcSMonad as TcS @@ -368,10 +368,14 @@ tcCheckSatisfiability :: Bag EvVar -> TcM Bool tcCheckSatisfiability givens = do { lcl_env <- TcRn.getLclEnv ; let given_loc = mkGivenLoc topTcLevel UnkSkol lcl_env + given_cts = [ mkNonCanonical (CtGiven { ctev_evar = ev_id + , ctev_pred = evVarPred ev_id + , ctev_loc = given_loc }) + | ev_id <- bagToList givens ] ; traceTc "checkSatisfiabilty {" (ppr givens) ; (res, _ev_binds) <- runTcS $ - do { cts <- solveSimpleGivens given_loc (bagToList givens) - ; return (not (isEmptyBag cts)) } + do { insols <- solveSimpleGivens given_cts + ; return (not (isEmptyBag insols)) } ; traceTc "checkSatisfiabilty }" (ppr res) ; return (not res) } @@ -1071,7 +1075,7 @@ solveImplication :: Implication -- Wanted solveImplication imp@(Implic { ic_tclvl = tclvl , ic_binds = ev_binds , ic_skols = skols - , ic_given = givens + , ic_given = given_ids , ic_wanted = wanteds , ic_info = info , ic_status = status @@ -1088,8 +1092,9 @@ solveImplication imp@(Implic { ic_tclvl = tclvl -- Solve the nested constraints ; (no_given_eqs, given_insols, residual_wanted) - <- nestImplicTcS ev_binds tclvl $ - do { givens_w_scs <- concatMapM (addSuperClasses . mk_given_ev) givens + <- nestImplicTcS ev_binds tclvl $ + do { let loc = mkGivenLoc tclvl info env + ; givens_w_scs <- concatMapM (mkGivenWithSuperClasses loc) given_ids ; given_insols <- solveSimpleGivens givens_w_scs ; residual_wanted <- solveWanteds wanteds @@ -1121,11 +1126,6 @@ solveImplication imp@(Implic { ic_tclvl = tclvl , text "implication evbinds = " <+> ppr (evBindMapBinds evbinds) ] ; return (floated_eqs, res_implic) } - where - given_loc = mkGivenLoc tclvl info env - mk_given_ev ev_id = CtGiven { ctev_evar = ev_id - , ctev_pred = evVarPred ev_id - , ctev_loc = given_loc } ---------------------- setImplicationStatus :: Implication -> TcS (Maybe Implication) diff --git a/compiler/utils/Bag.hs b/compiler/utils/Bag.hs index 357399b..d959709 100644 --- a/compiler/utils/Bag.hs +++ b/compiler/utils/Bag.hs @@ -20,7 +20,7 @@ module Bag ( listToBag, bagToList, mapAccumBagL, foldrBagM, foldlBagM, mapBagM, mapBagM_, flatMapBagM, flatMapBagPairM, - mapAndUnzipBagM, mapAccumBagL, mapAccumBagLM + mapAndUnzipBagM, mapAccumBagL, mapAccumBagLM, mapAndUnzipBagM, mapAccumBagLM, anyBagM, filterBagM ) where From git at git.haskell.org Tue Dec 8 16:51:20 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 8 Dec 2015 16:51:20 +0000 (UTC) Subject: [commit: ghc] wip/T11067: Manually update submodules to HEAD (807dc1f) Message-ID: <20151208165120.145283A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T11067 Link : http://ghc.haskell.org/trac/ghc/changeset/807dc1fc1774271c744ab3b6a56f5e97811e3821/ghc >--------------------------------------------------------------- commit 807dc1fc1774271c744ab3b6a56f5e97811e3821 Author: Simon Peyton Jones Date: Tue Dec 8 16:50:32 2015 +0000 Manually update submodules to HEAD >--------------------------------------------------------------- 807dc1fc1774271c744ab3b6a56f5e97811e3821 libraries/unix | 2 +- utils/haddock | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/libraries/unix b/libraries/unix index 137fa1b..147630c 160000 --- a/libraries/unix +++ b/libraries/unix @@ -1 +1 @@ -Subproject commit 137fa1b06a79a9baa0d5fcf2ec11f964c3423f6a +Subproject commit 147630c7c76bd9b947524ef140d21b9e81967c6e diff --git a/utils/haddock b/utils/haddock index fcd1bb7..f4ef254 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit fcd1bb7177a800f6f56a623c2468fc46a59c527b +Subproject commit f4ef2548954bedf26674adc7a06574e718898d19 From git at git.haskell.org Tue Dec 8 16:51:22 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 8 Dec 2015 16:51:22 +0000 (UTC) Subject: [commit: ghc] wip/T11067's head updated: Manually update submodules to HEAD (807dc1f) Message-ID: <20151208165122.BF7F53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T11067' now includes: 9aa9458 Note STM's vulnerability to non-allocating loops c7a058f User's Guide: Add links to MFP wiki page 5699ac9 User documentation for DuplicateRecordFields d2a2d5e Note #11108 in the bugs section of users guide c4308b4 rts/Pool: Add poolTryTake 1712a9e LibdwPool: Use poolTryTake ba14f04 Libdw: Handle failure to grab session for location lookup d25f853 Update transformers submodule 49aae12 Check arity on default decl for assoc types 583867b Update haskeline & terminfo submodules 85fcd03 Implement new -XTemplateHaskellQuotes pragma 72e3620 ghci: Add support for prompt functions 55c737f ghc-pkg: print version when verbose 399a5b4 Remove deprecated quasiquoter syntax. 71c0cc1 GHCi should not defer typed holes 54a9456 Update containers submodule 616aceb Update deepseq submodule 5897213 Remove redundant `#if`s f101a82 ghci: Refactor handling of :show bcd55a9 Some improvements on CoreToDos passed to plugins 290def7 Implement warnings for Semigroups as parent of Monoid afb7213 MkId: Typos in comments 14d0f7f Build system: Add stage specific SRC_HC_(WARNING_)OPTS 6dce643 Fix grammar and typo in TcTyDecls 36c1247 Remove duplicated line 44c3e37 Fix warning about unused pattern variable b432e2f Make the determinism tests more robust 1e041b7 Refactor treatment of wildcards 218fdf9 Make the order of fixities in the iface file deterministic 741f837 Implement more deterministic operations and document them 96eac39 Wibbles to type errors 8e021c4 Merge remote-tracking branch 'origin/master' into wip/T11067 52b02e6 Comments only (isIrrefutablePat) b564731 Comments (TcSMonad) d00cdf2 Revert "ghci: Add support for prompt functions" 1caff20 StgSyn: Remove unused SRT constructor c75948b Move Stg-specific code from DynFlags to SimplStg d4d54b4 Remove *.xml from gitignore a12e47b Avoid panic due to partial ieName 8cba907 Create empty dump files when there was nothing to dump 0d1a2d2 ErrUtils: Spruce up Haddocks e7929ba Update bytestring submodule d25f3c0 users_guide/glasgow_exts.rst: fix link markup 8a50610 Major Overhaul of Pattern Match Checking (Fixes #595) 43a31fe testsuite: haddock.compiler: Bump expected allocations a034031 extending_ghc.rst: fix broken link (Trac #10950) c5597bb Revert "Create empty dump files when there was nothing to dump" 7b29b0b Fix haddock syntax 0dd61fe Kill redundant patterns 934b3a0 Update test output 40fc353 Bump hoopl submodule ae4398d Improve performance for PM check on literals (Fixes #11160 and #11161) 99d01e1 Remove unused import in deSugar/TmOracle.hs 7af29da Use Autoconf's AC_USE_SYSTEM_EXTENSIONS cd9f3bf RTS: Rename InCall.stat struct field to .rstat 6ef351d On AIX we need -D_BSD defined in d40f5b7 PmExpr: Fix CPP unacceptable too clang's CPP 36a208f Use builtin ISO 8859-1 decoder in mkTextEncoding befc4e4 Check: More Clang/CPP wibbles e9220da Bump allocations for T783 dc33e4c T5642 is broken 96e67c0 T5642: Skip it entirely 5b2b7e3 Make callToPats deterministic in SpecConstr 1c9fd3f Case-of-empty-alts is trivial (Trac #11155) 28035c0 Add derived constraints for wildcard signatures 1cb3c8c Wibbles only 822141b Make -dppr-debug show contents of (TypeError ...) 1160dc5 Fix egregious error in eta-reduction of data families 31b482b Minor refactoring of user type errors 67565a7 Tidy user type errors in checkValidType 43a5970 Comments only 16aae60 T5642: Fix skip usage caa6851 testsuite: Rename pmcheck/T7669 to pmcheck/T7669a d4bf863 Update peak_megabytes_allocated for T9675 020375d Add linter to check for binaries accidentally added to repository 901cab1 lint: Add linter to catch uses of ASSERT macro that Clang dislikes c865c42 StgCmmMonad: Implement Outputable instance for Sequel for debugging e2c518e libdw: enable support only on i386 and amd64 81cf200 pmcheck: Comments about term equality representation 406444b pmcheck: Comments about undecidability of literal equality 8f28797 Fix broken linters when using python3 c714f8f Use git.h.o copy of arcanist-external-json-linter a14296c Temporarily disable external-json linters 51d08d8 Enable non-canonical Monad instance warnings for stage1/2 314bc99 ghc.mk: cleanup: use tab consistently d6512c7 ghc.mk: don't run mkUserGuidePart more than once 13ab2c6 ghc.mk: fix docs re-rebuilding 5f1e42f Allow to compile OSMem.c when MEM_NORESERVE is not available df67940 Make ghc.mk compatible with pedantic /bin/sh impls 986ceb1 Implement new `-fwarn-noncanonical-monoid-instances` 8b42214 Tweak use of AC_USE_SYSTEM_EXTENSIONS be92c28 Update hoopl submodule f5127c8 linters/check-cpp: Don't produce debug log 3ea4fb7 Documentation: escape characters in template-haskell Haddocks 42a5469 Ignore generated linter.log 3d55e41 ghc-pkg: Restore old behavior in colored version; fixes 6119 8cef8af Re-export data family when exporting a data instance without an export list 91e985c Minor stylistic fixes in glasgow_exts.rst 2110037 Add isImport, isDecl, and isStmt functions to GHC API d4bcd05 rts: Remove space before argument list in ASSERTs 700c42b Use TypeLits in the meta-data encoding of GHC.Generics 51a5e68 Refactor ConDecl 1bd40c8 Move checking for missing signatures to RnNames.reportUnusedNames 151c4b0 ghc-pkg: don't sort packages unnecessarily 04e1c27 rts: One more Clang-unfriendly CPP usage 9acb570 Change the superclass story (recursive superclasses) 821c043 Merge remote-tracking branch 'origin/master' into wip/T11067 54f42f7 Wibbles 807dc1f Manually update submodules to HEAD From git at git.haskell.org Tue Dec 8 17:24:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 8 Dec 2015 17:24:27 +0000 (UTC) Subject: [commit: ghc] branch 'wip/D1590' created Message-ID: <20151208172427.3785A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/D1590 Referencing: 83bf7b68371fd9849a91e5b2f79325a35d669ed9 From git at git.haskell.org Tue Dec 8 17:24:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 8 Dec 2015 17:24:29 +0000 (UTC) Subject: [commit: ghc] wip/D1590: Refactor GHCi Command type; allow "hidden" commands (83bf7b6) Message-ID: <20151208172429.D7BCE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/D1590 Link : http://ghc.haskell.org/trac/ghc/changeset/83bf7b68371fd9849a91e5b2f79325a35d669ed9/ghc >--------------------------------------------------------------- commit 83bf7b68371fd9849a91e5b2f79325a35d669ed9 Author: Herbert Valerio Riedel Date: Tue Dec 8 17:10:08 2015 +0100 Refactor GHCi Command type; allow "hidden" commands Summary: This transforms the 'Command' tuple into a record which is easier to extend. While at it, this refactoring turns the IDE `:complete` into a hidden command excluded from completion. The next obvious step is to add a summary text field for constructing the `:help` output (as well as allowing to get `:help ` for single commands. This is a preparatory refactoring for D1240 / #10874 Reviewers: bgamari, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1590 >--------------------------------------------------------------- 83bf7b68371fd9849a91e5b2f79325a35d669ed9 ghc/GhciMonad.hs | 20 ++++++++++++++++---- ghc/InteractiveUI.hs | 47 +++++++++++++++++++++++++++++++++-------------- 2 files changed, 49 insertions(+), 18 deletions(-) diff --git a/ghc/GhciMonad.hs b/ghc/GhciMonad.hs index c094b08..c1abe4f 100644 --- a/ghc/GhciMonad.hs +++ b/ghc/GhciMonad.hs @@ -14,7 +14,7 @@ module GhciMonad ( GHCi(..), startGHCi, GHCiState(..), setGHCiState, getGHCiState, modifyGHCiState, GHCiOption(..), isOptionSet, setOption, unsetOption, - Command, + Command(..), BreakLocation(..), TickArray, getDynFlags, @@ -58,9 +58,6 @@ import Control.Monad.IO.Class ----------------------------------------------------------------------------- -- GHCi monad --- the Bool means: True = we should exit GHCi (:quit) -type Command = (String, String -> InputT GHCi Bool, CompletionFunc GHCi) - data GHCiState = GHCiState { progname :: String, @@ -111,6 +108,21 @@ data GHCiState = GHCiState type TickArray = Array Int [(BreakIndex,SrcSpan)] +-- | A GHCi command +data Command + = Command + { cmdName :: String + -- ^ Name of GHCi command (e.g. "exit") + , cmdAction :: String -> InputT GHCi Bool + -- ^ The 'Bool' value denotes whether to exit GHCi + , cmdHidden :: Bool + -- ^ Commands which are excluded from default completion + -- and @:help@ summary. This is usually set for commands not + -- useful for interactive use but rather for IDEs. + , cmdCompletionFunc :: CompletionFunc GHCi + -- ^ 'CompletionFunc' for arguments + } + data GHCiOption = ShowTiming -- show time/allocs after evaluation | ShowType -- show the type of expressions diff --git a/ghc/InteractiveUI.hs b/ghc/InteractiveUI.hs index 7fd9c8b..0727d6b 100644 --- a/ghc/InteractiveUI.hs +++ b/ghc/InteractiveUI.hs @@ -130,13 +130,10 @@ ghciWelcomeMsg :: String ghciWelcomeMsg = "GHCi, version " ++ cProjectVersion ++ ": http://www.haskell.org/ghc/ :? for help" -cmdName :: Command -> String -cmdName (n,_,_) = n - GLOBAL_VAR(macros_ref, [], [Command]) ghciCommands :: [Command] -ghciCommands = [ +ghciCommands = map mkCmd [ -- Hugs users are accustomed to :e, so make sure it doesn't overlap ("?", keepGoing help, noCompletion), ("add", keepGoingPaths addModule, completeFilename), @@ -148,7 +145,6 @@ ghciCommands = [ ("cd", keepGoing' changeDirectory, completeFilename), ("check", keepGoing' checkModule, completeHomeModule), ("continue", keepGoing continueCmd, noCompletion), - ("complete", keepGoing completeCmd, noCompletion), ("cmd", keepGoing cmdCmd, completeExpression), ("ctags", keepGoing createCTagsWithLineNumbersCmd, completeFilename), ("ctags!", keepGoing createCTagsWithRegExesCmd, completeFilename), @@ -189,8 +185,21 @@ ghciCommands = [ ("trace", keepGoing traceCmd, completeExpression), ("undef", keepGoing undefineMacro, completeMacro), ("unset", keepGoing unsetOptions, completeSetOptions) + ] ++ map mkCmdHidden [ -- hidden commands + ("complete", keepGoing completeCmd) ] - + where + mkCmd (n,a,c) = Command { cmdName = n + , cmdAction = a + , cmdHidden = False + , cmdCompletionFunc = c + } + + mkCmdHidden (n,a) = Command { cmdName = n + , cmdAction = a + , cmdHidden = True + , cmdCompletionFunc = noCompletion + } -- We initialize readline (in the interactiveUI function) to use -- word_break_chars as the default set of completion word break characters. @@ -1019,7 +1028,7 @@ specialCommand str = do maybe_cmd <- lift $ lookupCommand cmd htxt <- short_help <$> getGHCiState case maybe_cmd of - GotCommand (_,f,_) -> f (dropWhile isSpace rest) + GotCommand cmd -> (cmdAction cmd) (dropWhile isSpace rest) BadCommand -> do liftIO $ hPutStr stdout ("unknown command ':" ++ cmd ++ "'\n" ++ htxt) @@ -1049,7 +1058,10 @@ lookupCommand' :: String -> GHCi (Maybe Command) lookupCommand' ":" = return Nothing lookupCommand' str' = do macros <- liftIO $ readIORef macros_ref - ghci_cmds <- ghci_commands `fmap` getGHCiState + ghci_cmds <- ghci_commands <$> getGHCiState + + let ghci_cmds_nohide = filter (not . cmdHidden) ghci_cmds + let (str, xcmds) = case str' of ':' : rest -> (rest, []) -- "::" selects a builtin command _ -> (str', macros) -- otherwise include macros in lookup @@ -1057,7 +1069,8 @@ lookupCommand' str' = do lookupExact s = find $ (s ==) . cmdName lookupPrefix s = find $ (s `isPrefixOf`) . cmdName - builtinPfxMatch = lookupPrefix str ghci_cmds + -- hidden commands can only be matched exact + builtinPfxMatch = lookupPrefix str ghci_cmds_nohide -- first, look for exact match (while preferring macros); then, look -- for first prefix match (preferring builtins), *unless* a macro @@ -1307,8 +1320,14 @@ defineMacro overwrite s = do new_expr = L (getLoc expr) $ ExprWithTySig body tySig hv <- GHC.compileParsedExpr new_expr - liftIO (writeIORef macros_ref -- later defined macros have precedence - ((macro_name, lift . runMacro hv, noCompletion) : filtered)) + let newCmd = Command { cmdName = macro_name + , cmdAction = lift . runMacro hv + , cmdHidden = False + , cmdCompletionFunc = noCompletion + } + + -- later defined macros have precedence + liftIO $ writeIORef macros_ref (newCmd : filtered) runMacro :: GHC.HValue{-String -> IO String-} -> String -> GHCi Bool runMacro fun s = do @@ -2533,14 +2552,14 @@ ghciCompleteWord line@(left,_) = case firstWord of lookupCompletion c = do maybe_cmd <- lookupCommand' c case maybe_cmd of - Just (_,_,f) -> return f - Nothing -> return completeFilename + Just cmd -> return (cmdCompletionFunc cmd) + Nothing -> return completeFilename completeGhciCommand = wrapCompleter " " $ \w -> do macros <- liftIO $ readIORef macros_ref cmds <- ghci_commands `fmap` getGHCiState let macro_names = map (':':) . map cmdName $ macros - let command_names = map (':':) . map cmdName $ cmds + let command_names = map (':':) . map cmdName $ filter (not . cmdHidden) cmds let{ candidates = case w of ':' : ':' : _ -> map (':':) command_names _ -> nub $ macro_names ++ command_names } From git at git.haskell.org Tue Dec 8 21:59:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 8 Dec 2015 21:59:34 +0000 (UTC) Subject: [commit: ghc] master: Refactor GHCi Command type; allow "hidden" commands (7997d6c) Message-ID: <20151208215934.D644B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7997d6c0f0ba4560dab799cd87850917e0df5e2f/ghc >--------------------------------------------------------------- commit 7997d6c0f0ba4560dab799cd87850917e0df5e2f Author: Herbert Valerio Riedel Date: Tue Dec 8 22:59:41 2015 +0100 Refactor GHCi Command type; allow "hidden" commands This transforms the 'Command' tuple into a record which is easier to extend. While at it, this refactoring turns the IDE `:complete` into a hidden command excluded from completion. The next obvious step is to add a summary text field for constructing the `:help` output (as well as allowing to get `:help ` for single commands. This is a preparatory refactoring for D1240 / #10874 Reviewed By: thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1590 >--------------------------------------------------------------- 7997d6c0f0ba4560dab799cd87850917e0df5e2f ghc/GhciMonad.hs | 20 ++++++++++++++++---- ghc/InteractiveUI.hs | 47 +++++++++++++++++++++++++++++++++-------------- 2 files changed, 49 insertions(+), 18 deletions(-) diff --git a/ghc/GhciMonad.hs b/ghc/GhciMonad.hs index c094b08..c1abe4f 100644 --- a/ghc/GhciMonad.hs +++ b/ghc/GhciMonad.hs @@ -14,7 +14,7 @@ module GhciMonad ( GHCi(..), startGHCi, GHCiState(..), setGHCiState, getGHCiState, modifyGHCiState, GHCiOption(..), isOptionSet, setOption, unsetOption, - Command, + Command(..), BreakLocation(..), TickArray, getDynFlags, @@ -58,9 +58,6 @@ import Control.Monad.IO.Class ----------------------------------------------------------------------------- -- GHCi monad --- the Bool means: True = we should exit GHCi (:quit) -type Command = (String, String -> InputT GHCi Bool, CompletionFunc GHCi) - data GHCiState = GHCiState { progname :: String, @@ -111,6 +108,21 @@ data GHCiState = GHCiState type TickArray = Array Int [(BreakIndex,SrcSpan)] +-- | A GHCi command +data Command + = Command + { cmdName :: String + -- ^ Name of GHCi command (e.g. "exit") + , cmdAction :: String -> InputT GHCi Bool + -- ^ The 'Bool' value denotes whether to exit GHCi + , cmdHidden :: Bool + -- ^ Commands which are excluded from default completion + -- and @:help@ summary. This is usually set for commands not + -- useful for interactive use but rather for IDEs. + , cmdCompletionFunc :: CompletionFunc GHCi + -- ^ 'CompletionFunc' for arguments + } + data GHCiOption = ShowTiming -- show time/allocs after evaluation | ShowType -- show the type of expressions diff --git a/ghc/InteractiveUI.hs b/ghc/InteractiveUI.hs index 7fd9c8b..0727d6b 100644 --- a/ghc/InteractiveUI.hs +++ b/ghc/InteractiveUI.hs @@ -130,13 +130,10 @@ ghciWelcomeMsg :: String ghciWelcomeMsg = "GHCi, version " ++ cProjectVersion ++ ": http://www.haskell.org/ghc/ :? for help" -cmdName :: Command -> String -cmdName (n,_,_) = n - GLOBAL_VAR(macros_ref, [], [Command]) ghciCommands :: [Command] -ghciCommands = [ +ghciCommands = map mkCmd [ -- Hugs users are accustomed to :e, so make sure it doesn't overlap ("?", keepGoing help, noCompletion), ("add", keepGoingPaths addModule, completeFilename), @@ -148,7 +145,6 @@ ghciCommands = [ ("cd", keepGoing' changeDirectory, completeFilename), ("check", keepGoing' checkModule, completeHomeModule), ("continue", keepGoing continueCmd, noCompletion), - ("complete", keepGoing completeCmd, noCompletion), ("cmd", keepGoing cmdCmd, completeExpression), ("ctags", keepGoing createCTagsWithLineNumbersCmd, completeFilename), ("ctags!", keepGoing createCTagsWithRegExesCmd, completeFilename), @@ -189,8 +185,21 @@ ghciCommands = [ ("trace", keepGoing traceCmd, completeExpression), ("undef", keepGoing undefineMacro, completeMacro), ("unset", keepGoing unsetOptions, completeSetOptions) + ] ++ map mkCmdHidden [ -- hidden commands + ("complete", keepGoing completeCmd) ] - + where + mkCmd (n,a,c) = Command { cmdName = n + , cmdAction = a + , cmdHidden = False + , cmdCompletionFunc = c + } + + mkCmdHidden (n,a) = Command { cmdName = n + , cmdAction = a + , cmdHidden = True + , cmdCompletionFunc = noCompletion + } -- We initialize readline (in the interactiveUI function) to use -- word_break_chars as the default set of completion word break characters. @@ -1019,7 +1028,7 @@ specialCommand str = do maybe_cmd <- lift $ lookupCommand cmd htxt <- short_help <$> getGHCiState case maybe_cmd of - GotCommand (_,f,_) -> f (dropWhile isSpace rest) + GotCommand cmd -> (cmdAction cmd) (dropWhile isSpace rest) BadCommand -> do liftIO $ hPutStr stdout ("unknown command ':" ++ cmd ++ "'\n" ++ htxt) @@ -1049,7 +1058,10 @@ lookupCommand' :: String -> GHCi (Maybe Command) lookupCommand' ":" = return Nothing lookupCommand' str' = do macros <- liftIO $ readIORef macros_ref - ghci_cmds <- ghci_commands `fmap` getGHCiState + ghci_cmds <- ghci_commands <$> getGHCiState + + let ghci_cmds_nohide = filter (not . cmdHidden) ghci_cmds + let (str, xcmds) = case str' of ':' : rest -> (rest, []) -- "::" selects a builtin command _ -> (str', macros) -- otherwise include macros in lookup @@ -1057,7 +1069,8 @@ lookupCommand' str' = do lookupExact s = find $ (s ==) . cmdName lookupPrefix s = find $ (s `isPrefixOf`) . cmdName - builtinPfxMatch = lookupPrefix str ghci_cmds + -- hidden commands can only be matched exact + builtinPfxMatch = lookupPrefix str ghci_cmds_nohide -- first, look for exact match (while preferring macros); then, look -- for first prefix match (preferring builtins), *unless* a macro @@ -1307,8 +1320,14 @@ defineMacro overwrite s = do new_expr = L (getLoc expr) $ ExprWithTySig body tySig hv <- GHC.compileParsedExpr new_expr - liftIO (writeIORef macros_ref -- later defined macros have precedence - ((macro_name, lift . runMacro hv, noCompletion) : filtered)) + let newCmd = Command { cmdName = macro_name + , cmdAction = lift . runMacro hv + , cmdHidden = False + , cmdCompletionFunc = noCompletion + } + + -- later defined macros have precedence + liftIO $ writeIORef macros_ref (newCmd : filtered) runMacro :: GHC.HValue{-String -> IO String-} -> String -> GHCi Bool runMacro fun s = do @@ -2533,14 +2552,14 @@ ghciCompleteWord line@(left,_) = case firstWord of lookupCompletion c = do maybe_cmd <- lookupCommand' c case maybe_cmd of - Just (_,_,f) -> return f - Nothing -> return completeFilename + Just cmd -> return (cmdCompletionFunc cmd) + Nothing -> return completeFilename completeGhciCommand = wrapCompleter " " $ \w -> do macros <- liftIO $ readIORef macros_ref cmds <- ghci_commands `fmap` getGHCiState let macro_names = map (':':) . map cmdName $ macros - let command_names = map (':':) . map cmdName $ cmds + let command_names = map (':':) . map cmdName $ filter (not . cmdHidden) cmds let{ candidates = case w of ':' : ':' : _ -> map (':':) command_names _ -> nub $ macro_names ++ command_names } From git at git.haskell.org Tue Dec 8 22:00:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 8 Dec 2015 22:00:16 +0000 (UTC) Subject: [commit: ghc] branch 'wip/D1590' deleted Message-ID: <20151208220016.5018F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/D1590 From git at git.haskell.org Tue Dec 8 22:01:14 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 8 Dec 2015 22:01:14 +0000 (UTC) Subject: [commit: ghc] master: Add missing whitespace in toArgs' error msg (31bddc4) Message-ID: <20151208220114.A46313A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/31bddc42c24726a82e221c68df043703caeb42f4/ghc >--------------------------------------------------------------- commit 31bddc42c24726a82e221c68df043703caeb42f4 Author: Herbert Valerio Riedel Date: Tue Dec 8 23:01:35 2015 +0100 Add missing whitespace in toArgs' error msg Differential Revision: https://phabricator.haskell.org/D1591 >--------------------------------------------------------------- 31bddc42c24726a82e221c68df043703caeb42f4 compiler/utils/Util.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/utils/Util.hs b/compiler/utils/Util.hs index 406ee9c..d3830c3 100644 --- a/compiler/utils/Util.hs +++ b/compiler/utils/Util.hs @@ -868,7 +868,7 @@ toArgs str | all isSpace spaces -> Right args _ -> - Left ("Couldn't read " ++ show str ++ "as [String]") + Left ("Couldn't read " ++ show str ++ " as [String]") s -> toArgs' s where toArgs' :: String -> Either String [String] @@ -899,7 +899,7 @@ toArgs str | all isSpace (take 1 rest) -> Right (arg, rest) _ -> - Left ("Couldn't read " ++ show s ++ "as String") + Left ("Couldn't read " ++ show s ++ " as String") {- -- ----------------------------------------------------------------------------- -- Floats From git at git.haskell.org Wed Dec 9 09:14:24 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 9 Dec 2015 09:14:24 +0000 (UTC) Subject: [commit: ghc] master: Fix DeriveAnyClass (Trac #9968) (af77089) Message-ID: <20151209091424.AF2823A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/af77089b08b60c00128f0e5a65d18211ea62dfee/ghc >--------------------------------------------------------------- commit af77089b08b60c00128f0e5a65d18211ea62dfee Author: Simon Peyton Jones Date: Wed Dec 9 09:07:46 2015 +0000 Fix DeriveAnyClass (Trac #9968) The main issue concerned things like data T a = MkT a deriving( C Int ) which is supposed to generate instance C Int (T a) where {} But the 'Int' argument (called cls_tys in the code) wasn't even being passed to inferConstraints and mk_data_eqn, so it really had no chance. DeriveAnyClass came along after this code was written! Anyway I did quite a bit of tidying up in inferConstraints. Also I discovered that this case was not covered at all data T a b = MkT a b deriving( Bifunctor ) What constraints should we generate for the instance context? We can deal with classes whose last arg has kind *, like Eq, Ord; or (* -> *), like Functor, Traversable. But we really don't have a story for classes whose last arg has kind (* -> * -> *). So I augmented checkSideConditions to check for that and give a sensible error message. ToDo: update the user manual. >--------------------------------------------------------------- af77089b08b60c00128f0e5a65d18211ea62dfee compiler/typecheck/TcDeriv.hs | 350 ++++++++++++--------- compiler/typecheck/TcGenDeriv.hs | 15 +- testsuite/tests/deriving/should_compile/T9968.hs | 7 + testsuite/tests/deriving/should_compile/all.T | 1 + testsuite/tests/deriving/should_fail/T9968a.hs | 8 + testsuite/tests/deriving/should_fail/T9968a.stderr | 6 + testsuite/tests/deriving/should_fail/all.T | 2 + 7 files changed, 232 insertions(+), 157 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc af77089b08b60c00128f0e5a65d18211ea62dfee From git at git.haskell.org Wed Dec 9 09:14:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 9 Dec 2015 09:14:27 +0000 (UTC) Subject: [commit: ghc] master: Comments only (e9ea020) Message-ID: <20151209091427.5821C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e9ea02092a748a72f8481b10f29464fe26658fb5/ghc >--------------------------------------------------------------- commit e9ea02092a748a72f8481b10f29464fe26658fb5 Author: Simon Peyton Jones Date: Wed Dec 9 09:08:47 2015 +0000 Comments only >--------------------------------------------------------------- e9ea02092a748a72f8481b10f29464fe26658fb5 compiler/types/FamInstEnv.hs | 9 ++++----- 1 file changed, 4 insertions(+), 5 deletions(-) diff --git a/compiler/types/FamInstEnv.hs b/compiler/types/FamInstEnv.hs index 8fde8c5..a60b1c2 100644 --- a/compiler/types/FamInstEnv.hs +++ b/compiler/types/FamInstEnv.hs @@ -345,9 +345,8 @@ Then we get a data type for each instance, and an axiom: axiom ax7 :: T Int ~ TInt -- Eta-reduced axiom ax8 a :: T Bool [a] ~ TBoolList a -These two axioms for T, one with one pattern, one with two. The reason -for this eta-reduction is decribed in TcInstDcls - Note [Eta reduction for data family axioms] +These two axioms for T, one with one pattern, one with two; +see Note [Eta reduction for data families] -} type FamInstEnv = UniqFM FamilyInstEnv -- Maps a family to its instances @@ -967,8 +966,8 @@ We handle data families and type families separately here: * For data family instances, though, we need to re-split for each instance, because the breakdown might be different for each - instance. Why? Because of eta reduction; see Note [Eta reduction - for data family axioms] in TcInstDcls. + instance. Why? Because of eta reduction; see + Note [Eta reduction for data families]. -} -- checks if one LHS is dominated by a list of other branches From git at git.haskell.org Wed Dec 9 12:40:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 9 Dec 2015 12:40:16 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: A few documentation fixes after 7.10.3 tag was cut (9b50b5a) Message-ID: <20151209124016.E27DA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/9b50b5a5da4325e703210b2de2d816debe4c8a64/ghc >--------------------------------------------------------------- commit 9b50b5a5da4325e703210b2de2d816debe4c8a64 Author: Ben Gamari Date: Tue Dec 8 19:47:57 2015 +0100 A few documentation fixes after 7.10.3 tag was cut Unfortunately there were a few issues with the documentation in the tagged 7.10.3 release. This fixes these. These changes will be in a 7.10.3a release which will serve as the primary source release for 7.10.3. >--------------------------------------------------------------- 9b50b5a5da4325e703210b2de2d816debe4c8a64 ANNOUNCE | 4 ++-- docs/users_guide/intro.xml | 1 + docs/users_guide/ug-ent.xml.in | 1 + 3 files changed, 4 insertions(+), 2 deletions(-) diff --git a/ANNOUNCE b/ANNOUNCE index 7812eba..0018b37 100644 --- a/ANNOUNCE +++ b/ANNOUNCE @@ -1,6 +1,6 @@ ============================================================== - The (Interactive) Glasgow Haskell Compiler -- version 7.10.2 + The (Interactive) Glasgow Haskell Compiler -- version 7.10.3 ============================================================== The GHC Team is pleased to announce a new minor release of GHC. This is a @@ -29,7 +29,7 @@ bug-fix release and contains a number of important fixes, A more thorough list of the changes in the release can be found in the release notes, - http://haskell.org/ghc/docs/7.10.2/html/users_guide/release-7-10-2.html + http://haskell.org/ghc/docs/7.10.3/html/users_guide/release-7-10-3.html How to get it diff --git a/docs/users_guide/intro.xml b/docs/users_guide/intro.xml index 3292334..fb7116e 100644 --- a/docs/users_guide/intro.xml +++ b/docs/users_guide/intro.xml @@ -309,6 +309,7 @@ &relnotes1; &relnotes2; +&relnotes3; diff --git a/docs/users_guide/ug-ent.xml.in b/docs/users_guide/ug-ent.xml.in index b696aad..3629e93 100644 --- a/docs/users_guide/ug-ent.xml.in +++ b/docs/users_guide/ug-ent.xml.in @@ -5,6 +5,7 @@ + From git at git.haskell.org Wed Dec 9 12:40:19 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 9 Dec 2015 12:40:19 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Release notes: Fix more incorrectness (072c5c9) Message-ID: <20151209124019.842BA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/072c5c9648b9f48b26100b0e433611ebd12b3947/ghc >--------------------------------------------------------------- commit 072c5c9648b9f48b26100b0e433611ebd12b3947 Author: Ben Gamari Date: Wed Dec 9 13:40:12 2015 +0100 Release notes: Fix more incorrectness Cabal fix was merged. >--------------------------------------------------------------- 072c5c9648b9f48b26100b0e433611ebd12b3947 docs/users_guide/7.10.3-notes.xml | 10 +--------- 1 file changed, 1 insertion(+), 9 deletions(-) diff --git a/docs/users_guide/7.10.3-notes.xml b/docs/users_guide/7.10.3-notes.xml index 120299a..90464a3 100644 --- a/docs/users_guide/7.10.3-notes.xml +++ b/docs/users_guide/7.10.3-notes.xml @@ -117,7 +117,7 @@ - The template Haskell getQ and + The Template Haskell getQ and putQ functions are fixed (having been broken since GHC 7.10.1, (Trac #10596). @@ -156,14 +156,6 @@ - At the time of release there is a fix - in the Cabal upstream respository, although it is not yet - present in a release. - - - - Unfortunately the fix for Trac #10375 required that support for the ARM Thumb instruction set be disabled. From git at git.haskell.org Wed Dec 9 13:42:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 9 Dec 2015 13:42:46 +0000 (UTC) Subject: [commit: ghc] master: Improve documentation for DeriveAnyClass (8317893) Message-ID: <20151209134246.41A263A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/83178931aa7e244b7c37860d03e2ab4a29d6a34e/ghc >--------------------------------------------------------------- commit 83178931aa7e244b7c37860d03e2ab4a29d6a34e Author: Simon Peyton Jones Date: Wed Dec 9 13:42:58 2015 +0000 Improve documentation for DeriveAnyClass c.f. Trac #9968 >--------------------------------------------------------------- 83178931aa7e244b7c37860d03e2ab4a29d6a34e docs/users_guide/glasgow_exts.rst | 60 +++++++++++++++++++++++++++++++++------ 1 file changed, 51 insertions(+), 9 deletions(-) diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index d313556..51ac12a 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -4489,13 +4489,12 @@ Deriving any other class ------------------------ With ``-XDeriveAnyClass`` you can derive any other class. The compiler -will simply generate an empty instance. The instance context will be -generated according to the same rules used when deriving ``Eq``. This is +will simply generate an instance declaration with no explicitly-defined +mathods. +This is mostly useful in classes whose `minimal set <#minimal-pragma>`__ is empty, and especially when writing -`generic functions <#generic-programming>`__. In case you try to derive some -class on a newtype, and ``-XGeneralizedNewtypeDeriving`` is also on, -``-XDeriveAnyClass`` takes precedence. +`generic functions <#generic-programming>`__. As an example, consider a simple pretty-printer class ``SPretty``, which outputs pretty strings: :: @@ -4522,8 +4521,47 @@ That is, an ``SPretty Foo`` instance will be created with empty implementations for all methods. Since we are using ``-XDefaultSignatures`` in this example, a default implementation of ``sPpr`` is filled in automatically. -Similarly, ``-XDeriveAnyClass`` can be used to fill in default instances for -associated type families: :: +Note the following details + +- In case you try to derive some + class on a newtype, and ``-XGeneralizedNewtypeDeriving`` is also on, + ``-XDeriveAnyClass`` takes precedence. + +- ``-XDeriveAnyClass`` is allowed only when the last argument of the class + has kind ``*`` or ``(* -> *)``. So this is not allowed: :: + + data T a b = MkT a b deriving( Bifunctor ) + + because the last argument of ``Bifunctor :: (* -> * -> *) -> Constraint`` + has the wrong kind. + +- The instance context will be generated according to the same rules + used when deriving ``Eq`` (if the kind of the type is ``*``), or + the rules for ``Functor`` (if the kind of the type is ``(* -> *)``). + For example :: + + instance C a => C (a,b) where ... + + data T a b = MkT a (a,b) deriving( C ) + + The ``deriving`` clause will generate :: + + instance C a => C (T a b) where {} + + The constraints `C a` and `C (a,b)` are generated from the data + constructor arguments, but the latter simplifies to `C a`. + +- ``-XDeriveAnyClass`` can be used with partially applied classes, + such as :: + + data T a = MKT a deriving( D Int ) + + which generates :: + + instance D Int a => D Int (T a) where {} + +- ``-XDeriveAnyClass`` can be used to fill in default instances for + associated type families: :: {-# LANGUAGE DeriveAnyClass, TypeFamilies #-} @@ -4536,8 +4574,12 @@ associated type families: :: doubleBarSize :: Size Bar -> Size Bar doubleBarSize s = 2*s -Since ``-XDeriveAnyClass`` does not generate an instance definition for ``Size -Bar``, it will default to ``Int``. + The ``deriving( Sizable )`` is equivalent to saying :: + + instance Sizeable Bar where {} + + and then the normal rules for filling in associated types from the + default will apply, making ``Size Bar`` equal to ``Int``. .. _type-class-extensions: From git at git.haskell.org Wed Dec 9 15:28:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 9 Dec 2015 15:28:54 +0000 (UTC) Subject: [commit: ghc] master: More typos in comments/docs (688069c) Message-ID: <20151209152854.B91C63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/688069ca83e949b9bde9883af7df26114e2f9bc0/ghc >--------------------------------------------------------------- commit 688069ca83e949b9bde9883af7df26114e2f9bc0 Author: Gabor Greif Date: Wed Dec 9 16:15:07 2015 +0100 More typos in comments/docs >--------------------------------------------------------------- 688069ca83e949b9bde9883af7df26114e2f9bc0 compiler/basicTypes/DataCon.hs | 2 +- compiler/hsSyn/HsExpr.hs | 2 +- compiler/main/GhcMake.hs | 2 +- compiler/typecheck/TcBinds.hs | 6 +++--- compiler/typecheck/TcDeriv.hs | 2 +- compiler/typecheck/TcForeign.hs | 2 +- compiler/typecheck/TcSMonad.hs | 2 +- compiler/types/Type.hs | 2 +- docs/users_guide/glasgow_exts.rst | 2 +- libraries/base/GHC/IO/Encoding/Types.hs | 2 +- testsuite/tests/safeHaskell/check/all.T | 4 ++-- testsuite/tests/typecheck/should_compile/T9708.hs | 2 +- testsuite/tests/typecheck/should_fail/ContextStack2.hs | 2 +- 13 files changed, 16 insertions(+), 16 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 688069ca83e949b9bde9883af7df26114e2f9bc0 From git at git.haskell.org Wed Dec 9 16:14:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 9 Dec 2015 16:14:00 +0000 (UTC) Subject: [commit: ghc] wip/T11067: Manually update terminfo and containers to HEAD (7d755ad) Message-ID: <20151209161400.3ABD43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T11067 Link : http://ghc.haskell.org/trac/ghc/changeset/7d755adaf1b7715d7f656d1effec73c75291f31a/ghc >--------------------------------------------------------------- commit 7d755adaf1b7715d7f656d1effec73c75291f31a Author: Simon Peyton Jones Date: Tue Dec 8 17:09:56 2015 +0000 Manually update terminfo and containers to HEAD ...and transformers >--------------------------------------------------------------- 7d755adaf1b7715d7f656d1effec73c75291f31a libraries/containers | 2 +- libraries/terminfo | 2 +- libraries/transformers | 2 +- 3 files changed, 3 insertions(+), 3 deletions(-) diff --git a/libraries/containers b/libraries/containers index 924fafe..6405653 160000 --- a/libraries/containers +++ b/libraries/containers @@ -1 +1 @@ -Subproject commit 924fafe1030301ee1d62d7acd576e86b50251157 +Subproject commit 6405653480afa675eec804616547b8625244bc7c diff --git a/libraries/terminfo b/libraries/terminfo index 68e88c4..15ca1cb 160000 --- a/libraries/terminfo +++ b/libraries/terminfo @@ -1 +1 @@ -Subproject commit 68e88c453237763084f5032d133ee7347980f8b2 +Subproject commit 15ca1cb3b1e1b0d410544abd69e7ffcf727fc970 diff --git a/libraries/transformers b/libraries/transformers index 5ccb747..34fba39 160000 --- a/libraries/transformers +++ b/libraries/transformers @@ -1 +1 @@ -Subproject commit 5ccb747e67d579e3f212fd3526469c35282e532e +Subproject commit 34fba39b1279936a739ca8857e9592cc9a44c34e From git at git.haskell.org Wed Dec 9 16:14:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 9 Dec 2015 16:14:03 +0000 (UTC) Subject: [commit: ghc] wip/T11067: Implement recursive superclasses (643397a) Message-ID: <20151209161403.627123A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T11067 Link : http://ghc.haskell.org/trac/ghc/changeset/643397a09f6e08a97dc104db3b1fd3cb8fa06770/ghc >--------------------------------------------------------------- commit 643397a09f6e08a97dc104db3b1fd3cb8fa06770 Author: Simon Peyton Jones Date: Wed Dec 9 16:13:36 2015 +0000 Implement recursive superclasses This finishes it up except for docs >--------------------------------------------------------------- 643397a09f6e08a97dc104db3b1fd3cb8fa06770 compiler/typecheck/TcCanonical.hs | 82 +++++++++------- compiler/typecheck/TcErrors.hs | 82 +++++++++++----- compiler/typecheck/TcRnTypes.hs | 10 +- compiler/typecheck/TcSimplify.hs | 5 +- compiler/typecheck/TcTyClsDecls.hs | 12 --- compiler/typecheck/TcTyDecls.hs | 24 +++-- compiler/typecheck/TcType.hs | 29 +++++- compiler/utils/Bag.hs | 1 - testsuite/tests/driver/T4437.hs | 2 +- .../tests/indexed-types/should_compile/T11067.hs | 35 +++++++ .../indexed-types/should_compile/T3208b.stderr | 10 -- testsuite/tests/indexed-types/should_compile/all.T | 1 + .../tests/indexed-types/should_fail/T1897b.stderr | 22 ++--- .../tests/indexed-types/should_fail/T3330a.stderr | 18 ---- .../tests/indexed-types/should_fail/T4174.stderr | 16 ---- .../tests/indexed-types/should_fail/T8227.stderr | 35 +++---- .../tests/indexed-types/should_fail/T9662.stderr | 80 +++------------- testsuite/tests/module/mod40.stderr | 2 + .../should_compile/ExtraConstraints3.stderr | 14 +-- .../WarningWildcardInstantiations.stderr | 3 +- .../InstantiatedNamedWildcardsInConstraints.stderr | 2 +- .../should_fail/WildcardInstantiations.stderr | 3 +- testsuite/tests/pmcheck/should_compile/T3927b.hs | 1 + .../tests/pmcheck/should_compile/T3927b.stderr | 7 +- testsuite/tests/polykinds/T7332.hs | 3 +- .../tests/simplCore/should_compile/T4398.stderr | 18 +++- testsuite/tests/typecheck/should_compile/T11067.hs | 33 +++++++ .../tests/typecheck/should_compile/T9834.stderr | 105 ++++++++------------- .../tests/typecheck/should_compile/T9939.stderr | 13 ++- testsuite/tests/typecheck/should_fail/T2714.stderr | 35 +++---- testsuite/tests/typecheck/should_fail/T7869.stderr | 43 +++------ testsuite/tests/typecheck/should_fail/T8883.stderr | 2 +- testsuite/tests/typecheck/should_fail/T9415.stderr | 2 + testsuite/tests/typecheck/should_fail/T9739.stderr | 2 + .../tests/typecheck/should_fail/tcfail027.stderr | 2 + 35 files changed, 378 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 643397a09f6e08a97dc104db3b1fd3cb8fa06770 From git at git.haskell.org Wed Dec 9 17:40:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 9 Dec 2015 17:40:07 +0000 (UTC) Subject: [commit: ghc] wip/T11067: Documentation (b6a71da) Message-ID: <20151209174007.26F623A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T11067 Link : http://ghc.haskell.org/trac/ghc/changeset/b6a71da37ad783bccee2739593b9692aa94a078d/ghc >--------------------------------------------------------------- commit b6a71da37ad783bccee2739593b9692aa94a078d Author: Simon Peyton Jones Date: Wed Dec 9 17:38:41 2015 +0000 Documentation >--------------------------------------------------------------- b6a71da37ad783bccee2739593b9692aa94a078d docs/users_guide/glasgow_exts.rst | 37 +++++++++++++++++++++++++++++++++++++ 1 file changed, 37 insertions(+) diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index 4fc02f6..54f4c94 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -5873,6 +5873,43 @@ to subsume the ``OverloadedStrings`` extension (currently, as a special case, string literals benefit from statically allocated compact representation). +Recursive superclasses +---------------------- + +A class cannot generally have itself as a superclass. So this is illegal :: + + class C a => D a where ... + class D a => C a where ... + +GHC implements this test conservatively when type functions are involved. +For example :: + + type family F a :: Constraint + class F a => C a where ... + +GHC will complain about this, because you might later add :: + + type instance F Int = C Int + +and now we'd be in a superclass loop. + +However recursive superclasses are sometimes useful. Here's a real-life +example (Trac #10318) :: + + class (Frac (Frac a) ~ Frac a, + Fractional (Frac a), + IntegralDomain (Frac a)) + => IntegralDomain a where + type Frac a :: * + +Here the superclass cycle does terminate but it's not entirely straightforward +to see that it does. + +With the language extension ``-XRecursiveSuperClasses`` GHC will allow these +class declarations. If there really *is* a loop, GHC will only +expand it to finite depth. + + .. _type-families: Type families From git at git.haskell.org Thu Dec 10 10:16:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 10 Dec 2015 10:16:01 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #11192 (602889a) Message-ID: <20151210101601.C69403A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/602889aa23daecc21caaecb99ae8b055bca191f6/ghc >--------------------------------------------------------------- commit 602889aa23daecc21caaecb99ae8b055bca191f6 Author: Simon Peyton Jones Date: Thu Dec 10 10:15:16 2015 +0000 Test Trac #11192 >--------------------------------------------------------------- 602889aa23daecc21caaecb99ae8b055bca191f6 .../tests/partial-sigs/should_compile/T11192.hs | 15 ++++++++ .../partial-sigs/should_compile/T11192.stderr | 44 ++++++++++++++++++++++ testsuite/tests/partial-sigs/should_compile/all.T | 1 + 3 files changed, 60 insertions(+) diff --git a/testsuite/tests/partial-sigs/should_compile/T11192.hs b/testsuite/tests/partial-sigs/should_compile/T11192.hs new file mode 100644 index 0000000..fb27a35 --- /dev/null +++ b/testsuite/tests/partial-sigs/should_compile/T11192.hs @@ -0,0 +1,15 @@ +{-# LANGUAGE PartialTypeSignatures #-} + +module T11192 where + +fails :: a +fails = + let go :: _ + go 0 a = a + in go (0 :: Int) undefined + +succeeds :: a +succeeds = + let go :: _ + go _ a = a + in go (0 :: Int) undefined diff --git a/testsuite/tests/partial-sigs/should_compile/T11192.stderr b/testsuite/tests/partial-sigs/should_compile/T11192.stderr new file mode 100644 index 0000000..2fac5eb --- /dev/null +++ b/testsuite/tests/partial-sigs/should_compile/T11192.stderr @@ -0,0 +1,44 @@ + +T11192.hs:7:14: warning: + ? Found type wildcard ?_? standing for ?Int -> t -> t? + Where: ?t? is a rigid type variable bound by + the inferred type of go :: Int -> t -> t at T11192.hs:8:8 + ? In the type signature: + go :: _ + In the expression: + let + go :: _ + go 0 a = a + in go (0 :: Int) undefined + In an equation for ?fails?: + fails + = let + go :: _ + go 0 a = a + in go (0 :: Int) undefined + ? Relevant bindings include + go :: Int -> t -> t (bound at T11192.hs:8:8) + fails :: a (bound at T11192.hs:6:1) + +T11192.hs:13:14: warning: + ? Found type wildcard ?_? standing for ?t -> t1 -> t1? + Where: ?t? is a rigid type variable bound by + the inferred type of go :: t -> t1 -> t1 at T11192.hs:14:8 + ?t1? is a rigid type variable bound by + the inferred type of go :: t -> t1 -> t1 at T11192.hs:14:8 + ? In the type signature: + go :: _ + In the expression: + let + go :: _ + go _ a = a + in go (0 :: Int) undefined + In an equation for ?succeeds?: + succeeds + = let + go :: _ + go _ a = a + in go (0 :: Int) undefined + ? Relevant bindings include + go :: t -> t1 -> t1 (bound at T11192.hs:14:8) + succeeds :: a (bound at T11192.hs:12:1) diff --git a/testsuite/tests/partial-sigs/should_compile/all.T b/testsuite/tests/partial-sigs/should_compile/all.T index 5567ef1..caa8934 100644 --- a/testsuite/tests/partial-sigs/should_compile/all.T +++ b/testsuite/tests/partial-sigs/should_compile/all.T @@ -58,3 +58,4 @@ test('T10519', normal, compile, ['']) test('T10463', normal, compile, ['']) test('ExprSigLocal', normal, compile, ['']) test('T11016', normal, compile, ['']) +test('T11192', normal, compile, ['']) From git at git.haskell.org Thu Dec 10 10:54:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 10 Dec 2015 10:54:54 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #11187 (f4f00c0) Message-ID: <20151210105454.35D7A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f4f00c0f28f3c21eb6f1396f48058c430c4e9b30/ghc >--------------------------------------------------------------- commit f4f00c0f28f3c21eb6f1396f48058c430c4e9b30 Author: Simon Peyton Jones Date: Thu Dec 10 10:55:10 2015 +0000 Test Trac #11187 >--------------------------------------------------------------- f4f00c0f28f3c21eb6f1396f48058c430c4e9b30 testsuite/tests/indexed-types/should_compile/T11187.hs | 18 ++++++++++++++++++ testsuite/tests/indexed-types/should_compile/all.T | 1 + 2 files changed, 19 insertions(+) diff --git a/testsuite/tests/indexed-types/should_compile/T11187.hs b/testsuite/tests/indexed-types/should_compile/T11187.hs new file mode 100644 index 0000000..4f636a6 --- /dev/null +++ b/testsuite/tests/indexed-types/should_compile/T11187.hs @@ -0,0 +1,18 @@ +{-# LANGUAGE TypeFamilies #-} +{-# OPTIONS_GHC -fno-warn-redundant-constraints #-} + +module T11187 where +import Data.Type.Coercion + +type family X + +coercionXX :: Coercion X X +coercionXX = Coercion + +coercionXX1 :: Coercion X X +coercionXX1 = c where + c :: x ~ X => Coercion x x + c = Coercion + +coercionXX2 :: Coercion X X +coercionXX2 = c where c = Coercion diff --git a/testsuite/tests/indexed-types/should_compile/all.T b/testsuite/tests/indexed-types/should_compile/all.T index 39b8a3a..5de25bf 100644 --- a/testsuite/tests/indexed-types/should_compile/all.T +++ b/testsuite/tests/indexed-types/should_compile/all.T @@ -265,3 +265,4 @@ test('T10753', normal, compile, ['']) test('T10806', normal, compile_fail, ['']) test('T10815', normal, compile, ['']) test('T10931', normal, compile, ['']) +test('T11187', normal, compile, ['']) From git at git.haskell.org Fri Dec 11 12:53:56 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 11 Dec 2015 12:53:56 +0000 (UTC) Subject: [commit: ghc] tag 'ghc-7.10.3a-release' created Message-ID: <20151211125356.C4A753A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New tag : ghc-7.10.3a-release Referencing: 1d6bf410c1b8fdc831f2995d7527ae5bd26179f3 From git at git.haskell.org Fri Dec 11 18:11:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 11 Dec 2015 18:11:57 +0000 (UTC) Subject: [commit: ghc] master: Make sure PatSyns only get added once to tcg_patsyns (41ef8f7) Message-ID: <20151211181157.861833A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/41ef8f70819e9b99aacc6d81019e5a33a63dfeab/ghc >--------------------------------------------------------------- commit 41ef8f70819e9b99aacc6d81019e5a33a63dfeab Author: Matthew Pickering Date: Fri Dec 11 18:10:45 2015 +0000 Make sure PatSyns only get added once to tcg_patsyns Summary: Before, `PatSyn`s were getting added twice to `tcg_patsyns` so when inspecting afterwards there were duplicates in the list. This makes sure that only they only get added once. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1597 >--------------------------------------------------------------- 41ef8f70819e9b99aacc6d81019e5a33a63dfeab compiler/typecheck/TcBinds.hs | 8 +++----- compiler/typecheck/TcPatSyn.hs | 10 +++++----- compiler/typecheck/TcPatSyn.hs-boot | 7 +++---- 3 files changed, 11 insertions(+), 14 deletions(-) diff --git a/compiler/typecheck/TcBinds.hs b/compiler/typecheck/TcBinds.hs index 673109b..1254b78 100644 --- a/compiler/typecheck/TcBinds.hs +++ b/compiler/typecheck/TcBinds.hs @@ -49,7 +49,6 @@ import NameSet import NameEnv import SrcLoc import Bag -import PatSyn import ListSetOps import ErrUtils import Digraph @@ -483,13 +482,12 @@ tc_single :: forall thing. -> LHsBind Name -> TcM thing -> TcM (LHsBinds TcId, thing) tc_single _top_lvl sig_fn _prag_fn (L _ (PatSynBind psb at PSB{ psb_id = L _ name })) thing_inside - = do { (pat_syn, aux_binds, tcg_env) <- tc_pat_syn_decl - ; let tything = AConLike (PatSynCon pat_syn) - ; thing <- setGblEnv tcg_env $ tcExtendGlobalEnv [tything] thing_inside + = do { (aux_binds, tcg_env) <- tc_pat_syn_decl + ; thing <- setGblEnv tcg_env thing_inside ; return (aux_binds, thing) } where - tc_pat_syn_decl :: TcM (PatSyn, LHsBinds TcId, TcGblEnv) + tc_pat_syn_decl :: TcM (LHsBinds TcId, TcGblEnv) tc_pat_syn_decl = case sig_fn name of Nothing -> tcInferPatSynDecl psb Just (TcPatSynSig tpsi) -> tcCheckPatSynDecl psb tpsi diff --git a/compiler/typecheck/TcPatSyn.hs b/compiler/typecheck/TcPatSyn.hs index 30dcbf7..69eeef0 100644 --- a/compiler/typecheck/TcPatSyn.hs +++ b/compiler/typecheck/TcPatSyn.hs @@ -61,7 +61,7 @@ import Control.Monad (forM) -} tcInferPatSynDecl :: PatSynBind Name Name - -> TcM (PatSyn, LHsBinds Id, TcGblEnv) + -> TcM (LHsBinds Id, TcGblEnv) tcInferPatSynDecl PSB{ psb_id = lname@(L loc name), psb_args = details, psb_def = lpat, psb_dir = dir } = setSrcSpan loc $ @@ -96,7 +96,7 @@ tcInferPatSynDecl PSB{ psb_id = lname@(L loc name), psb_args = details, tcCheckPatSynDecl :: PatSynBind Name Name -> TcPatSynInfo - -> TcM (PatSyn, LHsBinds Id, TcGblEnv) + -> TcM (LHsBinds Id, TcGblEnv) tcCheckPatSynDecl PSB{ psb_id = lname@(L loc name), psb_args = details, psb_def = lpat, psb_dir = dir } TPSI{ patsig_tau = tau, @@ -163,7 +163,7 @@ tcCheckPatSynDecl PSB{ psb_id = lname@(L loc name), psb_args = details, (univ_tvs, req_theta, req_ev_binds, req_dicts) (ex_tvs, ex_tys, prov_theta, prov_ev_binds, prov_dicts) wrapped_args - pat_ty rec_fields } + pat_ty rec_fields } where (arg_tys, pat_ty) = tcSplitFunTys tau @@ -199,7 +199,7 @@ tc_patsyn_finish :: Located Name -- ^ PatSyn Name -> TcType -- ^ Pattern type -> [Name] -- ^ Selector names -- ^ Whether fields, empty if not record PatSyn - -> TcM (PatSyn, LHsBinds Id, TcGblEnv) + -> TcM (LHsBinds Id, TcGblEnv) tc_patsyn_finish lname dir is_infix lpat' (univ_tvs, req_theta, req_ev_binds, req_dicts) (ex_tvs, subst, prov_theta, prov_ev_binds, prov_dicts) @@ -262,7 +262,7 @@ tc_patsyn_finish lname dir is_infix lpat' tcRecSelBinds (ValBindsOut (zip (repeat NonRecursive) selector_binds) sigs) - ; return (patSyn, matcher_bind, tcg_env) } + ; return (matcher_bind, tcg_env) } where zonk_wrapped_arg :: (Var, HsWrapper) -> TcM (Var, HsWrapper) diff --git a/compiler/typecheck/TcPatSyn.hs-boot b/compiler/typecheck/TcPatSyn.hs-boot index 61f7958..11c1bc1 100644 --- a/compiler/typecheck/TcPatSyn.hs-boot +++ b/compiler/typecheck/TcPatSyn.hs-boot @@ -4,16 +4,15 @@ import Name ( Name ) import Id ( Id ) import HsSyn ( PatSynBind, LHsBinds ) import TcRnTypes ( TcM, TcPatSynInfo ) -import PatSyn ( PatSyn ) -import TcRnMonad ( TcGblEnv ) +import TcRnMonad ( TcGblEnv) import Outputable ( Outputable ) tcInferPatSynDecl :: PatSynBind Name Name - -> TcM (PatSyn, LHsBinds Id, TcGblEnv) + -> TcM (LHsBinds Id, TcGblEnv) tcCheckPatSynDecl :: PatSynBind Name Name -> TcPatSynInfo - -> TcM (PatSyn, LHsBinds Id, TcGblEnv) + -> TcM (LHsBinds Id, TcGblEnv) tcPatSynBuilderBind :: PatSynBind Name Name -> TcM (LHsBinds Id) From git at git.haskell.org Fri Dec 11 20:49:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 11 Dec 2015 20:49:39 +0000 (UTC) Subject: [commit: ghc] master: T7478: Don't expect broken on Darwin (f7c17c8) Message-ID: <20151211204939.2C7733A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f7c17c84f7dd8f2f1ddbfd7c5bdc3d918f25ea4d/ghc >--------------------------------------------------------------- commit f7c17c84f7dd8f2f1ddbfd7c5bdc3d918f25ea4d Author: Ben Gamari Date: Fri Dec 11 21:48:02 2015 +0100 T7478: Don't expect broken on Darwin This appears to be fixed as noted by goldfire on #7478 and my own experience. >--------------------------------------------------------------- f7c17c84f7dd8f2f1ddbfd7c5bdc3d918f25ea4d testsuite/tests/ghc-api/T7478/all.T | 1 - 1 file changed, 1 deletion(-) diff --git a/testsuite/tests/ghc-api/T7478/all.T b/testsuite/tests/ghc-api/T7478/all.T index b3a69a8..01d2dc0 100644 --- a/testsuite/tests/ghc-api/T7478/all.T +++ b/testsuite/tests/ghc-api/T7478/all.T @@ -1,7 +1,6 @@ test('T7478', [ unless(have_dynamic(),skip) , extra_clean(['A','A.exe','B.o','B.hi','C.o','C.hi']) - , when(opsys('darwin'), expect_broken(8294)) ], run_command, ['$MAKE -s --no-print-directory T7478']) From git at git.haskell.org Fri Dec 11 21:11:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 11 Dec 2015 21:11:25 +0000 (UTC) Subject: [commit: ghc] master: Mark retc001 as broken on Darwin (5447c20) Message-ID: <20151211211125.92A613A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5447c20e5d9d4e968df91f538ca942807dc46a53/ghc >--------------------------------------------------------------- commit 5447c20e5d9d4e968df91f538ca942807dc46a53 Author: Ben Gamari Date: Fri Dec 11 23:09:43 2015 +0200 Mark retc001 as broken on Darwin Due to #11204. A relatively easy fix would be to add a one second delay as described in the ticket, but this seems terrible. >--------------------------------------------------------------- 5447c20e5d9d4e968df91f538ca942807dc46a53 testsuite/tests/driver/retc001/all.T | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/driver/retc001/all.T b/testsuite/tests/driver/retc001/all.T index 7e5fda5..7e7c59a 100644 --- a/testsuite/tests/driver/retc001/all.T +++ b/testsuite/tests/driver/retc001/all.T @@ -1,5 +1,6 @@ test('retc001', - [clean_cmd('$MAKE -s clean')], + [clean_cmd('$MAKE -s clean'), + when(opsys('darwin'), expect_broken(11204))], run_command, ['$MAKE -s --no-print-directory retc001']) From git at git.haskell.org Fri Dec 11 21:19:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 11 Dec 2015 21:19:27 +0000 (UTC) Subject: [commit: ghc] master: T4801: Update expected allocations on Darwin (262954c) Message-ID: <20151211211927.91D5F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/262954c2b2de95c06ae796522dbcda4d34f00531/ghc >--------------------------------------------------------------- commit 262954c2b2de95c06ae796522dbcda4d34f00531 Author: Ben Gamari Date: Fri Dec 11 22:19:44 2015 +0100 T4801: Update expected allocations on Darwin >--------------------------------------------------------------- 262954c2b2de95c06ae796522dbcda4d34f00531 testsuite/tests/perf/compiler/all.T | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index fb52076..620a62c 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -212,8 +212,9 @@ test('T4801', # # 2014-10-13: 48 stricter seqDmdType compiler_stats_num_field('bytes allocated', - [(platform('x86_64-apple-darwin'), 434058304, 5), - # expected value: 510938976 (amd64/OS X): + [(platform('x86_64-apple-darwin'), 465653312, 10), + # prev: 510938976 (amd64/OS X): + # 2015-12-11: 465653312 (amd64/OS X) Update, bump tolerance to +/-10% (wordsize(32), 203962148, 10), # prev: 185669232 (x86/OSX) From git at git.haskell.org Fri Dec 11 22:17:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 11 Dec 2015 22:17:21 +0000 (UTC) Subject: [commit: ghc] master: Removed colon append operation (fixes #10785) (c205aeb) Message-ID: <20151211221721.B60463A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c205aebda7005744a5bbe44c11f37e98242145fa/ghc >--------------------------------------------------------------- commit c205aebda7005744a5bbe44c11f37e98242145fa Author: Ben Gamari Date: Fri Dec 11 22:36:15 2015 +0100 Removed colon append operation (fixes #10785) Reviewers: jgertm, austin, thomie Reviewed By: thomie Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1164 GHC Trac Issues: #10785 >--------------------------------------------------------------- c205aebda7005744a5bbe44c11f37e98242145fa testsuite/tests/cabal/T1750.stdout | 2 +- testsuite/tests/cabal/ghcpkg01.stdout | 6 +++--- testsuite/tests/cabal/ghcpkg05.stdout | 4 ++-- testsuite/tests/cabal/shadow.stdout | 8 ++++---- testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout | 8 ++++---- utils/ghc-pkg/Main.hs | 6 +++--- 6 files changed, 17 insertions(+), 17 deletions(-) diff --git a/testsuite/tests/cabal/T1750.stdout b/testsuite/tests/cabal/T1750.stdout index 62d0323..72d1cf6 100644 --- a/testsuite/tests/cabal/T1750.stdout +++ b/testsuite/tests/cabal/T1750.stdout @@ -1,4 +1,4 @@ -localT1750.package.conf: +localT1750.package.conf {T1750A-1} {T1750B-1} diff --git a/testsuite/tests/cabal/ghcpkg01.stdout b/testsuite/tests/cabal/ghcpkg01.stdout index c056cf9..d7b35b7 100644 --- a/testsuite/tests/cabal/ghcpkg01.stdout +++ b/testsuite/tests/cabal/ghcpkg01.stdout @@ -1,4 +1,4 @@ -local01.package.conf: +local01.package.conf (no packages) Reading package info from "test.pkg" ... done. name: testpkg @@ -55,7 +55,7 @@ pkgroot: import-dirs: /usr/local/lib/testpkg "c:/Program Files/testpkg" Reading package info from "test2.pkg" ... done. -local01.package.conf: +local01.package.conf testpkg-1.2.3.4 (testpkg-2.0) @@ -170,6 +170,6 @@ hs-libraries: testpkg-1.2.3.4-XXX include-dirs: /usr/local/include/testpkg "c:/Program Files/testpkg" pkgroot: -local01.package.conf: +local01.package.conf (no packages) Reading package info from "test3.pkg" ... done. diff --git a/testsuite/tests/cabal/ghcpkg05.stdout b/testsuite/tests/cabal/ghcpkg05.stdout index f89d332..980139d 100644 --- a/testsuite/tests/cabal/ghcpkg05.stdout +++ b/testsuite/tests/cabal/ghcpkg05.stdout @@ -1,6 +1,6 @@ -local05a.package.conf: +local05a.package.conf (testpkg-2.0) -local05b.package.conf: +local05b.package.conf (testpkg-3.0) diff --git a/testsuite/tests/cabal/shadow.stdout b/testsuite/tests/cabal/shadow.stdout index bdd2459..a47ce15 100644 --- a/testsuite/tests/cabal/shadow.stdout +++ b/testsuite/tests/cabal/shadow.stdout @@ -1,17 +1,17 @@ databases 1 and 2: -localshadow1.package.conf: +localshadow1.package.conf (shadow-1) (shadowdep-1) -localshadow2.package.conf: +localshadow2.package.conf (shadow-1) databases 1 and 3: -localshadow1.package.conf: +localshadow1.package.conf (shadow-1) (shadowdep-1) -localshadow3.package.conf: +localshadow3.package.conf (shadow-1) should FAIL: diff --git a/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout b/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout index 42e1778..59886cd 100644 --- a/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout +++ b/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout @@ -1,4 +1,4 @@ -pdb.safePkg01/local.db: +pdb.safePkg01/local.db safePkg01-1.0 trusted: False @@ -29,17 +29,17 @@ trusted: safe require own pkg trusted: True M_SafePkg6 -package dependencies: array-0.5.1.0 base-4.9.0.0* bytestring-0.10.7.0* deepseq-1.4.1.1 ghc-prim-0.5.0.0 integer-gmp-1.0.0.0 +package dependencies: array-0.5.1.0 base-4.9.0.0* bytestring-0.10.7.0* deepseq-1.4.2.0 ghc-prim-0.5.0.0 integer-gmp-1.0.0.0 trusted: trustworthy require own pkg trusted: False M_SafePkg7 -package dependencies: array-0.5.1.0 base-4.9.0.0* bytestring-0.10.7.0* deepseq-1.4.1.1 ghc-prim-0.5.0.0 integer-gmp-1.0.0.0 +package dependencies: array-0.5.1.0 base-4.9.0.0* bytestring-0.10.7.0* deepseq-1.4.2.0 ghc-prim-0.5.0.0 integer-gmp-1.0.0.0 trusted: safe require own pkg trusted: False M_SafePkg8 -package dependencies: array-0.5.1.0 base-4.9.0.0 bytestring-0.10.7.0* deepseq-1.4.1.1 ghc-prim-0.5.0.0 integer-gmp-1.0.0.0 +package dependencies: array-0.5.1.0 base-4.9.0.0 bytestring-0.10.7.0* deepseq-1.4.2.0 ghc-prim-0.5.0.0 integer-gmp-1.0.0.0 trusted: trustworthy require own pkg trusted: False diff --git a/utils/ghc-pkg/Main.hs b/utils/ghc-pkg/Main.hs index 2820f70..b302810 100644 --- a/utils/ghc-pkg/Main.hs +++ b/utils/ghc-pkg/Main.hs @@ -1241,7 +1241,7 @@ listPackages verbosity my_flags mPackageName mModuleName = do broken = map installedComponentId (brokenPackages pkg_map) show_normal PackageDB{ location = db_name, packages = pkg_confs } = - do hPutStrLn stdout (db_name ++ ":") + do hPutStrLn stdout db_name if null pkg_confs then hPutStrLn stdout " (no packages)" else hPutStrLn stdout $ unlines (map (" " ++) (map pp_pkg pkg_confs)) @@ -1273,8 +1273,8 @@ listPackages verbosity my_flags mPackageName mModuleName = do then termText (location db) <#> termText "\n (no packages)\n" else mconcat $ map (<#> termText "\n") $ - (termText (location db) : - map (termText " " <#>) (map pp_pkg pkg_confs)) + (termText (location db) + : map (termText " " <#>) (map pp_pkg pkg_confs)) where pp_pkg p | installedComponentId p `elem` broken = withF Red doc From git at git.haskell.org Fri Dec 11 22:17:24 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 11 Dec 2015 22:17:24 +0000 (UTC) Subject: [commit: ghc] master: Improved data family export documentation (b138248) Message-ID: <20151211221724.5E1073A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b1382481ac14a9f8999321581eaf88148bd44415/ghc >--------------------------------------------------------------- commit b1382481ac14a9f8999321581eaf88148bd44415 Author: David Kraeutmann Date: Fri Dec 11 22:36:55 2015 +0100 Improved data family export documentation Reviewers: simonpj, austin, bgamari Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1587 GHC Trac Issues: #11164 >--------------------------------------------------------------- b1382481ac14a9f8999321581eaf88148bd44415 compiler/rename/RnNames.hs | 5 +++-- docs/users_guide/glasgow_exts.rst | 5 +++++ 2 files changed, 8 insertions(+), 2 deletions(-) diff --git a/compiler/rename/RnNames.hs b/compiler/rename/RnNames.hs index d61c299..0024304 100644 --- a/compiler/rename/RnNames.hs +++ b/compiler/rename/RnNames.hs @@ -1223,8 +1223,9 @@ exports_from_avail Nothing rdr_env _imports _this_mod where -- #11164: when we define a data instance -- but not data family, re-export the family - -- Generally, whenever we export a part of a declaration, - -- export the declaration, too. + -- Even though we don't check whether this is actually a data family + -- only data families can locally define subordinate things (`ns` here) + -- without locally defining (and instead importing) the parent (`n`) fix_faminst (AvailTC n ns flds) | not (n `elem` ns) = AvailTC n (n:ns) flds diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index 0959337..9993618 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -6666,6 +6666,11 @@ adjustment for type families: associated types ``Tj``. The types need a keyword "``type``" to distinguish them from data constructors. +- Whenever there is no export list and a data instance is defined, the + corresponding data family type constructor is exported along with + the new data constructors, regardless of whether the data family + is defined locally or in another module. + .. _data-family-impexp-examples: Examples From git at git.haskell.org Fri Dec 11 22:17:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 11 Dec 2015 22:17:26 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Only run recomp015 on ELF-based platforms (ceaf0f4) Message-ID: <20151211221726.F3B4D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ceaf0f4683a3e0ba85ae420956cfc394824e9a38/ghc >--------------------------------------------------------------- commit ceaf0f4683a3e0ba85ae420956cfc394824e9a38 Author: Ben Gamari Date: Fri Dec 11 22:41:23 2015 +0100 testsuite: Only run recomp015 on ELF-based platforms It fails on OS X with hundreds of messages of the form, ``` ManySections.s:196576:10: error: error: mach-o section specifier uses an unknown section type .section s65525,"", at progbits ^ ManySections.s:196579:10: error: error: mach-o section specifier uses an unknown section type .section s65526,"", at progbits ``` It fails on Windows with messages of the form, ``` ManySections.s:196579:10: error: Error: junk at the end of line, first unrecognized character is ',' ``` Test Plan: Validate Reviewers: hsyl20, thomie, austin Reviewed By: thomie, austin Differential Revision: https://phabricator.haskell.org/D1601 GHC Trac Issues: #11022 >--------------------------------------------------------------- ceaf0f4683a3e0ba85ae420956cfc394824e9a38 testsuite/tests/driver/recomp015/all.T | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/driver/recomp015/all.T b/testsuite/tests/driver/recomp015/all.T index ff86caf..4ab3e88 100644 --- a/testsuite/tests/driver/recomp015/all.T +++ b/testsuite/tests/driver/recomp015/all.T @@ -1,7 +1,8 @@ # Test for the ELF parser: more than 0xff00 sections (use different ELF fields) test('recomp015', - [ clean_cmd('$MAKE -s clean') ], + [ clean_cmd('$MAKE -s clean'), + unless(opsys('linux') or opsys('solaris2') or opsys('openbsd'), skip)], run_command, ['$MAKE -s --no-print-directory recomp015']) From git at git.haskell.org Fri Dec 11 22:17:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 11 Dec 2015 22:17:30 +0000 (UTC) Subject: [commit: ghc] master: Fix infix record field fixity (#11167 and #11173). (6e56ac5) Message-ID: <20151211221730.DD6AB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6e56ac58a6905197412d58e32792a04a63b94d7e/ghc >--------------------------------------------------------------- commit 6e56ac58a6905197412d58e32792a04a63b94d7e Author: Adam Gundry Date: Fri Dec 11 22:43:26 2015 +0100 Fix infix record field fixity (#11167 and #11173). This extends D1585 with proper support for infix duplicate record fields. In particular, it is now possible to declare record fields as infix in a module for which `DuplicateRecordFields` is enabled, fixity is looked up correctly and a readable (although unpleasant) error message is generated if multiple fields with different fixities are in scope. As a bonus, `DEPRECATED` and `WARNING` pragmas now work for duplicate record fields. The pragma applies to all fields with the given label. In addition, a couple of minor `DuplicateRecordFields` bugs, which were pinpointed by the `T11167_ambig` test case, are fixed by this patch: - Ambiguous infix fields can now be disambiguated by putting a type signature on the first argument - Polymorphic type constructor signatures (such as `ContT () IO a` in `T11167_ambig`) now work for disambiguation Parts of this patch are from D1585 authored by @KaneTW. Test Plan: New tests added. Reviewers: KaneTW, bgamari, austin Reviewed By: bgamari Subscribers: thomie, hvr Differential Revision: https://phabricator.haskell.org/D1600 GHC Trac Issues: #11167, #11173 >--------------------------------------------------------------- 6e56ac58a6905197412d58e32792a04a63b94d7e compiler/hsSyn/HsExpr.hs | 1 + compiler/hsSyn/HsTypes.hs | 4 ++ compiler/main/HscTypes.hs | 12 +++-- compiler/rename/RnEnv.hs | 59 ++++++++++++++++++---- compiler/rename/RnExpr.hs | 7 +-- compiler/rename/RnNames.hs | 11 ++-- compiler/rename/RnSource.hs | 4 +- compiler/typecheck/TcExpr.hs | 16 +++++- .../overloadedrecflds/should_compile/T11173.hs | 6 +++ .../overloadedrecflds/should_compile/T11173a.hs | 10 ++++ .../tests/overloadedrecflds/should_compile/all.T | 1 + ...cfldsfail11.hs => OverloadedRecFldsFail11_A.hs} | 3 +- .../should_fail/T11167_ambiguous_fixity.hs | 6 +++ .../should_fail/T11167_ambiguous_fixity.stderr | 16 ++++++ .../should_fail/T11167_ambiguous_fixity_A.hs | 5 ++ .../should_fail/T11167_ambiguous_fixity_B.hs | 3 ++ .../tests/overloadedrecflds/should_fail/all.T | 8 ++- .../should_fail/overloadedrecfldsfail11.hs | 6 +-- .../should_fail/overloadedrecfldsfail11.stderr | 11 ++-- testsuite/tests/rename/should_compile/T11167.hs | 21 ++++++++ .../tests/rename/should_compile/T11167_ambig.hs | 23 +++++++++ testsuite/tests/rename/should_compile/all.T | 2 + 22 files changed, 201 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 6e56ac58a6905197412d58e32792a04a63b94d7e From git at git.haskell.org Fri Dec 11 23:22:52 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 11 Dec 2015 23:22:52 +0000 (UTC) Subject: [commit: ghc] master: Add kind equalities to GHC. (6746549) Message-ID: <20151211232252.914A13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6746549772c5cc0ac66c0fce562f297f4d4b80a2/ghc >--------------------------------------------------------------- commit 6746549772c5cc0ac66c0fce562f297f4d4b80a2 Author: Richard Eisenberg Date: Fri Dec 11 18:19:53 2015 -0500 Add kind equalities to GHC. This implements the ideas originally put forward in "System FC with Explicit Kind Equality" (ICFP'13). There are several noteworthy changes with this patch: * We now have casts in types. These change the kind of a type. See new constructor `CastTy`. * All types and all constructors can be promoted. This includes GADT constructors. GADT pattern matches take place in type family equations. In Core, types can now be applied to coercions via the `CoercionTy` constructor. * Coercions can now be heterogeneous, relating types of different kinds. A coercion proving `t1 :: k1 ~ t2 :: k2` proves both that `t1` and `t2` are the same and also that `k1` and `k2` are the same. * The `Coercion` type has been significantly enhanced. The documentation in `docs/core-spec/core-spec.pdf` reflects the new reality. * The type of `*` is now `*`. No more `BOX`. * Users can write explicit kind variables in their code, anywhere they can write type variables. For backward compatibility, automatic inference of kind-variable binding is still permitted. * The new extension `TypeInType` turns on the new user-facing features. * Type families and synonyms are now promoted to kinds. This causes trouble with parsing `*`, leading to the somewhat awkward new `HsAppsTy` constructor for `HsType`. This is dispatched with in the renamer, where the kind `*` can be told apart from a type-level multiplication operator. Without `-XTypeInType` the old behavior persists. With `-XTypeInType`, you need to import `Data.Kind` to get `*`, also known as `Type`. * The kind-checking algorithms in TcHsType have been significantly rewritten to allow for enhanced kinds. * The new features are still quite experimental and may be in flux. * TODO: Several open tickets: #11195, #11196, #11197, #11198, #11203. * TODO: Update user manual. Tickets addressed: #9017, #9173, #7961, #10524, #8566, #11142. Updates Haddock submodule. >--------------------------------------------------------------- 6746549772c5cc0ac66c0fce562f297f4d4b80a2 .gitmodules | 58 +- README.md | 90 +- compiler/basicTypes/BasicTypes.hs | 4 + compiler/basicTypes/ConLike.hs | 4 +- compiler/basicTypes/DataCon.hs | 360 ++- compiler/basicTypes/DataCon.hs-boot | 7 +- compiler/basicTypes/Id.hs | 90 +- compiler/basicTypes/IdInfo.hs | 20 +- compiler/basicTypes/IdInfo.hs-boot | 2 + compiler/basicTypes/Lexeme.hs | 1 - compiler/basicTypes/MkId.hs | 159 +- compiler/basicTypes/MkId.hs-boot | 3 + compiler/basicTypes/Name.hs | 8 +- compiler/basicTypes/NameEnv.hs | 5 +- compiler/basicTypes/OccName.hs | 7 +- compiler/basicTypes/PatSyn.hs | 12 +- compiler/basicTypes/PatSyn.hs-boot | 2 +- compiler/basicTypes/SrcLoc.hs | 8 + compiler/basicTypes/Unique.hs | 9 +- compiler/basicTypes/Var.hs | 75 +- compiler/basicTypes/VarEnv.hs | 63 +- compiler/basicTypes/VarSet.hs | 20 +- compiler/cmm/Cmm.hs | 0 compiler/cmm/CmmExpr.hs | 0 compiler/cmm/CmmLayoutStack.hs | 0 compiler/cmm/Hoopl/Dataflow.hs | 0 compiler/codeGen/StgCmmClosure.hs | 18 +- compiler/codeGen/StgCmmLayout.hs | 0 compiler/coreSyn/CoreArity.hs | 49 +- compiler/coreSyn/CoreFVs.hs | 284 ++- compiler/coreSyn/CoreLint.hs | 680 +++--- compiler/coreSyn/CorePrep.hs | 9 +- compiler/coreSyn/CoreSubst.hs | 244 +- compiler/coreSyn/CoreSyn.hs | 76 +- compiler/coreSyn/CoreTidy.hs | 11 +- compiler/coreSyn/CoreUnfold.hs | 1 - compiler/coreSyn/CoreUtils.hs | 72 +- compiler/coreSyn/MkCore.hs | 96 +- compiler/coreSyn/PprCore.hs | 8 +- compiler/coreSyn/TrieMap.hs | 432 ++-- compiler/deSugar/Check.hs | 2 +- compiler/deSugar/Desugar.hs | 32 +- compiler/deSugar/DsArrows.hs | 20 +- compiler/deSugar/DsBinds.hs | 211 +- compiler/deSugar/DsCCall.hs | 32 +- compiler/deSugar/DsExpr.hs | 45 +- compiler/deSugar/DsForeign.hs | 52 +- compiler/deSugar/DsGRHSs.hs | 5 +- compiler/deSugar/DsListComp.hs | 118 +- compiler/deSugar/DsMeta.hs | 93 +- compiler/deSugar/DsMonad.hs | 6 +- compiler/deSugar/DsUtils.hs | 22 +- compiler/deSugar/Match.hs | 20 +- compiler/deSugar/MatchCon.hs | 64 +- compiler/deSugar/PmExpr.hs | 2 + compiler/ghc.cabal.in | 2 +- compiler/ghc.mk | 2 +- compiler/ghci/ByteCodeGen.hs | 31 +- compiler/ghci/Debugger.hs | 10 +- compiler/ghci/DebuggerUtils.hs | 0 compiler/ghci/RtClosureInspect.hs | 59 +- compiler/hsSyn/Convert.hs | 71 +- compiler/hsSyn/HsDecls.hs | 16 +- compiler/hsSyn/HsExpr.hs | 1 - compiler/hsSyn/HsPat.hs | 9 +- compiler/hsSyn/HsTypes.hs | 257 +- compiler/hsSyn/HsUtils.hs | 123 +- compiler/iface/BinIface.hs | 10 +- compiler/iface/BuildTyCl.hs | 92 +- compiler/iface/IfaceEnv.hs | 25 +- compiler/iface/IfaceSyn.hs | 203 +- compiler/iface/IfaceType.hs | 633 +++-- compiler/iface/MkIface.hs | 56 +- compiler/iface/TcIface.hs | 346 ++- compiler/iface/TcIface.hs-boot | 2 +- compiler/main/Annotations.hs | 0 compiler/main/DynFlags.hs | 9 + compiler/main/DynamicLoading.hs | 3 +- compiler/main/GHC.hs | 9 +- compiler/main/GhcMonad.hs | 0 compiler/main/GhcPlugins.hs | 4 +- compiler/main/HscStats.hs | 0 compiler/main/HscTypes.hs | 20 +- compiler/main/InteractiveEval.hs | 28 +- compiler/main/InteractiveEvalTypes.hs | 2 +- compiler/main/PipelineMonad.hs | 0 compiler/main/PprTyThing.hs | 4 +- compiler/nativeGen/PPC/Ppr.hs | 1 - compiler/nativeGen/RegAlloc/Graph/ArchBase.hs | 0 compiler/nativeGen/RegAlloc/Graph/ArchX86.hs | 0 compiler/nativeGen/RegAlloc/Graph/Coalesce.hs | 0 compiler/nativeGen/RegAlloc/Graph/Main.hs | 0 compiler/nativeGen/RegAlloc/Graph/Spill.hs | 0 compiler/nativeGen/RegAlloc/Graph/SpillClean.hs | 0 compiler/nativeGen/RegAlloc/Graph/SpillCost.hs | 0 compiler/nativeGen/RegAlloc/Graph/Stats.hs | 0 compiler/nativeGen/RegAlloc/Linear/Main.hs | 0 compiler/nativeGen/RegAlloc/Linear/PPC/FreeRegs.hs | 0 .../nativeGen/RegAlloc/Linear/SPARC/FreeRegs.hs | 0 compiler/nativeGen/RegAlloc/Linear/StackMap.hs | 0 compiler/nativeGen/RegAlloc/Linear/Stats.hs | 0 compiler/nativeGen/SPARC/CodeGen/Gen64.hs | 3 - compiler/parser/ApiAnnotation.hs | 4 - compiler/parser/Lexer.x | 10 - compiler/parser/Parser.y | 222 +- compiler/parser/RdrHsSyn.hs | 52 +- compiler/prelude/PrelInfo.hs | 72 +- compiler/prelude/PrelNames.hs | 147 +- compiler/prelude/PrelNames.hs-boot | 3 +- compiler/prelude/PrelRules.hs | 50 +- compiler/prelude/PrimOp.hs | 6 +- compiler/prelude/TysPrim.hs | 245 +- compiler/prelude/TysWiredIn.hs | 396 ++-- compiler/prelude/TysWiredIn.hs-boot | 10 +- compiler/rename/RnEnv.hs | 21 +- compiler/rename/RnNames.hs | 2 +- compiler/rename/RnPat.hs | 4 +- compiler/rename/RnSource.hs | 98 +- compiler/rename/RnTypes.hs | 832 ++++--- compiler/simplCore/CSE.hs | 4 +- compiler/simplCore/CoreMonad.hs | 1 - compiler/simplCore/FloatIn.hs | 169 +- compiler/simplCore/OccurAnal.hs | 2 +- compiler/simplCore/SAT.hs | 2 +- compiler/simplCore/SetLevels.hs | 30 +- compiler/simplCore/SimplEnv.hs | 64 +- compiler/simplCore/SimplMonad.hs | 4 +- compiler/simplCore/SimplUtils.hs | 17 +- compiler/simplCore/Simplify.hs | 76 +- compiler/simplStg/UnariseStg.hs | 2 +- compiler/specialise/Rules.hs | 54 +- compiler/specialise/SpecConstr.hs | 10 +- compiler/specialise/Specialise.hs | 60 +- compiler/stgSyn/StgLint.hs | 1 - compiler/stranal/DmdAnal.hs | 4 +- compiler/stranal/WwLib.hs | 39 +- compiler/typecheck/FamInst.hs | 120 +- compiler/typecheck/FunDeps.hs | 60 +- compiler/typecheck/Inst.hs | 170 +- compiler/typecheck/TcArrows.hs | 18 +- compiler/typecheck/TcBinds.hs | 139 +- compiler/typecheck/TcCanonical.hs | 570 +++-- compiler/typecheck/TcClassDcl.hs | 20 +- compiler/typecheck/TcDefaults.hs | 5 +- compiler/typecheck/TcDeriv.hs | 204 +- compiler/typecheck/TcEnv.hs | 37 +- compiler/typecheck/TcErrors.hs | 418 ++-- compiler/typecheck/TcEvidence.hs | 663 ++---- compiler/typecheck/TcExpr.hs | 130 +- compiler/typecheck/TcFlatten.hs | 263 ++- compiler/typecheck/TcForeign.hs | 55 +- compiler/typecheck/TcGenDeriv.hs | 31 +- compiler/typecheck/TcGenGenerics.hs | 31 +- compiler/typecheck/TcHsSyn.hs | 309 ++- compiler/typecheck/TcHsType.hs | 2078 +++++++++------- compiler/typecheck/TcInstDcls.hs | 87 +- compiler/typecheck/TcInteract.hs | 291 ++- compiler/typecheck/TcMType.hs | 741 ++++-- compiler/typecheck/TcMatches.hs | 20 +- compiler/typecheck/TcPat.hs | 72 +- compiler/typecheck/TcPatSyn.hs | 53 +- compiler/typecheck/TcPluginM.hs | 64 +- compiler/typecheck/TcRnDriver.hs | 41 +- compiler/typecheck/TcRnMonad.hs | 60 +- compiler/typecheck/TcRnTypes.hs | 335 ++- compiler/typecheck/TcRules.hs | 140 +- compiler/typecheck/TcSMonad.hs | 642 ++--- compiler/typecheck/TcSimplify.hs | 599 +++-- compiler/typecheck/TcSplice.hs | 178 +- compiler/typecheck/TcTyClsDecls.hs | 1099 ++++++--- compiler/typecheck/TcTyDecls.hs | 229 +- compiler/typecheck/TcType.hs | 990 +++++--- compiler/typecheck/TcType.hs-boot | 1 + compiler/typecheck/TcTypeNats.hs | 111 +- compiler/typecheck/TcTypeable.hs | 5 +- compiler/typecheck/TcUnify.hs | 724 +++--- compiler/typecheck/TcUnify.hs-boot | 7 +- compiler/typecheck/TcValidity.hs | 702 ++++-- compiler/types/Class.hs | 20 +- compiler/types/CoAxiom.hs | 34 +- compiler/types/Coercion.hs | 2495 +++++++++---------- compiler/types/Coercion.hs-boot | 46 + compiler/types/FamInstEnv.hs | 511 +++- compiler/types/InstEnv.hs | 24 +- compiler/types/Kind.hs | 297 +-- compiler/types/OptCoercion.hs | 568 +++-- compiler/types/TyCoRep.hs | 2496 ++++++++++++++++++++ .../types/{TypeRep.hs-boot => TyCoRep.hs-boot} | 9 +- compiler/types/TyCon.hs | 211 +- compiler/types/Type.hs | 1895 +++++++++------ compiler/types/Type.hs-boot | 15 +- compiler/types/TypeRep.hs | 1020 -------- compiler/types/Unify.hs | 1237 ++++++---- compiler/utils/Bag.hs | 2 +- compiler/utils/ListSetOps.hs | 15 +- compiler/utils/MonadUtils.hs | 24 +- compiler/utils/Outputable.hs | 17 +- compiler/utils/Pair.hs | 12 +- compiler/utils/Serialized.hs | 0 compiler/utils/UniqDFM.hs | 4 + compiler/utils/UniqDSet.hs | 15 +- compiler/utils/UniqSet.hs | 2 +- compiler/utils/Util.hs | 49 +- compiler/vectorise/Vectorise.hs | 0 compiler/vectorise/Vectorise/Builtins.hs | 0 compiler/vectorise/Vectorise/Builtins/Base.hs | 0 .../vectorise/Vectorise/Builtins/Initialise.hs | 2 +- compiler/vectorise/Vectorise/Convert.hs | 15 +- compiler/vectorise/Vectorise/Env.hs | 6 +- compiler/vectorise/Vectorise/Exp.hs | 60 +- .../vectorise/Vectorise/Generic/Description.hs | 0 compiler/vectorise/Vectorise/Generic/PADict.hs | 2 +- compiler/vectorise/Vectorise/Generic/PAMethods.hs | 18 +- compiler/vectorise/Vectorise/Generic/PData.hs | 14 +- compiler/vectorise/Vectorise/Monad.hs | 0 compiler/vectorise/Vectorise/Monad/Base.hs | 0 compiler/vectorise/Vectorise/Monad/Global.hs | 0 compiler/vectorise/Vectorise/Monad/InstEnv.hs | 0 compiler/vectorise/Vectorise/Monad/Local.hs | 6 +- compiler/vectorise/Vectorise/Monad/Naming.hs | 11 +- compiler/vectorise/Vectorise/Type/Classify.hs | 21 +- compiler/vectorise/Vectorise/Type/Env.hs | 0 compiler/vectorise/Vectorise/Type/TyConDecl.hs | 12 +- compiler/vectorise/Vectorise/Type/Type.hs | 15 +- compiler/vectorise/Vectorise/Utils.hs | 0 compiler/vectorise/Vectorise/Utils/Base.hs | 0 compiler/vectorise/Vectorise/Utils/Closure.hs | 0 compiler/vectorise/Vectorise/Utils/Hoisting.hs | 0 compiler/vectorise/Vectorise/Utils/PADict.hs | 21 +- compiler/vectorise/Vectorise/Utils/Poly.hs | 0 compiler/vectorise/Vectorise/Var.hs | 0 compiler/vectorise/Vectorise/Vect.hs | 0 docs/core-spec/.gitignore | 1 + docs/core-spec/CoreLint.ott | 309 ++- docs/core-spec/CoreSyn.ott | 219 +- docs/core-spec/Makefile | 2 +- docs/core-spec/OpSem.ott | 6 +- docs/core-spec/core-spec.mng | 83 +- docs/core-spec/core-spec.pdf | Bin 342464 -> 348408 bytes docs/users_guide/glasgow_exts.rst | 3 - docs/users_guide/using.rst | 19 +- libraries/base/Data/Coerce.hs | 3 +- libraries/base/Data/Kind.hs | 19 + libraries/base/Data/Monoid.hs | 1 - libraries/base/Data/Type/Coercion.hs | 10 +- libraries/base/Data/Type/Equality.hs | 40 +- libraries/base/Data/Typeable/Internal.hs | 48 +- libraries/base/GHC/Base.hs | 19 +- libraries/base/GHC/Exts.hs | 11 +- libraries/base/GHC/TypeLits.hs | 2 - libraries/base/base.cabal | 1 + libraries/base/tests/CatEntail.hs | 2 +- libraries/ghc-prim/GHC/Classes.hs | 1 - libraries/ghc-prim/GHC/Types.hs | 62 +- rae.txt | 319 +++ testsuite/tests/ado/ado004.stderr | 4 +- .../tests/annotations/should_fail/annfail10.stderr | 2 +- .../tests/deSugar/should_compile/T2431.stderr | 22 +- .../tests/deSugar/should_compile/T4488.stderr | 32 +- testsuite/tests/{ado => dependent}/Makefile | 0 testsuite/tests/dependent/should_compile/Dep1.hs | 13 + testsuite/tests/dependent/should_compile/Dep2.hs | 7 + testsuite/tests/dependent/should_compile/Dep3.hs | 26 + .../dependent/should_compile/KindEqualities.hs | 25 + .../dependent/should_compile/KindEqualities2.hs | 43 + .../tests/dependent/should_compile/KindLevels.hs | 9 + .../should_compile/Makefile | 0 .../tests/dependent/should_compile/RAE_T32b.hs | 23 + testsuite/tests/dependent/should_compile/Rae31.hs | 24 + .../tests/dependent/should_compile/RaeBlogPost.hs | 63 + testsuite/tests/dependent/should_compile/all.T | 10 + .../tests/dependent/should_compile/mkGADTVars.hs | 9 + .../tests/dependent/should_fail/BadTelescope.hs | 9 + .../dependent/should_fail/BadTelescope.stderr | 9 + .../tests/dependent/should_fail/BadTelescope2.hs | 14 + .../dependent/should_fail/BadTelescope2.stderr | 16 + .../tests/dependent/should_fail/BadTelescope3.hs | 9 + .../dependent/should_fail/BadTelescope3.stderr | 6 + .../tests/dependent/should_fail/BadTelescope4.hs | 13 + .../dependent/should_fail/BadTelescope4.stderr | 15 + testsuite/tests/dependent/should_fail/DepFail1.hs | 11 + .../tests/dependent/should_fail/DepFail1.stderr | 12 + testsuite/tests/dependent/should_fail/Makefile | 5 + .../tests/dependent/should_fail/PromotedClass.hs | 11 + .../dependent/should_fail/PromotedClass.stderr | 6 + testsuite/tests/dependent/should_fail/RAE_T32a.hs | 35 + .../tests/dependent/should_fail/RAE_T32a.stderr | 19 + testsuite/tests/dependent/should_fail/SelfDep.hs | 3 + .../tests/dependent/should_fail/SelfDep.stderr | 5 + .../tests/dependent/should_fail/TypeSkolEscape.hs | 8 + .../dependent/should_fail/TypeSkolEscape.stderr | 7 + testsuite/tests/dependent/should_fail/all.T | 9 + .../{should_fail => should_compile}/T10524.hs | 1 + testsuite/tests/deriving/should_compile/all.T | 1 + testsuite/tests/deriving/should_fail/T1496.stderr | 8 +- testsuite/tests/deriving/should_fail/T7959.stderr | 12 +- testsuite/tests/deriving/should_fail/all.T | 1 - .../tests/deriving/should_fail/drvfail005.stderr | 9 +- testsuite/tests/driver/T4437.hs | 3 +- testsuite/tests/driver/werror.stderr | 2 +- testsuite/tests/gadt/T3163.stderr | 2 +- testsuite/tests/gadt/gadt-escape1.stderr | 32 +- testsuite/tests/gadt/gadt10.stderr | 4 +- testsuite/tests/gadt/gadt13.stderr | 30 +- testsuite/tests/gadt/gadt7.stderr | 34 +- testsuite/tests/ghc-api/annotations/T10307.stdout | 1 - testsuite/tests/ghc-api/annotations/T10312.stderr | 0 testsuite/tests/ghc-api/annotations/T10312.stdout | 2 - testsuite/tests/ghc-api/annotations/T10357.stderr | 14 +- testsuite/tests/ghc-api/annotations/T10357.stdout | 1 - testsuite/tests/ghc-api/annotations/T10358.stdout | 5 - testsuite/tests/ghc-api/annotations/T11018.stderr | 2 +- testsuite/tests/ghc-api/annotations/T11018.stdout | 6 +- .../tests/ghc-api/annotations/exampleTest.stdout | 3 +- .../tests/ghc-api/annotations/listcomps.stdout | 2 - .../tests/ghc-api/annotations/parseTree.stdout | 4 +- testsuite/tests/ghc-api/landmines/landmines.stdout | 4 +- .../tests/ghci.debugger/scripts/break001.stdout | 4 +- .../tests/ghci.debugger/scripts/break003.stderr | 2 +- .../tests/ghci.debugger/scripts/break003.stdout | 8 +- .../tests/ghci.debugger/scripts/break006.stderr | 16 +- .../tests/ghci.debugger/scripts/break006.stdout | 12 +- .../tests/ghci.debugger/scripts/break012.stdout | 10 +- .../tests/ghci.debugger/scripts/break018.stdout | 4 +- .../ghci.debugger/scripts/break022/break022.stdout | 2 +- .../tests/ghci.debugger/scripts/break026.stdout | 40 +- .../tests/ghci.debugger/scripts/break028.stdout | 6 +- .../tests/ghci.debugger/scripts/hist001.stdout | 22 +- .../tests/ghci.debugger/scripts/print018.stdout | 6 +- .../tests/ghci.debugger/scripts/print022.stdout | 6 +- .../tests/ghci.debugger/scripts/print025.stdout | 2 +- .../tests/ghci.debugger/scripts/print031.stdout | 2 +- .../tests/ghci.debugger/scripts/print036.stdout | 1 - testsuite/tests/ghci/prog009/ghci.prog009.stdout | 0 testsuite/tests/ghci/scripts/Defer02.stderr | 7 +- testsuite/tests/ghci/scripts/Defer02.stdout | 2 +- testsuite/tests/ghci/scripts/T10122.stdout | 2 +- testsuite/tests/ghci/scripts/T10508.stderr | 6 +- testsuite/tests/ghci/scripts/T2182ghci.stderr | 10 +- testsuite/tests/ghci/scripts/T4087.stdout | 2 +- testsuite/tests/ghci/scripts/T4175.stdout | 15 +- testsuite/tests/ghci/scripts/T6018ghcifail.stderr | 6 +- testsuite/tests/ghci/scripts/T7627.stdout | 6 +- testsuite/tests/ghci/scripts/T7730.stdout | 2 +- testsuite/tests/ghci/scripts/T7873.script | 5 +- testsuite/tests/ghci/scripts/T7873.stderr | 7 + testsuite/tests/ghci/scripts/T7873.stdout | 8 +- testsuite/tests/ghci/scripts/T7939.stdout | 35 +- testsuite/tests/ghci/scripts/T9181.stdout | 24 +- testsuite/tests/ghci/scripts/ghci001.stdout | 0 testsuite/tests/ghci/scripts/ghci013.stdout | 2 +- testsuite/tests/ghci/scripts/ghci047.stderr | 26 +- testsuite/tests/ghci/scripts/ghci051.stderr | 4 +- testsuite/tests/ghci/scripts/ghci055.stdout | 4 +- testsuite/tests/ghci/scripts/ghci059.script | 2 +- testsuite/tests/ghci/scripts/ghci059.stdout | 2 +- .../should_compile_flag_haddock/haddockA023.stderr | 2 +- .../should_compile_flag_haddock/haddockA026.stderr | 2 +- .../should_compile_flag_haddock/haddockA027.stderr | 4 +- .../should_compile_flag_haddock/haddockA028.stderr | 2 +- .../should_compile/PushedInAsGivens.stderr | 3 +- .../tests/indexed-types/should_compile/Simple12.hs | 1 - .../indexed-types/should_compile/T3017.stderr | 5 +- .../indexed-types/should_compile/T3208b.stderr | 3 +- .../tests/indexed-types/should_compile/T9316.hs | 1 - .../tests/indexed-types/should_compile/T9747.hs | 2 +- .../indexed-types/should_fail/ClosedFam3.stderr | 24 +- .../indexed-types/should_fail/Overlap4.stderr | 1 + .../indexed-types/should_fail/SimpleFail12.stderr | 2 +- .../indexed-types/should_fail/SimpleFail14.stderr | 8 +- .../indexed-types/should_fail/SimpleFail1a.stderr | 7 +- .../indexed-types/should_fail/SimpleFail1b.stderr | 4 +- .../indexed-types/should_fail/SimpleFail6.stderr | 4 +- .../tests/indexed-types/should_fail/T10141.stderr | 5 +- .../tests/indexed-types/should_fail/T10899.stderr | 2 +- .../tests/indexed-types/should_fail/T2627b.stderr | 13 +- .../tests/indexed-types/should_fail/T2664.stderr | 34 +- .../tests/indexed-types/should_fail/T3330a.stderr | 16 +- .../tests/indexed-types/should_fail/T3330c.stderr | 23 +- .../tests/indexed-types/should_fail/T4179.stderr | 22 +- .../tests/indexed-types/should_fail/T5439.stderr | 46 +- .../tests/indexed-types/should_fail/T6123.stderr | 12 +- .../tests/indexed-types/should_fail/T7786.stderr | 64 +- .../tests/indexed-types/should_fail/T7788.stderr | 6 +- .../tests/indexed-types/should_fail/T9160.stderr | 2 +- .../tests/indexed-types/should_fail/T9171.stderr | 17 +- .../tests/indexed-types/should_fail/T9357.stderr | 2 +- testsuite/tests/indexed-types/should_run/T5719.hs | 2 +- testsuite/tests/mdo/should_compile/mdo006.hs | 0 testsuite/tests/module/mod71.stderr | 20 +- testsuite/tests/module/mod72.stderr | 2 +- .../tests/parser/should_compile/read014.stderr | 2 +- testsuite/tests/parser/should_fail/T3811d.stderr | 2 +- testsuite/tests/parser/should_fail/T7848.stderr | 4 +- .../tests/parser/should_fail/readFail003.stderr | 30 +- .../tests/partial-sigs/should_compile/ADT.stderr | 2 +- .../should_compile/DataFamilyInstanceLHS.stderr | 2 +- .../partial-sigs/should_compile/Meltdown.stderr | 2 +- .../partial-sigs/should_compile/SkipMany.stderr | 2 +- .../partial-sigs/should_compile/T10403.stderr | 14 +- .../partial-sigs/should_compile/T10438.stderr | 16 +- .../partial-sigs/should_compile/T11192.stderr | 4 +- .../should_compile/TypeFamilyInstanceLHS.stderr | 3 +- .../WarningWildcardInstantiations.stderr | 26 +- .../tests/partial-sigs/should_fail/T10045.stderr | 4 +- .../should_fail/WildcardInstantiations.stderr | 24 +- testsuite/tests/patsyn/should_fail/T9161-2.stderr | 7 +- testsuite/tests/perf/compiler/all.T | 42 +- testsuite/tests/perf/haddock/all.T | 6 +- testsuite/tests/polykinds/PolyInstances.hs | 22 + testsuite/tests/polykinds/PolyKinds02.stderr | 7 +- testsuite/tests/polykinds/PolyKinds04.stderr | 5 +- testsuite/tests/polykinds/PolyKinds07.stderr | 2 +- testsuite/tests/polykinds/SigTvKinds.hs | 7 + testsuite/tests/polykinds/SigTvKinds2.hs | 7 + testsuite/tests/polykinds/SigTvKinds2.stderr | 6 + testsuite/tests/polykinds/T10503.stderr | 29 +- testsuite/tests/polykinds/T11142.hs | 10 + testsuite/tests/polykinds/T11142.stderr | 7 + testsuite/tests/polykinds/T5716.hs | 0 testsuite/tests/polykinds/T5716.stderr | 9 +- testsuite/tests/polykinds/T6021.hs | 2 +- testsuite/tests/polykinds/T6021.stderr | 5 +- testsuite/tests/polykinds/T6039.stderr | 4 - testsuite/tests/polykinds/T6129.stderr | 2 +- testsuite/tests/polykinds/T7224.stderr | 9 +- testsuite/tests/polykinds/T7230.stderr | 6 +- testsuite/tests/polykinds/T7278.hs | 3 +- testsuite/tests/polykinds/T7278.stderr | 9 +- testsuite/tests/polykinds/T7328.hs | 2 +- testsuite/tests/polykinds/T7328.stderr | 11 +- testsuite/tests/polykinds/T7341.hs | 2 +- testsuite/tests/polykinds/T7341.stderr | 4 +- testsuite/tests/polykinds/T7404.stderr | 7 +- testsuite/tests/polykinds/T7438.stderr | 35 +- testsuite/tests/polykinds/T7481.stderr | 4 - testsuite/tests/polykinds/T7524.stderr | 6 +- testsuite/tests/polykinds/T7594.hs | 4 +- testsuite/tests/polykinds/T7805.stderr | 8 +- testsuite/tests/polykinds/T7939a.stderr | 5 +- testsuite/tests/polykinds/T8566.stderr | 35 +- testsuite/tests/polykinds/T8616.stderr | 14 +- testsuite/tests/polykinds/T9200b.stderr | 7 +- testsuite/tests/polykinds/T9222.stderr | 32 +- testsuite/tests/polykinds/T9569.hs | 2 +- testsuite/tests/polykinds/all.T | 10 +- testsuite/tests/rename/should_fail/T2993.stderr | 2 +- .../tests/rename/should_fail/rnfail026.stderr | 15 +- .../tests/rename/should_fail/rnfail055.stderr | 3 +- testsuite/tests/roles/should_compile/Roles1.stderr | 84 +- .../tests/roles/should_compile/Roles13.stderr | 34 +- .../tests/roles/should_compile/Roles14.stderr | 9 +- testsuite/tests/roles/should_compile/Roles2.stderr | 18 +- testsuite/tests/roles/should_compile/Roles3.stderr | 38 +- testsuite/tests/roles/should_compile/Roles4.stderr | 16 +- testsuite/tests/roles/should_compile/T8958.stderr | 6 +- testsuite/tests/roles/should_compile/all.T | 10 +- testsuite/tests/rts/T9045.hs | 1 + testsuite/tests/simplCore/should_compile/Makefile | 2 +- .../tests/simplCore/should_compile/T7360.stderr | 58 +- .../tests/simplCore/should_compile/T8274.stdout | 10 +- .../tests/simplCore/should_compile/T9400.stderr | 6 +- .../tests/simplCore/should_compile/rule2.stderr | 4 +- .../simplCore/should_compile/spec-inline.stderr | 7 +- testsuite/tests/stranal/sigs/DmdAnalGADTs.stderr | 2 + testsuite/tests/stranal/sigs/T8569.stderr | 2 + testsuite/tests/th/T3177a.stderr | 14 +- testsuite/tests/th/T3920.hs | 0 testsuite/tests/th/T7021a.hs | 2 +- testsuite/tests/th/T8953.stderr | 4 +- testsuite/tests/th/TH_RichKinds.hs | 2 +- testsuite/tests/th/TH_RichKinds.stderr | 4 +- testsuite/tests/th/TH_Roles2.stderr | 1 + testsuite/tests/typecheck/should_compile/T5581.hs | 2 +- testsuite/tests/typecheck/should_compile/T5655.hs | 2 +- .../tests/typecheck/should_compile/T9834.stderr | 126 +- .../tests/typecheck/should_compile/T9939.stderr | 24 +- .../tests/typecheck/should_compile/tc141.stderr | 20 +- .../tests/typecheck/should_compile/tc167.stderr | 1 + .../tests/typecheck/should_compile/tc211.stderr | 20 +- .../tests/typecheck/should_compile/tc231.stderr | 4 +- .../tests/typecheck/should_compile/tc243.stderr | 2 +- testsuite/tests/typecheck/should_compile/tc255.hs | 2 +- testsuite/tests/typecheck/should_compile/tc256.hs | 2 +- testsuite/tests/typecheck/should_compile/tc257.hs | 2 +- testsuite/tests/typecheck/should_compile/tc258.hs | 2 +- .../typecheck/should_fail/AssocTyDef04.stderr | 2 +- .../tests/typecheck/should_fail/AssocTyDef06.hs | 2 +- .../typecheck/should_fail/AssocTyDef06.stderr | 9 +- .../typecheck/should_fail/FrozenErrorTests.stderr | 87 +- .../tests/typecheck/should_fail/T10285.stderr | 2 +- .../tests/typecheck/should_fail/T11112.stderr | 2 +- testsuite/tests/typecheck/should_fail/T1633.hs | 2 + testsuite/tests/typecheck/should_fail/T1633.stderr | 6 +- testsuite/tests/typecheck/should_fail/T2994.stderr | 32 +- testsuite/tests/typecheck/should_fail/T3540.stderr | 22 +- testsuite/tests/typecheck/should_fail/T3950.stderr | 22 +- testsuite/tests/typecheck/should_fail/T4875.stderr | 8 +- testsuite/tests/typecheck/should_fail/T5570.stderr | 12 +- testsuite/tests/typecheck/should_fail/T5853.stderr | 35 +- .../tests/typecheck/should_fail/T6018fail.stderr | 8 +- .../typecheck/should_fail/T6018failclosed.stderr | 13 +- testsuite/tests/typecheck/should_fail/T7368.stderr | 12 +- .../tests/typecheck/should_fail/T7368a.stderr | 20 +- testsuite/tests/typecheck/should_fail/T7410.stderr | 8 +- testsuite/tests/typecheck/should_fail/T7453.stderr | 64 +- testsuite/tests/typecheck/should_fail/T7609.stderr | 19 +- testsuite/tests/typecheck/should_fail/T7645.stderr | 8 +- testsuite/tests/typecheck/should_fail/T7696.stderr | 4 +- testsuite/tests/typecheck/should_fail/T7734.stderr | 28 +- testsuite/tests/typecheck/should_fail/T7778.stderr | 13 +- testsuite/tests/typecheck/should_fail/T7857.stderr | 30 +- testsuite/tests/typecheck/should_fail/T7892.stderr | 2 +- testsuite/tests/typecheck/should_fail/T8030.stderr | 6 +- testsuite/tests/typecheck/should_fail/T8262.stderr | 14 +- testsuite/tests/typecheck/should_fail/T8514.stderr | 3 +- testsuite/tests/typecheck/should_fail/T8603.stderr | 12 +- testsuite/tests/typecheck/should_fail/T8806.stderr | 20 +- testsuite/tests/typecheck/should_fail/T9109.stderr | 27 +- testsuite/tests/typecheck/should_fail/T9196.stderr | 15 +- testsuite/tests/typecheck/should_fail/T9201.stderr | 9 +- testsuite/tests/typecheck/should_fail/T9260.stderr | 10 +- testsuite/tests/typecheck/should_fail/T9999.stderr | 15 +- .../typecheck/should_fail/TcCoercibleFail.stderr | 100 +- .../typecheck/should_fail/TcCoercibleFail2.hs | 2 + .../typecheck/should_fail/TcCoercibleFail2.stderr | 4 +- .../tests/typecheck/should_fail/tcfail002.stderr | 14 +- .../tests/typecheck/should_fail/tcfail004.stderr | 16 +- .../tests/typecheck/should_fail/tcfail005.stderr | 16 +- .../tests/typecheck/should_fail/tcfail010.stderr | 2 +- .../tests/typecheck/should_fail/tcfail013.stderr | 11 +- .../tests/typecheck/should_fail/tcfail014.stderr | 14 +- .../tests/typecheck/should_fail/tcfail018.stderr | 2 +- .../tests/typecheck/should_fail/tcfail032.stderr | 24 +- testsuite/tests/typecheck/should_fail/tcfail036.hs | 2 + .../tests/typecheck/should_fail/tcfail036.stderr | 10 +- .../tests/typecheck/should_fail/tcfail049.stderr | 2 +- .../tests/typecheck/should_fail/tcfail050.stderr | 2 +- .../tests/typecheck/should_fail/tcfail057.stderr | 2 +- .../tests/typecheck/should_fail/tcfail070.stderr | 3 +- .../tests/typecheck/should_fail/tcfail078.stderr | 6 +- .../tests/typecheck/should_fail/tcfail088.stderr | 2 +- .../tests/typecheck/should_fail/tcfail090.stderr | 10 +- .../tests/typecheck/should_fail/tcfail099.stderr | 26 +- .../tests/typecheck/should_fail/tcfail113.stderr | 20 +- .../tests/typecheck/should_fail/tcfail122.stderr | 29 +- .../tests/typecheck/should_fail/tcfail123.stderr | 6 +- .../tests/typecheck/should_fail/tcfail132.stderr | 13 +- .../tests/typecheck/should_fail/tcfail133.stderr | 8 +- .../tests/typecheck/should_fail/tcfail140.stderr | 58 +- .../tests/typecheck/should_fail/tcfail146.stderr | 8 +- .../tests/typecheck/should_fail/tcfail147.stderr | 4 +- .../tests/typecheck/should_fail/tcfail151.stderr | 7 + .../tests/typecheck/should_fail/tcfail159.stderr | 6 +- .../tests/typecheck/should_fail/tcfail160.stderr | 7 +- .../tests/typecheck/should_fail/tcfail161.stderr | 7 +- .../tests/typecheck/should_fail/tcfail181.stderr | 2 +- .../tests/typecheck/should_fail/tcfail184.stderr | 2 +- .../tests/typecheck/should_fail/tcfail195.stderr | 2 +- .../tests/typecheck/should_fail/tcfail196.stderr | 5 +- .../tests/typecheck/should_fail/tcfail197.stderr | 7 +- .../tests/typecheck/should_fail/tcfail200.stderr | 14 +- .../tests/typecheck/should_fail/tcfail201.stderr | 2 +- .../tests/typecheck/should_fail/tcfail212.stderr | 24 +- testsuite/tests/typecheck/should_fail/tcfail213.hs | 2 +- testsuite/tests/typecheck/should_fail/tcfail214.hs | 2 +- .../tests/typecheck/should_fail/tcfail217.stderr | 2 +- testsuite/tests/typecheck/should_run/T10284.hs | 11 +- testsuite/tests/typecheck/should_run/T10284.stderr | 8 +- testsuite/tests/typecheck/should_run/T10284.stdout | 2 +- testsuite/tests/typecheck/should_run/T7861.stdout | 1 - testsuite/tests/typecheck/should_run/tcrun043.hs | 2 +- testsuite/tests/typecheck/should_run/tcrun044.hs | 2 +- .../tests/warnings/should_compile/T11077.stderr | 2 +- utils/genprimopcode/Main.hs | 2 +- utils/haddock | 2 +- 576 files changed, 21781 insertions(+), 15223 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 6746549772c5cc0ac66c0fce562f297f4d4b80a2 From git at git.haskell.org Fri Dec 11 23:30:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 11 Dec 2015 23:30:46 +0000 (UTC) Subject: [commit: ghc] master: Revert README.md changes from 6746549772c5 (5183109) Message-ID: <20151211233046.D81EF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/518310915fa2298f105a2ff5facd4c1ef796717d/ghc >--------------------------------------------------------------- commit 518310915fa2298f105a2ff5facd4c1ef796717d Author: Austin Seipp Date: Fri Dec 11 17:31:23 2015 -0600 Revert README.md changes from 6746549772c5 Signed-off-by: Austin Seipp >--------------------------------------------------------------- 518310915fa2298f105a2ff5facd4c1ef796717d README.md | 90 ++++++++++++++------------------------------------------------- 1 file changed, 19 insertions(+), 71 deletions(-) diff --git a/README.md b/README.md index ac97f34..227657f 100644 --- a/README.md +++ b/README.md @@ -1,91 +1,39 @@ -Dependent Types Branch of GHC -============================= +The Glasgow Haskell Compiler +============================ -This is a fork of GHC, with work toward supporting dependent types. -Anyone is welcome to download and play with this implementation, -and I am happy to receive feedback and issue reports on GitHub. +[![Build Status](https://api.travis-ci.org/ghc/ghc.svg?branch=master)](http://travis-ci.org/ghc/ghc) -There are two options of using this branch: manual, and Nix-based. +This is the source tree for [GHC][1], a compiler and interactive +environment for the Haskell functional programming language. -Manual ------- - -This code should build, but I have tested it only on `DEBUG` settings; -I recommend using build style `devel2` in `build.mk`. - -Here is a minimal script you can follow to build this at home; -see the [GHC Building Guide] [3] for more info. - -~~~ -git clone https://github.com/goldfirere/ghc.git -cd ghc -git checkout nokinds -git remote set-url origin git://git.haskell.org/ghc.git # so submodules work -git submodule update --init -cd mk -cp build.mk.sample build.mk -## edit build.mk to uncomment the line to choose the `devel2` configuration -cd .. -perl boot -./configure -make -~~~ - -Check out the `testsuite/tests/dependent/should_compile` directory for -a few sample programs that should compile on this fork of GHC. - -For more information about GHC, visit [GHC's web site][1]. +For more information, visit [GHC's web site][1]. Information for developers of GHC can be found on the [GHC Trac][2]. -Nix-based ---------- - -Thanks to @deepfire, this branch is available in Nixpkgs, which means that with -some effort it can be fairly automatically employed to build any package from -Hackage. This way, though, requires that one installs the Nix package manager in -parallel with the system package manager -- and this option is currently -unavailable on Windows. - -Here are the instructions: - -1. To install the Nix package manager, taking over /nix for package storage: - - curl https://nixos.org/nix/install | sh - -2. Make Nix use the `master` repository of Nixpkgs package definitions: - git clone https://github.com/NixOS/nixpkgs.git - pushd ~/.nix-defexpr - rm -rf channels - ln -s ../nixpkgs - popd - echo 'export NIX_PATH=nixpkgs=/home/------/nixpkgs' >> ~/.bashrc - export NIX_PATH=nixpkgs=/home/------/nixpkgs +Getting the Source +================== -3. [OPTIONAL] To enable prebuilt binaries from Peter Simons/NixOS Hydra servers: +There are two ways to get a source tree: - sudo mkdir /etc/nix - echo 'binary-caches = http://hydra.nixos.org/ http://hydra.cryp.to/' | sudo dd of=/etc/nix/nix.conf + 1. *Download source tarballs* - # If you don't do that, everything will still work, just it'll have - # to build everything from source. + Download the GHC source distribution: -4. Enter a shell with `ghc-nokinds` available: + ghc--src.tar.bz2 - nix-shell -p haskell.compiler.ghcNokinds + which contains GHC itself and the "boot" libraries. -5. See it's indeed `nokinds`: + 2. *Check out the source code from git* - wget https://raw.githubusercontent.com/goldfirere/ghc/nokinds/testsuite/tests/dependent/should_compile/KindEqualities2.hs - runhaskell KindEqualities2.hs + $ git clone --recursive git://git.haskell.org/ghc.git -To apply 'nokinds' to building packages from Hackage, the best option would be -to follow instructions from the "Nix loves Haskell" talk by Peter Simons: + Note: cloning GHC from Github requires a special setup. See [Getting a GHC + repository from Github] [7]. - http://cryp.to/nixos-meetup-3-slides.pdf + **DO NOT submit pull request directly to the github repo.** + *See the GHC team's working conventions re [how to contribute a patch to GHC](http://ghc.haskell.org/trac/ghc/wiki/WorkingConventions/FixingBugs "ghc.haskell.org/trac/ghc/wiki/WorkingConventions/FixingBug").* -..where the relevant compiler name would be "ghcNokinds". Building & Installing ===================== From git at git.haskell.org Fri Dec 11 23:35:56 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 11 Dec 2015 23:35:56 +0000 (UTC) Subject: [commit: ghc] master: haddock: Fix submodule commit to point to ghc-head (a6e0394) Message-ID: <20151211233556.EA4173A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a6e03945a75fa541b84e433e40eae8dd081d4cbf/ghc >--------------------------------------------------------------- commit a6e03945a75fa541b84e433e40eae8dd081d4cbf Author: Austin Seipp Date: Fri Dec 11 17:34:26 2015 -0600 haddock: Fix submodule commit to point to ghc-head 6746549772c5 accidentally pointed it to a branch (wip/rae-nokinds), before rebasing it onto ghc-head. Signed-off-by: Austin Seipp >--------------------------------------------------------------- a6e03945a75fa541b84e433e40eae8dd081d4cbf utils/haddock | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/haddock b/utils/haddock index bd61e8e..0fc8cfd 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit bd61e8e22b11d1c4f03dd6ddc45a794e3362d45c +Subproject commit 0fc8cfd532f5dfd12b5504f44a2b3c9fb659cd87 From git at git.haskell.org Fri Dec 11 23:35:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 11 Dec 2015 23:35:59 +0000 (UTC) Subject: [commit: ghc] master: Revert .gitmodules changes from 6746549772c5 (b5d5d83) Message-ID: <20151211233559.89D793A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b5d5d83122c93c2a25839127edfd6b2df7ed6928/ghc >--------------------------------------------------------------- commit b5d5d83122c93c2a25839127edfd6b2df7ed6928 Author: Austin Seipp Date: Fri Dec 11 17:36:20 2015 -0600 Revert .gitmodules changes from 6746549772c5 Signed-off-by: Austin Seipp >--------------------------------------------------------------- b5d5d83122c93c2a25839127edfd6b2df7ed6928 .gitmodules | 58 +++++++++++++++++++++++++++++----------------------------- 1 file changed, 29 insertions(+), 29 deletions(-) diff --git a/.gitmodules b/.gitmodules index 26b4fa0..73ce0d1 100644 --- a/.gitmodules +++ b/.gitmodules @@ -1,119 +1,119 @@ [submodule "libraries/binary"] path = libraries/binary - url = http://git.haskell.org/packages/binary.git + url = ../packages/binary.git ignore = untracked [submodule "libraries/bytestring"] path = libraries/bytestring - url = http://git.haskell.org/packages/bytestring.git + url = ../packages/bytestring.git ignore = untracked [submodule "libraries/Cabal"] path = libraries/Cabal - url = http://git.haskell.org/packages/Cabal.git + url = ../packages/Cabal.git ignore = untracked [submodule "libraries/containers"] path = libraries/containers - url = http://git.haskell.org/packages/containers.git + url = ../packages/containers.git ignore = untracked [submodule "libraries/haskeline"] path = libraries/haskeline - url = http://git.haskell.org/packages/haskeline.git + url = ../packages/haskeline.git ignore = untracked [submodule "libraries/pretty"] path = libraries/pretty - url = http://git.haskell.org/packages/pretty.git + url = ../packages/pretty.git ignore = untracked [submodule "libraries/terminfo"] path = libraries/terminfo - url = http://git.haskell.org/packages/terminfo.git + url = ../packages/terminfo.git ignore = untracked [submodule "libraries/transformers"] path = libraries/transformers - url = http://git.haskell.org/packages/transformers.git + url = ../packages/transformers.git ignore = untracked [submodule "libraries/xhtml"] path = libraries/xhtml - url = http://git.haskell.org/packages/xhtml.git + url = ../packages/xhtml.git ignore = untracked [submodule "libraries/Win32"] path = libraries/Win32 - url = http://git.haskell.org/packages/Win32.git + url = ../packages/Win32.git ignore = untracked [submodule "libraries/primitive"] path = libraries/primitive - url = http://git.haskell.org/packages/primitive.git + url = ../packages/primitive.git ignore = untracked [submodule "libraries/vector"] path = libraries/vector - url = http://git.haskell.org/packages/vector.git + url = ../packages/vector.git ignore = untracked [submodule "libraries/time"] path = libraries/time - url = http://git.haskell.org/packages/time.git + url = ../packages/time.git ignore = untracked [submodule "libraries/random"] path = libraries/random - url = http://git.haskell.org/packages/random.git + url = ../packages/random.git ignore = untracked [submodule "libraries/array"] path = libraries/array - url = http://git.haskell.org/packages/array.git + url = ../packages/array.git ignore = none [submodule "libraries/deepseq"] path = libraries/deepseq - url = http://git.haskell.org/packages/deepseq.git + url = ../packages/deepseq.git ignore = none [submodule "libraries/directory"] path = libraries/directory - url = http://git.haskell.org/packages/directory.git + url = ../packages/directory.git ignore = none [submodule "libraries/filepath"] path = libraries/filepath - url = http://git.haskell.org/packages/filepath.git + url = ../packages/filepath.git ignore = none [submodule "libraries/hoopl"] path = libraries/hoopl - url = http://git.haskell.org/packages/hoopl.git + url = ../packages/hoopl.git ignore = none [submodule "libraries/hpc"] path = libraries/hpc - url = http://git.haskell.org/packages/hpc.git + url = ../packages/hpc.git ignore = none [submodule "libraries/process"] path = libraries/process - url = http://git.haskell.org/packages/process.git + url = ../packages/process.git ignore = none [submodule "libraries/unix"] path = libraries/unix - url = http://git.haskell.org/packages/unix.git + url = ../packages/unix.git ignore = none [submodule "libraries/parallel"] path = libraries/parallel - url = http://git.haskell.org/packages/parallel.git + url = ../packages/parallel.git ignore = none [submodule "libraries/stm"] path = libraries/stm - url = http://git.haskell.org/packages/stm.git + url = ../packages/stm.git ignore = none [submodule "libraries/dph"] path = libraries/dph - url = http://git.haskell.org/packages/dph.git + url = ../packages/dph.git ignore = none [submodule "utils/haddock"] path = utils/haddock - url = http://git.haskell.org/haddock.git + url = ../haddock.git ignore = none branch = ghc-head [submodule "nofib"] path = nofib - url = http://git.haskell.org/nofib.git + url = ../nofib.git ignore = none [submodule "utils/hsc2hs"] path = utils/hsc2hs - url = http://git.haskell.org/hsc2hs.git + url = ../hsc2hs.git ignore = none [submodule "libffi-tarballs"] path = libffi-tarballs - url = http://git.haskell.org/libffi-tarballs.git + url = ../libffi-tarballs.git ignore = none [submodule ".arc-linters/arcanist-external-json-linter"] path = .arc-linters/arcanist-external-json-linter From git at git.haskell.org Fri Dec 11 23:51:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 11 Dec 2015 23:51:40 +0000 (UTC) Subject: [commit: ghc] master: rm rae.txt (a459451) Message-ID: <20151211235140.D02983A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a459451f6c1b292129994dbc13ef6eaaffa11864/ghc >--------------------------------------------------------------- commit a459451f6c1b292129994dbc13ef6eaaffa11864 Author: Austin Seipp Date: Fri Dec 11 17:52:15 2015 -0600 rm rae.txt Signed-off-by: Austin Seipp >--------------------------------------------------------------- a459451f6c1b292129994dbc13ef6eaaffa11864 rae.txt | 319 ---------------------------------------------------------------- 1 file changed, 319 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a459451f6c1b292129994dbc13ef6eaaffa11864 From git at git.haskell.org Sat Dec 12 02:53:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 12 Dec 2015 02:53:15 +0000 (UTC) Subject: [commit: ghc] master: Test case for #7961. (68f198f) Message-ID: <20151212025315.D7C973A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/68f198f50ca6439957a65a95ce6e087d43b56eed/ghc >--------------------------------------------------------------- commit 68f198f50ca6439957a65a95ce6e087d43b56eed Author: Richard Eisenberg Date: Fri Dec 11 21:51:37 2015 -0500 Test case for #7961. Test case: dependent/shoud_compile/TypeLevelVec >--------------------------------------------------------------- 68f198f50ca6439957a65a95ce6e087d43b56eed .../tests/dependent/should_compile/TypeLevelVec.hs | 26 ++++++++++++++++++++++ testsuite/tests/dependent/should_compile/all.T | 1 + 2 files changed, 27 insertions(+) diff --git a/testsuite/tests/dependent/should_compile/TypeLevelVec.hs b/testsuite/tests/dependent/should_compile/TypeLevelVec.hs new file mode 100644 index 0000000..19f605c --- /dev/null +++ b/testsuite/tests/dependent/should_compile/TypeLevelVec.hs @@ -0,0 +1,26 @@ +{-# LANGUAGE TypeInType, UnicodeSyntax, GADTs, NoImplicitPrelude, + TypeOperators, TypeFamilies #-} +{-# OPTIONS_GHC -fno-warn-unticked-promoted-constructors #-} + +module TypeLevelVec where + +import Data.Kind + +data ? ? Type where + O ? ? + S ? ? ? ? + +type family x + y where + O + n = n + S m + n = S (m + n) +infixl 5 + + +data Vec ? ? ? Type ? Type where + Nil ? Vec O a + (:>) ? a ? Vec n a ? Vec (S n) a +infixr 8 :> + +type family (x ? Vec n a) ++ (y ? Vec m a) ? Vec (n + m) a where + Nil ++ y = y + (x :> xs) ++ y = x :> (xs ++ y) +infixl 5 ++ diff --git a/testsuite/tests/dependent/should_compile/all.T b/testsuite/tests/dependent/should_compile/all.T index 0f231db..1724ff6 100644 --- a/testsuite/tests/dependent/should_compile/all.T +++ b/testsuite/tests/dependent/should_compile/all.T @@ -8,3 +8,4 @@ test('RAE_T32b', only_ways('normal'), compile, ['']) test('KindLevels', normal, compile, ['']) test('RaeBlogPost', normal, compile, ['']) test('mkGADTVars', normal, compile, ['']) +test('TypeLevelVec',normal,compile, ['']) From git at git.haskell.org Sat Dec 12 03:07:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 12 Dec 2015 03:07:00 +0000 (UTC) Subject: [commit: ghc] master: Test #9017 in polykinds/T9017 (779dfea) Message-ID: <20151212030700.5A5943A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/779dfea1d9cc713d9b1e26bb559e8da309b2aeec/ghc >--------------------------------------------------------------- commit 779dfea1d9cc713d9b1e26bb559e8da309b2aeec Author: Richard Eisenberg Date: Fri Dec 11 22:07:06 2015 -0500 Test #9017 in polykinds/T9017 >--------------------------------------------------------------- 779dfea1d9cc713d9b1e26bb559e8da309b2aeec testsuite/tests/polykinds/T9017.hs | 8 ++++++++ testsuite/tests/polykinds/T9017.stderr | 26 ++++++++++++++++++++++++++ testsuite/tests/polykinds/all.T | 1 + 3 files changed, 35 insertions(+) diff --git a/testsuite/tests/polykinds/T9017.hs b/testsuite/tests/polykinds/T9017.hs new file mode 100644 index 0000000..7f93f54 --- /dev/null +++ b/testsuite/tests/polykinds/T9017.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE PolyKinds #-} + +module T9017 where + +import Control.Arrow + +foo :: a b (m b) +foo = arr return diff --git a/testsuite/tests/polykinds/T9017.stderr b/testsuite/tests/polykinds/T9017.stderr new file mode 100644 index 0000000..857d11a --- /dev/null +++ b/testsuite/tests/polykinds/T9017.stderr @@ -0,0 +1,26 @@ + +T9017.hs:8:7: error: + ? Couldn't match kind ?k? with ?*? + ?k? is a rigid type variable bound by + the type signature for: + foo :: forall k k1 (a :: k1 -> k -> *) (b :: k1) (m :: k1 -> k). + a b (m b) + at T9017.hs:7:8 + When matching the kind of ?a? + ? In the expression: arr return + In an equation for ?foo?: foo = arr return + ? Relevant bindings include + foo :: a b (m b) (bound at T9017.hs:8:1) + +T9017.hs:8:7: error: + ? Couldn't match kind ?k1? with ?*? + ?k1? is a rigid type variable bound by + the type signature for: + foo :: forall k k1 (a :: k1 -> k -> *) (b :: k1) (m :: k1 -> k). + a b (m b) + at T9017.hs:7:8 + When matching the kind of ?a? + ? In the expression: arr return + In an equation for ?foo?: foo = arr return + ? Relevant bindings include + foo :: a b (m b) (bound at T9017.hs:8:1) diff --git a/testsuite/tests/polykinds/all.T b/testsuite/tests/polykinds/all.T index a93ad8b..0005abc 100644 --- a/testsuite/tests/polykinds/all.T +++ b/testsuite/tests/polykinds/all.T @@ -126,3 +126,4 @@ test('T10934', normal, compile, ['']) test('T11142', normal, compile_fail, ['']) test('SigTvKinds', expect_broken(11203), compile, ['']) test('SigTvKinds2', expect_broken(11203), compile_fail, ['']) +test('T9017', normal, compile_fail, ['']) From git at git.haskell.org Sat Dec 12 08:38:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 12 Dec 2015 08:38:11 +0000 (UTC) Subject: [commit: ghc] master: Frontend plugins. (a3c2a26) Message-ID: <20151212083811.3C2073A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a3c2a26b3af034f09c960b2dad38f73be7e3a655/ghc >--------------------------------------------------------------- commit a3c2a26b3af034f09c960b2dad38f73be7e3a655 Author: Edward Z. Yang Date: Thu Dec 10 20:41:53 2015 -0800 Frontend plugins. Summary: Frontend plugins enable users to write plugins to replace GHC major modes. E.g. instead of saying ghc --make A B C a user can now say ghc --frontend GHC.Frontend.Shake A B C which might provide an alternative implementation of a multi-module build. For more details, see the manual entry. Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: simonmar, bgamari, austin, simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1598 GHC Trac Issues: #11194 >--------------------------------------------------------------- a3c2a26b3af034f09c960b2dad38f73be7e3a655 compiler/main/DynFlags.hs | 6 ++++ compiler/main/DynamicLoading.hs | 19 +++++++---- compiler/main/Plugins.hs | 10 ++++++ compiler/prelude/PrelNames.hs | 6 +++- docs/users_guide/extending_ghc.rst | 50 +++++++++++++++++++++++++++++ ghc/Main.hs | 27 ++++++++++++++++ testsuite/.gitignore | 1 + testsuite/tests/plugins/FrontendPlugin.hs | 52 +++++++++++++++++++++++++++++++ testsuite/tests/plugins/Makefile | 7 +++++ testsuite/tests/plugins/all.T | 3 ++ testsuite/tests/plugins/frontend01.hs | 1 + testsuite/tests/plugins/frontend01.stdout | 4 +++ 12 files changed, 179 insertions(+), 7 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a3c2a26b3af034f09c960b2dad38f73be7e3a655 From git at git.haskell.org Sat Dec 12 16:39:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 12 Dec 2015 16:39:31 +0000 (UTC) Subject: [commit: ghc] master: Implement -fwarn-missing-pat-syn-sigs (1883afb) Message-ID: <20151212163931.8084B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1883afb2eee88c828adf6aa8014bab64dd6e8096/ghc >--------------------------------------------------------------- commit 1883afb2eee88c828adf6aa8014bab64dd6e8096 Author: Matthew Pickering Date: Sat Dec 12 16:38:07 2015 +0000 Implement -fwarn-missing-pat-syn-sigs This adds a warning when a pattern synonym is not accompanied by a signature in the style of `-fwarn-missing-sigs`. It is turned on by -Wall. If the user specifies, `-fwarn-missing-exported-signatures` with `-fwarn-missing-pat-syn-sigs` then it will only warn when the pattern synonym is exported. Test Plan: ./validate Reviewers: hvr, austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1596 GHC Trac Issues: #11053 >--------------------------------------------------------------- 1883afb2eee88c828adf6aa8014bab64dd6e8096 compiler/hsSyn/HsBinds.hs | 13 +++++- compiler/main/DynFlags.hs | 7 +++- compiler/rename/RnNames.hs | 50 ++++++++++++++++-------- docs/users_guide/7.12.1-notes.rst | 4 ++ docs/users_guide/using-warnings.rst | 11 ++++++ libraries/base/GHC/Exception.hs | 1 + testsuite/tests/patsyn/should_compile/all.T | 2 - testsuite/tests/patsyn/should_fail/T11053.hs | 18 +++++++++ testsuite/tests/patsyn/should_fail/T11053.stderr | 19 +++++++++ testsuite/tests/patsyn/should_fail/all.T | 1 + 10 files changed, 104 insertions(+), 22 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1883afb2eee88c828adf6aa8014bab64dd6e8096 From git at git.haskell.org Sat Dec 12 17:38:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 12 Dec 2015 17:38:51 +0000 (UTC) Subject: [commit: ghc] master: Dwarf: Use .short instead of .hword on Darwin (3640ae9) Message-ID: <20151212173851.E99FB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3640ae92fc1ffa283425203bba3dbf231fcb3e52/ghc >--------------------------------------------------------------- commit 3640ae92fc1ffa283425203bba3dbf231fcb3e52 Author: Ben Gamari Date: Sat Dec 12 17:00:10 2015 +0100 Dwarf: Use .short instead of .hword on Darwin Apparently gnu as uses `.short` as a synonym for `.word`. To emit a 16-bit value one would use `.hword`. However, Darwin doesn't support `.hword`, instead taking `.short` to mean a 16-bit value. The insanity is nearly unbearable! OS X reference: https://developer.apple.com/library/mac/documentation/DeveloperTools/Ref erence/Assembler/040-Assembler_Directives/asm_directives.html#//apple_re f/doc/uid/TP30000823-TPXREF101 gnu as reference: https://sourceware.org/binutils/docs/as/hword.html#hword Test Plan: Validate Reviewers: austin Reviewed By: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1602 GHC Trac Issues: #11202 >--------------------------------------------------------------- 3640ae92fc1ffa283425203bba3dbf231fcb3e52 compiler/nativeGen/Dwarf/Types.hs | 9 ++++++++- 1 file changed, 8 insertions(+), 1 deletion(-) diff --git a/compiler/nativeGen/Dwarf/Types.hs b/compiler/nativeGen/Dwarf/Types.hs index 91a5e41..e80f2a1 100644 --- a/compiler/nativeGen/Dwarf/Types.hs +++ b/compiler/nativeGen/Dwarf/Types.hs @@ -477,7 +477,14 @@ pprByte x = ptext (sLit "\t.byte ") <> ppr (fromIntegral x :: Word) -- | Assembly for a two-byte constant integer pprHalf :: Word16 -> SDoc -pprHalf x = ptext (sLit "\t.hword ") <> ppr (fromIntegral x :: Word) +pprHalf x = sdocWithPlatform $ \plat -> + -- Naturally Darwin doesn't support `.hword` and binutils uses `.short` + -- as a synonym for `.word` (but only some of the time!). The madness + -- is nearly too much to bear. + let dir = case platformOS plat of + OSDarwin -> text ".short" + _ -> text ".hword" + in text "\t" <> dir <+> ppr (fromIntegral x :: Word) -- | Assembly for a constant DWARF flag pprFlag :: Bool -> SDoc From git at git.haskell.org Sat Dec 12 17:38:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 12 Dec 2015 17:38:55 +0000 (UTC) Subject: [commit: ghc] master: Make -XStrict imply -XStrictData (4935b48) Message-ID: <20151212173855.225FE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4935b48bdbed916507d585f9185960916ed5f04b/ghc >--------------------------------------------------------------- commit 4935b48bdbed916507d585f9185960916ed5f04b Author: Adam Sandberg Eriksson Date: Sat Dec 12 16:58:40 2015 +0100 Make -XStrict imply -XStrictData Fixes #11182. Reviewers: bgamari, simonpj, austin Reviewed By: simonpj, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1592 GHC Trac Issues: #11182 >--------------------------------------------------------------- 4935b48bdbed916507d585f9185960916ed5f04b compiler/main/DynFlags.hs | 1 + testsuite/tests/driver/T11182.hs | 10 ++++++++++ testsuite/tests/driver/T11182.stdout | 1 + testsuite/tests/driver/all.T | 1 + 4 files changed, 13 insertions(+) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 6487379..63cfe03 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -3381,6 +3381,7 @@ impliedXFlags , (Opt_DuplicateRecordFields, turnOn, Opt_DisambiguateRecordFields) , (Opt_TemplateHaskell, turnOn, Opt_TemplateHaskellQuotes) + , (Opt_Strict, turnOn, Opt_StrictData) ] -- Note [Documenting optimisation flags] diff --git a/testsuite/tests/driver/T11182.hs b/testsuite/tests/driver/T11182.hs new file mode 100644 index 0000000..a8bedf4 --- /dev/null +++ b/testsuite/tests/driver/T11182.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE Strict #-} +-- | Strict should imply StrictData +module Main where + +data Lazy a = Lazy ~a + +main :: IO () +main = + case Lazy undefined of + Lazy _ -> putStrLn "Lazy" diff --git a/testsuite/tests/driver/T11182.stdout b/testsuite/tests/driver/T11182.stdout new file mode 100644 index 0000000..e2749de --- /dev/null +++ b/testsuite/tests/driver/T11182.stdout @@ -0,0 +1 @@ +Lazy diff --git a/testsuite/tests/driver/all.T b/testsuite/tests/driver/all.T index 5c0de6e..12522df 100644 --- a/testsuite/tests/driver/all.T +++ b/testsuite/tests/driver/all.T @@ -460,3 +460,4 @@ test('T9360b', normal, run_command, ['{compiler} -e "" --interactive']) test('T10970', normal, compile_and_run, ['-hide-all-packages -package base -package containers']) test('T10970a', normal, compile_and_run, ['']) test('T4931', normal, compile_and_run, ['']) +test('T11182', normal, compile_and_run, ['']) From git at git.haskell.org Sat Dec 12 17:38:58 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 12 Dec 2015 17:38:58 +0000 (UTC) Subject: [commit: ghc] master: Rework the Implicit CallStack solver to handle local lets. (3ec8288) Message-ID: <20151212173858.CB6C33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3ec8288a18d57fb856e257905897daae237a1d5d/ghc >--------------------------------------------------------------- commit 3ec8288a18d57fb856e257905897daae237a1d5d Author: Eric Seidel Date: Sat Dec 12 16:53:50 2015 +0100 Rework the Implicit CallStack solver to handle local lets. We can't just solve CallStack constraints indiscriminately when they occur in the RHS of a let-binder. The top-level given CallStack (if any) will not be in scope, so I've re-worked the CallStack solver as follows: 1. CallStacks are treated like regular IPs unless one of the following two rules apply. 2. In a function call, we push the call-site onto a NEW wanted CallStack, which GHC will solve as a regular IP (either directly from a given, or by quantifying over it in a local let). 3. If, after the constraint solver is done, any wanted CallStacks remain, we default them to the empty CallStack. This rule exists mainly to clean up after rule 2 in a top-level binder with no given CallStack. In rule (2) we have to be careful to emit the new wanted with an IPOccOrigin instead of an OccurrenceOf origin, so rule (2) doesn't fire again. This is a bit shady but I've updated the Note to explain the trick. Test Plan: validate Reviewers: simonpj, austin, bgamari, hvr Reviewed By: simonpj, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1422 GHC Trac Issues: #10845 >--------------------------------------------------------------- 3ec8288a18d57fb856e257905897daae237a1d5d .gitignore | 1 + compiler/deSugar/DsBinds.hs | 3 +- compiler/typecheck/TcEvidence.hs | 119 ++++++++++----------- compiler/typecheck/TcHsSyn.hs | 2 - compiler/typecheck/TcInteract.hs | 77 +++++++------ compiler/typecheck/TcRnTypes.hs | 17 ++- compiler/typecheck/TcSimplify.hs | 38 ++++++- compiler/utils/Outputable.hs | 5 +- docs/users_guide/7.12.1-notes.rst | 46 ++++---- docs/users_guide/glasgow_exts.rst | 63 +++++------ libraries/base/GHC/Exception.hs | 40 ++++--- libraries/base/GHC/IO/Exception.hs | 2 +- libraries/base/GHC/Stack.hs | 6 +- libraries/base/GHC/Stack/Types.hs | 59 +++++++--- libraries/base/changelog.md | 12 ++- testsuite/.gitignore | 1 + testsuite/tests/codeGen/should_run/cgrun059.stderr | 1 + .../tests/concurrent/should_run/conc021.stderr | 1 + .../tests/ghci.debugger/scripts/break011.stdout | 8 +- .../tests/ghci.debugger/scripts/break017.stdout | 3 +- .../tests/ghci.debugger/scripts/print033.stdout | 2 +- testsuite/tests/ghci/scripts/T5557.stdout | 6 +- testsuite/tests/ghci/scripts/T8959.stdout | 9 +- testsuite/tests/ghci/scripts/ghci013.stdout | 2 +- testsuite/tests/ghci/scripts/ghci046.stdout | 4 +- testsuite/tests/ghci/scripts/ghci055.stdout | 7 +- .../should_compile/ExtraConstraints3.stderr | 4 +- .../tests/partial-sigs/should_fail/T10999.stderr | 7 +- .../tests/pmcheck/should_compile/T3927b.stderr | 39 ------- testsuite/tests/th/T1849.script | 6 +- testsuite/tests/typecheck/should_run/IPLocation.hs | 26 ++--- .../tests/typecheck/should_run/IPLocation.stdout | 36 +++---- testsuite/tests/typecheck/should_run/T10845.hs | 20 ++++ testsuite/tests/typecheck/should_run/T10845.stdout | 5 + testsuite/tests/typecheck/should_run/T10846.hs | 20 ++++ testsuite/tests/typecheck/should_run/T10846.stdout | 3 + testsuite/tests/typecheck/should_run/T8119.stdout | 3 +- testsuite/tests/typecheck/should_run/all.T | 2 + 38 files changed, 396 insertions(+), 309 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 3ec8288a18d57fb856e257905897daae237a1d5d From git at git.haskell.org Sat Dec 12 17:39:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 12 Dec 2015 17:39:01 +0000 (UTC) Subject: [commit: ghc] master: Build system: fix 'make install-strip' in bindist (aaed24a) Message-ID: <20151212173901.709AC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/aaed24a4e0d8fa0d49aca167fddfb8b606755e05/ghc >--------------------------------------------------------------- commit aaed24a4e0d8fa0d49aca167fddfb8b606755e05 Author: Thomas Miedema Date: Sat Dec 12 17:02:28 2015 +0100 Build system: fix 'make install-strip' in bindist The INSTALL_PROGRAM variable is set in mk/config.mk, so we have to include that file before using it. Running 'make install' before './configure' in a bindist will now also display a nice message. Reviewers: hvr, austin, bgamari Reviewed By: bgamari Differential Revision: https://phabricator.haskell.org/D1604 GHC Trac Issues: #1851 >--------------------------------------------------------------- aaed24a4e0d8fa0d49aca167fddfb8b606755e05 Makefile | 25 +++++++++++++------------ rules/haddock.mk | 2 ++ 2 files changed, 15 insertions(+), 12 deletions(-) diff --git a/Makefile b/Makefile index 348375f..6be584f 100644 --- a/Makefile +++ b/Makefile @@ -18,6 +18,18 @@ MAKEFLAGS += --no-builtin-rules .SUFFIXES: +ifneq "$(filter maintainer-clean distclean clean clean_% help,$(MAKECMDGOALS))" "" +-include mk/config.mk +else +include mk/config.mk +ifeq "$(ProjectVersion)" "" +$(error Please run ./configure first) +endif +endif + +include mk/custom-settings.mk + + ifeq "$(wildcard distrib/)" "" # We're in a bindist @@ -45,7 +57,7 @@ install show: .PHONY: install-strip install-strip: # See Note [install-strip]. - $(MAKE) --no-print-directory -f ghc.mk INSTALL_PROGRAM='$(INSTALL_PROGRAM) -s' install + $(MAKE) --no-print-directory -f ghc.mk INSTALL_PROGRAM='$(INSTALL_PROGRAM) -s' install BINDIST=YES NO_INCLUDE_DEPS=YES else @@ -58,17 +70,6 @@ default : all help: @cat MAKEHELP.md -ifneq "$(filter maintainer-clean distclean clean clean_% help,$(MAKECMDGOALS))" "" --include mk/config.mk -else -include mk/config.mk -ifeq "$(ProjectVersion)" "" -$(error Please run ./configure first) -endif -endif - -include mk/custom-settings.mk - # Verify that stage 0 LLVM backend isn't affected by Bug #9439 if needed ifeq "$(GHC_LLVM_AFFECTED_BY_9439)" "1" ifneq "$(findstring -fllvm,$(SRC_HC_OPTS) $(GhcHcOpts) $(GhcStage1HcOpts))" "" diff --git a/rules/haddock.mk b/rules/haddock.mk index e716bb8..f6978a7 100644 --- a/rules/haddock.mk +++ b/rules/haddock.mk @@ -10,11 +10,13 @@ # # ----------------------------------------------------------------------------- +ifneq "$(BINDIST)" "YES" HADDOCK_VER := $(shell grep "^version:" utils/haddock/haddock.cabal | sed "s/version: *//") HADDOCK_MAJOR_VER := $(shell echo $(HADDOCK_VER) | sed 's/\([0-9]\{1,\}\)\.\([0-9]\{1,\}\)\.\([0-9]\{1,\}\)/\1/') HADDOCK_MINOR_VER := $(shell echo $(HADDOCK_VER) | sed 's/\([0-9]\{1,\}\)\.\([0-9]\{1,\}\)\.\([0-9]\{1,\}\)/\2/') HADDOCK_PATCH_VER := $(shell echo $(HADDOCK_VER) | sed 's/\([0-9]\{1,\}\)\.\([0-9]\{1,\}\)\.\([0-9]\{1,\}\)/\3/') HADDOCK_VERSION_STRING := $(shell echo $$(($(HADDOCK_MAJOR_VER) * 1000 + $(HADDOCK_MINOR_VER) * 10 + $(HADDOCK_PATCH_VER)))) +endif define haddock # args: $1 = dir, $2 = distdir $(call trace, haddock($1,$2)) From git at git.haskell.org Sat Dec 12 19:01:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 12 Dec 2015 19:01:30 +0000 (UTC) Subject: [commit: ghc] master: Refactor type families in Template Haskell (9934819) Message-ID: <20151212190130.07BCA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9934819f3bb086bba91874cde4f0b17b30b10451/ghc >--------------------------------------------------------------- commit 9934819f3bb086bba91874cde4f0b17b30b10451 Author: John Leo Date: Sat Dec 12 19:28:18 2015 +0100 Refactor type families in Template Haskell Fixes #10902. Test Plan: validate Reviewers: goldfire, austin, hvr, jstolarek, bgamari Reviewed By: jstolarek, bgamari Subscribers: hvr, thomie Differential Revision: https://phabricator.haskell.org/D1570 GHC Trac Issues: #10902 >--------------------------------------------------------------- 9934819f3bb086bba91874cde4f0b17b30b10451 compiler/hsSyn/Convert.hs | 29 ++++++++++++++-------- compiler/typecheck/TcSplice.hs | 14 +++++------ docs/users_guide/7.12.1-notes.rst | 5 ++++ libraries/template-haskell/Language/Haskell/TH.hs | 2 +- .../template-haskell/Language/Haskell/TH/Lib.hs | 14 ++++++----- .../template-haskell/Language/Haskell/TH/Ppr.hs | 21 ++++++++-------- .../template-haskell/Language/Haskell/TH/Syntax.hs | 18 ++++++++------ libraries/template-haskell/changelog.md | 7 ++++++ testsuite/tests/indexed-types/should_fail/T9160.hs | 3 ++- .../tests/indexed-types/should_fail/T9160.stderr | 2 +- testsuite/tests/th/ClosedFam2TH.hs | 11 ++++---- testsuite/tests/th/T10306.hs | 4 +-- testsuite/tests/th/T6018th.hs | 18 +++++++------- testsuite/tests/th/T8028.hs | 4 +-- testsuite/tests/th/T8028a.hs | 2 +- testsuite/tests/th/T8884.hs | 10 +++++--- testsuite/tests/th/TH_RichKinds2.hs | 15 +++++------ testsuite/tests/th/TH_RichKinds2.stderr | 2 +- 18 files changed, 106 insertions(+), 75 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 9934819f3bb086bba91874cde4f0b17b30b10451 From git at git.haskell.org Sat Dec 12 19:46:20 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 12 Dec 2015 19:46:20 +0000 (UTC) Subject: [commit: ghc] master: Fix release notes markup (59cc6ed) Message-ID: <20151212194620.8D3853A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/59cc6edbada5f87b917805627294caf3f602052a/ghc >--------------------------------------------------------------- commit 59cc6edbada5f87b917805627294caf3f602052a Author: Ben Gamari Date: Sat Dec 12 20:46:20 2015 +0100 Fix release notes markup >--------------------------------------------------------------- 59cc6edbada5f87b917805627294caf3f602052a docs/users_guide/7.12.1-notes.rst | 76 ++++++++++++++++++++++++++------------- 1 file changed, 51 insertions(+), 25 deletions(-) diff --git a/docs/users_guide/7.12.1-notes.rst b/docs/users_guide/7.12.1-notes.rst index c0b1042..7932708 100644 --- a/docs/users_guide/7.12.1-notes.rst +++ b/docs/users_guide/7.12.1-notes.rst @@ -12,7 +12,36 @@ Highlights The highlights, since the 7.10 branch, are: -- TODO FIXME +- TODO FIXME + +- nokinds + +- Record pattern synonyms + +- ``-XDeriveAnyClass`` + +- More reliable DWARF debugging information + +- Injective type classes + +- Applicative ``do`` notation + +- Support for wildcards in data and type family instances + +- ``Strict`` and ``StrictData`` extensions, allowing modules to be compiled with + strict-by-default bindings. + +- ``DuplicateRecordFields``, allowing multiple datatypes to declare the same + record field names provided they are used unambiguously + +- Support for implicit parameters providing light-weight callstacks and source locations + +- User-defined error messages for type errors + +- A rewritten (and greatly improved) pattern exhaustiveness checker + +- The reworked users guide you are now reading + Full details ------------ @@ -23,20 +52,17 @@ Language - TODO FIXME. - The parser now supports Haddock comments on GADT data constructors. - For example, - - :: + For example :: - data Expr a where - -- | Just a normal sum - Sum :: Int -> Int -> Expr Int + data Expr a where + -- | Just a normal sum + Sum :: Int -> Int -> Expr Int - Implicit parameters of the new ``base`` type ``GHC.Stack.CallStack`` are treated specially in function calls, the solver automatically appends the source location of the call to the ``CallStack`` in - the environment. For example + the environment. For example :: - :: myerror :: (?callStack :: CallStack) => String -> a myerror msg = error (msg ++ "\n" ++ prettyCallStack ?callStack) @@ -84,12 +110,12 @@ Language pattern P :: a -> b -> (a, b) pattern P{x,y} = (x,y) - will allow `P` to be used like a record data constructor and also defines - selector functions `x :: (a, b) -> a` and `y :: (a, b) -> b`. + will allow ``P`` to be used like a record data constructor and also defines + selector functions ``x :: (a, b) -> a`` and ``y :: (a, b) -> b``. - Pattern synonyms can now be bundled with type constructors. For a pattern - synonym `P` and a type constructor `T`, `P` can be bundled with `T` so that - when `T` is imported `P` is also imported. With this change + synonym ``P`` and a type constructor ``T``, ``P`` can be bundled with ``T`` + so that when ``T`` is imported ``P`` is also imported. With this change a library author can provide either real data constructors or pattern synonyms in an opaque manner. See :ref:`pattern-synonyms` for details. :: @@ -127,7 +153,7 @@ Language import Bar (T(MkT)) In previous versions of GHC, this required a workaround via an - explicit export list in Bar. + explicit export list in ``Bar``. @@ -190,9 +216,9 @@ Compiler warnings makes sure the definition of ``Semigroup`` as a superclass of ``Monoid`` does not break any code. -- Added the ``-fwarn-missing-pat-syn-sigs`` flag. When enabled, this will issue - a warning when a pattern synonym definition doesn't have a type signature. - It is turned off by default but enabled by ``-Wall``. +- Added the ``-fwarn-missing-pat-syn-sigs`` flag. When enabled, this will issue + a warning when a pattern synonym definition doesn't have a type signature. + It is turned off by default but enabled by ``-Wall``. GHCi ~~~~ @@ -364,25 +390,25 @@ ghc strictness annotations as the user wrote them, whether from an imported module or not. -- Moved `startsVarSym`, `startsVarId`, `startsConSym`, `startsConId`, - `startsVarSymASCII`, and `isVarSymChar` from `Lexeme` to the `GHC.Lemexe` - module of the `ghc-boot` library. +- Moved ``startsVarSym``, ``startsVarId``, ``startsConSym``, ``startsConId``, + ``startsVarSymASCII``, and ``isVarSymChar`` from ``Lexeme`` to the + ``GHC.Lemexe`` module of the ``ghc-boot`` library. -- Add `isImport`, `isDecl`, and `isStmt` functions. +- Add ``isImport``, ``isDecl``, and ``isStmt`` functions. ghc-boot ~~~~~~~~ - This is an internal package. Use with caution. -- This package was renamed from `bin-package-db` to reflect its new purpose +- This package was renamed from ``bin-package-db`` to reflect its new purpose of containing intra-GHC functionality that needs to be shared across multiple GHC boot libraries. -- Added `GHC.Lexeme`, which contains functions for determining if a +- Added ``GHC.Lexeme``, which contains functions for determining if a character can be the first letter of a variable or data constructor in - Haskell, as defined by GHC. (These functions were moved from `Lexeme` - in `ghc`.) + Haskell, as defined by GHC. (These functions were moved from ``Lexeme`` + in ``ghc``.) ghc-prim ~~~~~~~~ From git at git.haskell.org Sat Dec 12 22:31:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 12 Dec 2015 22:31:29 +0000 (UTC) Subject: [commit: ghc] master: Remove redundant imports (669c5ed) Message-ID: <20151212223129.12BE53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/669c5ed6e67deb39648de614a2e58892807a6840/ghc >--------------------------------------------------------------- commit 669c5ed6e67deb39648de614a2e58892807a6840 Author: Richard Eisenberg Date: Sat Dec 12 17:31:31 2015 -0500 Remove redundant imports >--------------------------------------------------------------- 669c5ed6e67deb39648de614a2e58892807a6840 compiler/typecheck/Inst.hs | 1 - compiler/typecheck/TcArrows.hs | 1 - compiler/typecheck/TcRnTypes.hs | 1 - 3 files changed, 3 deletions(-) diff --git a/compiler/typecheck/Inst.hs b/compiler/typecheck/Inst.hs index bd27a18..ed12eff 100644 --- a/compiler/typecheck/Inst.hs +++ b/compiler/typecheck/Inst.hs @@ -43,7 +43,6 @@ import TysWiredIn ( heqDataCon ) import FunDeps import TcMType import Type -import Coercion ( Role(..) ) import TcType import HscTypes import Class( Class ) diff --git a/compiler/typecheck/TcArrows.hs b/compiler/typecheck/TcArrows.hs index f078403e..444b148 100644 --- a/compiler/typecheck/TcArrows.hs +++ b/compiler/typecheck/TcArrows.hs @@ -25,7 +25,6 @@ import TcEvidence import Id( mkLocalId ) import Inst import Name -import Coercion ( Role(..) ) import TysWiredIn import VarSet import TysPrim diff --git a/compiler/typecheck/TcRnTypes.hs b/compiler/typecheck/TcRnTypes.hs index b0c2e80..94b7478 100644 --- a/compiler/typecheck/TcRnTypes.hs +++ b/compiler/typecheck/TcRnTypes.hs @@ -129,7 +129,6 @@ import HscTypes import TcEvidence import TysWiredIn ( callStackTyCon, ipClass ) import Type -import CoAxiom ( Role ) import Class ( Class ) import TyCon ( TyCon ) import Coercion ( Coercion, mkHoleCo ) From git at git.haskell.org Sun Dec 13 12:41:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 13 Dec 2015 12:41:13 +0000 (UTC) Subject: [commit: ghc] master: configure: add support for 'sh4' (Trac #11209) (f48015b) Message-ID: <20151213124113.361223A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f48015bcac59960f6d266506a5f378c9bcf8f005/ghc >--------------------------------------------------------------- commit f48015bcac59960f6d266506a5f378c9bcf8f005 Author: Sergei Trofimovich Date: Sun Dec 13 12:36:47 2015 +0000 configure: add support for 'sh4' (Trac #11209) Debian has Renesas SH4 (SuperH) port with a triplet: sh4-linux-gnu Patch by glaubitz adds 'sh4' CPU to recognize target as ArchUnknown. Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- f48015bcac59960f6d266506a5f378c9bcf8f005 aclocal.m4 | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/aclocal.m4 b/aclocal.m4 index e0cd330..e46a19f 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -212,7 +212,7 @@ AC_DEFUN([FPTOOLS_SET_HASKELL_PLATFORM_VARS], mipsel) test -z "[$]2" || eval "[$]2=ArchMipsel" ;; - hppa|hppa1_1|ia64|m68k|rs6000|s390|s390x|sparc64|vax) + hppa|hppa1_1|ia64|m68k|rs6000|s390|s390x|sh4|sparc64|vax) test -z "[$]2" || eval "[$]2=ArchUnknown" ;; *) @@ -1825,6 +1825,9 @@ case "$1" in s390*) $2="s390" ;; + sh4) + $2="sh4" + ;; sparc64*) $2="sparc64" ;; From git at git.haskell.org Sun Dec 13 17:10:05 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 13 Dec 2015 17:10:05 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm's head updated: configure: add support for 'sh4' (Trac #11209) (f48015b) Message-ID: <20151213171005.0A09A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/gadtpm' now includes: d25f3c0 users_guide/glasgow_exts.rst: fix link markup 8a50610 Major Overhaul of Pattern Match Checking (Fixes #595) 43a31fe testsuite: haddock.compiler: Bump expected allocations a034031 extending_ghc.rst: fix broken link (Trac #10950) c5597bb Revert "Create empty dump files when there was nothing to dump" 7b29b0b Fix haddock syntax 0dd61fe Kill redundant patterns 934b3a0 Update test output 40fc353 Bump hoopl submodule ae4398d Improve performance for PM check on literals (Fixes #11160 and #11161) 99d01e1 Remove unused import in deSugar/TmOracle.hs 7af29da Use Autoconf's AC_USE_SYSTEM_EXTENSIONS cd9f3bf RTS: Rename InCall.stat struct field to .rstat 6ef351d On AIX we need -D_BSD defined in d40f5b7 PmExpr: Fix CPP unacceptable too clang's CPP 36a208f Use builtin ISO 8859-1 decoder in mkTextEncoding befc4e4 Check: More Clang/CPP wibbles e9220da Bump allocations for T783 dc33e4c T5642 is broken 96e67c0 T5642: Skip it entirely 5b2b7e3 Make callToPats deterministic in SpecConstr 1c9fd3f Case-of-empty-alts is trivial (Trac #11155) 28035c0 Add derived constraints for wildcard signatures 1cb3c8c Wibbles only 822141b Make -dppr-debug show contents of (TypeError ...) 1160dc5 Fix egregious error in eta-reduction of data families 31b482b Minor refactoring of user type errors 67565a7 Tidy user type errors in checkValidType 43a5970 Comments only 16aae60 T5642: Fix skip usage caa6851 testsuite: Rename pmcheck/T7669 to pmcheck/T7669a d4bf863 Update peak_megabytes_allocated for T9675 020375d Add linter to check for binaries accidentally added to repository 901cab1 lint: Add linter to catch uses of ASSERT macro that Clang dislikes c865c42 StgCmmMonad: Implement Outputable instance for Sequel for debugging e2c518e libdw: enable support only on i386 and amd64 81cf200 pmcheck: Comments about term equality representation 406444b pmcheck: Comments about undecidability of literal equality 8f28797 Fix broken linters when using python3 c714f8f Use git.h.o copy of arcanist-external-json-linter a14296c Temporarily disable external-json linters 51d08d8 Enable non-canonical Monad instance warnings for stage1/2 314bc99 ghc.mk: cleanup: use tab consistently d6512c7 ghc.mk: don't run mkUserGuidePart more than once 13ab2c6 ghc.mk: fix docs re-rebuilding 5f1e42f Allow to compile OSMem.c when MEM_NORESERVE is not available df67940 Make ghc.mk compatible with pedantic /bin/sh impls 986ceb1 Implement new `-fwarn-noncanonical-monoid-instances` 8b42214 Tweak use of AC_USE_SYSTEM_EXTENSIONS be92c28 Update hoopl submodule f5127c8 linters/check-cpp: Don't produce debug log 3ea4fb7 Documentation: escape characters in template-haskell Haddocks 42a5469 Ignore generated linter.log 3d55e41 ghc-pkg: Restore old behavior in colored version; fixes 6119 8cef8af Re-export data family when exporting a data instance without an export list 91e985c Minor stylistic fixes in glasgow_exts.rst 2110037 Add isImport, isDecl, and isStmt functions to GHC API d4bcd05 rts: Remove space before argument list in ASSERTs 700c42b Use TypeLits in the meta-data encoding of GHC.Generics 51a5e68 Refactor ConDecl 1bd40c8 Move checking for missing signatures to RnNames.reportUnusedNames 151c4b0 ghc-pkg: don't sort packages unnecessarily 04e1c27 rts: One more Clang-unfriendly CPP usage 0933331 Re-use `transformers`'s `MaybeT` rather than our own b292720 Remove redundant CPP conditionals 834f9a4 Get rid of tcView altogether 2f6e87a Introduce HasGhciState class and refactor use-sites 9f4ca5a Associate ErrorCall pattern with ErrorCall type fd3b845 Make HasDynFlags more transformers friendly 7a40a6c Update libffi-tarballs submodule to libffi 3.1 (re #10238) bb753c5 Rename s/7.12.1/8.0.1/ two minor occurences 2cfa5db Fix double MaybeT instance 2106d86 Fix typo sneaked in with fd3b845c01aa26b6e5 69c3964 docs/glasgow_exts: Use warning admonition e792711 users_guide: Show sub-sub-sections in ToC aa6ae8a Comments only 6c794c3 Comments about polymorphic recursion d7729c7 An assortment of typos 7997d6c Refactor GHCi Command type; allow "hidden" commands 31bddc4 Add missing whitespace in toArgs' error msg af77089 Fix DeriveAnyClass (Trac #9968) e9ea020 Comments only 8317893 Improve documentation for DeriveAnyClass 688069c More typos in comments/docs 602889a Test Trac #11192 f4f00c0 Test Trac #11187 41ef8f7 Make sure PatSyns only get added once to tcg_patsyns f7c17c8 T7478: Don't expect broken on Darwin 5447c20 Mark retc001 as broken on Darwin 262954c T4801: Update expected allocations on Darwin c205aeb Removed colon append operation (fixes #10785) b138248 Improved data family export documentation ceaf0f4 testsuite: Only run recomp015 on ELF-based platforms 6e56ac5 Fix infix record field fixity (#11167 and #11173). 6746549 Add kind equalities to GHC. 5183109 Revert README.md changes from 6746549772c5 a6e0394 haddock: Fix submodule commit to point to ghc-head b5d5d83 Revert .gitmodules changes from 6746549772c5 a459451 rm rae.txt 68f198f Test case for #7961. 779dfea Test #9017 in polykinds/T9017 a3c2a26 Frontend plugins. 1883afb Implement -fwarn-missing-pat-syn-sigs 3ec8288 Rework the Implicit CallStack solver to handle local lets. 4935b48 Make -XStrict imply -XStrictData 3640ae9 Dwarf: Use .short instead of .hword on Darwin aaed24a Build system: fix 'make install-strip' in bindist 9934819 Refactor type families in Template Haskell 59cc6ed Fix release notes markup 669c5ed Remove redundant imports f48015b configure: add support for 'sh4' (Trac #11209) From git at git.haskell.org Sun Dec 13 23:03:56 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 13 Dec 2015 23:03:56 +0000 (UTC) Subject: [commit: ghc] master: Update Cabal submodule (0bf0cf9) Message-ID: <20151213230356.B69A53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0bf0cf936c7895b19d0fd6a19d5238eed6c8feb6/ghc >--------------------------------------------------------------- commit 0bf0cf936c7895b19d0fd6a19d5238eed6c8feb6 Author: Herbert Valerio Riedel Date: Sun Dec 13 23:37:27 2015 +0100 Update Cabal submodule >--------------------------------------------------------------- 0bf0cf936c7895b19d0fd6a19d5238eed6c8feb6 libraries/Cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Cabal b/libraries/Cabal index 4e11fb9..d602f63 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit 4e11fb9f353ad78c862c4c123143a0e793fc22d5 +Subproject commit d602f63e7daf426514e38492bfdeeb4f33bd361d From git at git.haskell.org Mon Dec 14 07:33:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 14 Dec 2015 07:33:27 +0000 (UTC) Subject: [commit: ghc] master: Use idiomatic way to tell Autoconf the c compiler (fcc6b1d) Message-ID: <20151214073327.F39983A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fcc6b1def57d3009f9a3662a96d87ee041eb49b8/ghc >--------------------------------------------------------------- commit fcc6b1def57d3009f9a3662a96d87ee041eb49b8 Author: Herbert Valerio Riedel Date: Mon Dec 14 07:36:37 2015 +0100 Use idiomatic way to tell Autoconf the c compiler The non-idiomatic `--with-cc` flag was added via 5c789e424c1461c1dadfd38c44fcb9e8f38bf755 However, `--with-cc` seems rather fragile and support for `--with-cc` needs to be added explicitly to autoconf-based Cabal packages. The `CC=` flag, however, is supported natively by GNU Autoconf, so let's use the standard facility for that. Relatedly, Cabal prior to version 1.24 used a similiar flag `--with-gcc=...`, but starting with Cabal-1.24 this has been changed to use `CC=...` instead as well (see https://github.com/haskell/cabal/pull/2946) This also updates a few submodules removing the now obsolete `--with-cc` flag support. Reviewed By: trofi, thomie, erikd Differential Revision: https://phabricator.haskell.org/D1608 >--------------------------------------------------------------- fcc6b1def57d3009f9a3662a96d87ee041eb49b8 libraries/base/configure.ac | 5 +---- libraries/directory | 2 +- libraries/integer-gmp/configure.ac | 5 +---- libraries/process | 2 +- libraries/unix | 2 +- rules/build-package-data.mk | 2 +- 6 files changed, 6 insertions(+), 12 deletions(-) diff --git a/libraries/base/configure.ac b/libraries/base/configure.ac index 3d372d7..b8a4774 100644 --- a/libraries/base/configure.ac +++ b/libraries/base/configure.ac @@ -10,10 +10,7 @@ AC_CANONICAL_BUILD AC_CANONICAL_HOST AC_CANONICAL_TARGET -AC_ARG_WITH([cc], - [C compiler], - [CC=$withval]) -AC_PROG_CC() +AC_PROG_CC dnl make extensions visible to allow feature-tests to detect them lateron AC_USE_SYSTEM_EXTENSIONS diff --git a/libraries/directory b/libraries/directory index a7a5b0b..298529b 160000 --- a/libraries/directory +++ b/libraries/directory @@ -1 +1 @@ -Subproject commit a7a5b0b738aad432a9cad512a26d7564120ef0e8 +Subproject commit 298529bf8adc38ed602eab300c63bbc68510e5a3 diff --git a/libraries/integer-gmp/configure.ac b/libraries/integer-gmp/configure.ac index 4e3df11..c19dbbc 100644 --- a/libraries/integer-gmp/configure.ac +++ b/libraries/integer-gmp/configure.ac @@ -6,10 +6,7 @@ AC_CONFIG_SRCDIR([cbits/wrappers.c]) AC_CANONICAL_TARGET -AC_ARG_WITH([cc], - [C compiler], - [CC=$withval]) -AC_PROG_CC() +AC_PROG_CC dnl make extensions visible to allow feature-tests to detect them lateron AC_USE_SYSTEM_EXTENSIONS diff --git a/libraries/process b/libraries/process index 0edb978..e594712 160000 --- a/libraries/process +++ b/libraries/process @@ -1 +1 @@ -Subproject commit 0edb97876c2f783b33f9a69089ca9d26a061e112 +Subproject commit e594712a8fe49c94ff43ab016739e0fa63f0de00 diff --git a/libraries/unix b/libraries/unix index 147630c..59edb0a 160000 --- a/libraries/unix +++ b/libraries/unix @@ -1 +1 @@ -Subproject commit 147630c7c76bd9b947524ef140d21b9e81967c6e +Subproject commit 59edb0a0a0d91ecfe938029b3b00a0c99dcb8481 diff --git a/rules/build-package-data.mk b/rules/build-package-data.mk index 938b6bf..3525c91 100644 --- a/rules/build-package-data.mk +++ b/rules/build-package-data.mk @@ -111,7 +111,7 @@ ifneq "$3" "0" $1_$2_CONFIGURE_OPTS += --with-ld="$$(LD_STAGE$3)" endif -$1_$2_CONFIGURE_OPTS += --configure-option=--with-cc="$$(CC_STAGE$3)" +$1_$2_CONFIGURE_OPTS += --configure-option=CC="$$(CC_STAGE$3)" $1_$2_CONFIGURE_OPTS += --with-ar="$$(AR_STAGE$3)" $1_$2_CONFIGURE_OPTS += $$(if $$(ALEX),--with-alex="$$(ALEX)") $1_$2_CONFIGURE_OPTS += $$(if $$(HAPPY),--with-happy="$$(HAPPY)") From git at git.haskell.org Mon Dec 14 09:42:28 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 14 Dec 2015 09:42:28 +0000 (UTC) Subject: [commit: ghc] master: Don't pass CC= explicitly to `./configure` scripts (baed2f5) Message-ID: <20151214094228.2FB4A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/baed2f5a26a5d4c4e951bd8f003f71fca3ef45e8/ghc >--------------------------------------------------------------- commit baed2f5a26a5d4c4e951bd8f003f71fca3ef45e8 Author: Herbert Valerio Riedel Date: Mon Dec 14 10:42:17 2015 +0100 Don't pass CC= explicitly to `./configure` scripts This is a follow-up to fcc6b1d / D1608 which is made possible by the recent Cabal update: As `ghc-cabal` is called with `--with-gcc`, this gets passed to `./configure` as `CC=...` argument. So we don't need to set `CC=...` ourselves explicitly again. Prior to the changes in Cabal (pulled in via 0bf0cf936c7) and fcc6b1d, `./configure` scripts would be called with a `--with-cc` argument followed by a `--with-gcc` argument. After this commit, `./configure` will be passed a single `CC=...` argument constructed by the `Cabal` library. Reviewed By: erikd Differential Revision: https://phabricator.haskell.org/D1611 >--------------------------------------------------------------- baed2f5a26a5d4c4e951bd8f003f71fca3ef45e8 rules/build-package-data.mk | 1 - 1 file changed, 1 deletion(-) diff --git a/rules/build-package-data.mk b/rules/build-package-data.mk index 3525c91..17b87e0 100644 --- a/rules/build-package-data.mk +++ b/rules/build-package-data.mk @@ -111,7 +111,6 @@ ifneq "$3" "0" $1_$2_CONFIGURE_OPTS += --with-ld="$$(LD_STAGE$3)" endif -$1_$2_CONFIGURE_OPTS += --configure-option=CC="$$(CC_STAGE$3)" $1_$2_CONFIGURE_OPTS += --with-ar="$$(AR_STAGE$3)" $1_$2_CONFIGURE_OPTS += $$(if $$(ALEX),--with-alex="$$(ALEX)") $1_$2_CONFIGURE_OPTS += $$(if $$(HAPPY),--with-happy="$$(HAPPY)") From git at git.haskell.org Mon Dec 14 14:10:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 14 Dec 2015 14:10:17 +0000 (UTC) Subject: [commit: ghc] master: Some more typos in comments (65920c9) Message-ID: <20151214141017.E49433A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/65920c9e6a17094c3a0abbdbed5ab01f8524850e/ghc >--------------------------------------------------------------- commit 65920c9e6a17094c3a0abbdbed5ab01f8524850e Author: Gabor Greif Date: Mon Dec 14 10:43:23 2015 +0100 Some more typos in comments >--------------------------------------------------------------- 65920c9e6a17094c3a0abbdbed5ab01f8524850e compiler/typecheck/TcSimplify.hs | 4 ++-- rts/Capability.c | 2 +- testsuite/tests/programs/andy_cherry/DataTypes.hs | 2 +- 3 files changed, 4 insertions(+), 4 deletions(-) diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs index 190c6c4..261abd0 100644 --- a/compiler/typecheck/TcSimplify.hs +++ b/compiler/typecheck/TcSimplify.hs @@ -425,11 +425,11 @@ tcCheckSatisfiability :: Bag EvVar -> TcM Bool tcCheckSatisfiability givens = do { lcl_env <- TcM.getLclEnv ; let given_loc = mkGivenLoc topTcLevel UnkSkol lcl_env - ; traceTc "checkSatisfiabilty {" (ppr givens) + ; traceTc "checkSatisfiability {" (ppr givens) ; (res, _ev_binds) <- runTcS $ do { cts <- solveSimpleGivens given_loc (bagToList givens) ; return (not (isEmptyBag cts)) } - ; traceTc "checkSatisfiabilty }" (ppr res) + ; traceTc "checkSatisfiability }" (ppr res) ; return (not res) } {- diff --git a/rts/Capability.c b/rts/Capability.c index b0b7f30..45ee2c8 100644 --- a/rts/Capability.c +++ b/rts/Capability.c @@ -859,7 +859,7 @@ yieldCapability (Capability** pCap, Task *task, rtsBool gcAllowed) // // - A bound thread can only be migrated by the holder of the // Capability on which the bound thread currently lives. So, if we -// hold Capabilty C, and task->cap == C, then task cannot be +// hold Capability C, and task->cap == C, then task cannot be // migrated under our feet. // Note [migrated bound threads 2] diff --git a/testsuite/tests/programs/andy_cherry/DataTypes.hs b/testsuite/tests/programs/andy_cherry/DataTypes.hs index b36de83..bcb6cbc 100644 --- a/testsuite/tests/programs/andy_cherry/DataTypes.hs +++ b/testsuite/tests/programs/andy_cherry/DataTypes.hs @@ -508,7 +508,7 @@ data Board = Board (Array BoardPos BoardSquare) MoveNumber -- current player & and move - (Maybe ChessFile) -- e.p. possibilties. + (Maybe ChessFile) -- e.p. possibilities. From git at git.haskell.org Mon Dec 14 14:33:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 14 Dec 2015 14:33:25 +0000 (UTC) Subject: [commit: ghc] master: Add testcase for #11216 (59d3948) Message-ID: <20151214143325.542A03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/59d3948f02b8a50788f2049014b302bb5b88c5a7/ghc >--------------------------------------------------------------- commit 59d3948f02b8a50788f2049014b302bb5b88c5a7 Author: Ben Gamari Date: Mon Dec 14 15:14:36 2015 +0100 Add testcase for #11216 >--------------------------------------------------------------- 59d3948f02b8a50788f2049014b302bb5b88c5a7 testsuite/tests/rebindable/T11216.hs | 6 ++++++ testsuite/tests/rebindable/all.T | 1 + 2 files changed, 7 insertions(+) diff --git a/testsuite/tests/rebindable/T11216.hs b/testsuite/tests/rebindable/T11216.hs new file mode 100644 index 0000000..e05feb9 --- /dev/null +++ b/testsuite/tests/rebindable/T11216.hs @@ -0,0 +1,6 @@ +{-# LANGUAGE RebindableSyntax #-} + +module Bug where + +foo :: (a, b) -> () +foo x | (_,_) <- x = () diff --git a/testsuite/tests/rebindable/all.T b/testsuite/tests/rebindable/all.T index b00e721..3ca873e 100644 --- a/testsuite/tests/rebindable/all.T +++ b/testsuite/tests/rebindable/all.T @@ -31,3 +31,4 @@ test('T4851', normal, compile, ['']) test('T5908', normal, compile, ['']) test('T10112', normal, compile, ['']) +test('T11216', [expect_broken(11216)], compile, ['']) \ No newline at end of file From git at git.haskell.org Mon Dec 14 14:33:28 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 14 Dec 2015 14:33:28 +0000 (UTC) Subject: [commit: ghc] master: Make binds in do-blocks strict when -XStrict (#11193) (419b6c0) Message-ID: <20151214143328.7E9193A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/419b6c00c194ccbd3c94539c26246dc41c88ed6c/ghc >--------------------------------------------------------------- commit 419b6c00c194ccbd3c94539c26246dc41c88ed6c Author: Adam Sandberg Eriksson Date: Mon Dec 14 15:03:15 2015 +0100 Make binds in do-blocks strict when -XStrict (#11193) Previously bindings in `do` blocks were omitted. With `-XStrict` ```lang=hs do content <- action other_things ``` should be equivalent to ```lang=hs do !content <- action other_things ``` Fixes #11193. Reviewers: bgamari, austin Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1612 GHC Trac Issues: #11193 >--------------------------------------------------------------- 419b6c00c194ccbd3c94539c26246dc41c88ed6c compiler/deSugar/Match.hs | 20 +++++++++++--------- testsuite/tests/deSugar/should_run/T11193.hs | 8 ++++++++ testsuite/tests/deSugar/should_run/T11193.stderr | 3 +++ testsuite/tests/deSugar/should_run/all.T | 1 + 4 files changed, 23 insertions(+), 9 deletions(-) diff --git a/compiler/deSugar/Match.hs b/compiler/deSugar/Match.hs index 6ffa25d..f551fa4 100644 --- a/compiler/deSugar/Match.hs +++ b/compiler/deSugar/Match.hs @@ -700,7 +700,7 @@ matchWrapper ctxt mb_scr (MG { mg_alts = L _ matches where mk_eqn_info vars (L _ (Match _ pats _ grhss)) = do { dflags <- getDynFlags - ; let upats = map (strictify dflags) pats + ; let upats = map (getMaybeStrictPat dflags) pats dicts = toTcTypeBag (collectEvVarsPats upats) -- Only TcTyVars ; tm_cs <- genCaseTmCs2 mb_scr upats vars ; match_result <- addDictsDs dicts $ -- See Note [Type and Term Equality Propagation] @@ -708,10 +708,6 @@ matchWrapper ctxt mb_scr (MG { mg_alts = L _ matches dsGRHSs ctxt upats grhss rhs_ty ; return (EqnInfo { eqn_pats = upats, eqn_rhs = match_result}) } - strictify dflags pat = - let (is_strict, pat') = getUnBangedLPat dflags pat - in if is_strict then BangPat pat' else unLoc pat' - handleWarnings = if isGenerated origin then discardWarningsDs else id @@ -760,21 +756,27 @@ matchSinglePat :: CoreExpr -> HsMatchContext Name -> LPat Id -- Do not warn about incomplete patterns -- Used for things like [ e | pat <- stuff ], where -- incomplete patterns are just fine -matchSinglePat (Var var) ctx (L _ pat) ty match_result +matchSinglePat (Var var) ctx pat ty match_result = do { dflags <- getDynFlags ; locn <- getSrcSpanDs - + ; let pat' = getMaybeStrictPat dflags pat -- pattern match check warnings - ; dsPmWarn dflags (DsMatchContext ctx locn) (checkSingle var pat) + ; dsPmWarn dflags (DsMatchContext ctx locn) (checkSingle var pat') ; match [var] ty - [EqnInfo { eqn_pats = [pat], eqn_rhs = match_result }] } + [EqnInfo { eqn_pats = [pat'], eqn_rhs = match_result }] } matchSinglePat scrut hs_ctx pat ty match_result = do { var <- selectSimpleMatchVarL pat ; match_result' <- matchSinglePat (Var var) hs_ctx pat ty match_result ; return (adjustMatchResult (bindNonRec var scrut) match_result') } +getMaybeStrictPat :: DynFlags -> LPat Id -> Pat Id +getMaybeStrictPat dflags pat = + let (is_strict, pat') = getUnBangedLPat dflags pat + in if is_strict then BangPat pat' else unLoc pat' + + {- ************************************************************************ * * diff --git a/testsuite/tests/deSugar/should_run/T11193.hs b/testsuite/tests/deSugar/should_run/T11193.hs new file mode 100644 index 0000000..a8759a3 --- /dev/null +++ b/testsuite/tests/deSugar/should_run/T11193.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE Strict #-} + +module Main where + +main = do + ~a <- return (error "don't error here!") + b <- return (error "error here!") -- this binding should be strict + print "should never reach here" diff --git a/testsuite/tests/deSugar/should_run/T11193.stderr b/testsuite/tests/deSugar/should_run/T11193.stderr new file mode 100644 index 0000000..50e427c --- /dev/null +++ b/testsuite/tests/deSugar/should_run/T11193.stderr @@ -0,0 +1,3 @@ +T11193: error here! +CallStack (from ImplicitParams): + error, called at T11193.hs:7:16 in main:Main diff --git a/testsuite/tests/deSugar/should_run/all.T b/testsuite/tests/deSugar/should_run/all.T index cc21ed7..9f50ea6 100644 --- a/testsuite/tests/deSugar/should_run/all.T +++ b/testsuite/tests/deSugar/should_run/all.T @@ -52,3 +52,4 @@ test('T10215', normal, compile_and_run, ['']) test('DsStrictData', normal, compile_and_run, ['']) test('DsStrict', normal, compile_and_run, ['']) test('DsStrictLet', normal, compile_and_run, ['-O']) +test('T11193', exit_code(1), compile_and_run, ['']) From git at git.haskell.org Mon Dec 14 14:33:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 14 Dec 2015 14:33:32 +0000 (UTC) Subject: [commit: ghc] master: Use Cxt for deriving clauses in TH (#10819) (04ab55d) Message-ID: <20151214143332.15F933A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/04ab55d9a6fe311b7cb544211738caca6c00c720/ghc >--------------------------------------------------------------- commit 04ab55d9a6fe311b7cb544211738caca6c00c720 Author: Ben Gamari Date: Mon Dec 14 15:01:12 2015 +0100 Use Cxt for deriving clauses in TH (#10819) Summary: Deriving clauses in the TH representations of data, newtype, data instance, and newtype instance declarations previously were just [Name], which didn't allow for more complex derived classes, eg. multi-parameter typeclasses. This switches out [Name] for Cxt, representing the derived classes as types instead of names. Test Plan: validate Reviewers: goldfire, spinda, austin Reviewed By: goldfire, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1202 GHC Trac Issues: #10819 >--------------------------------------------------------------- 04ab55d9a6fe311b7cb544211738caca6c00c720 compiler/deSugar/DsMeta.hs | 28 +++++++++++----------- compiler/hsSyn/Convert.hs | 12 ++++------ docs/users_guide/7.12.1-notes.rst | 6 +++++ .../template-haskell/Language/Haskell/TH/Lib.hs | 20 +++++++++------- .../template-haskell/Language/Haskell/TH/Ppr.hs | 18 +++++++------- .../template-haskell/Language/Haskell/TH/Syntax.hs | 14 +++++------ testsuite/tests/rts/T7919A.hs | 4 ++-- testsuite/tests/th/T10819.hs | 25 +++++++++++++++++++ testsuite/tests/th/T10819_Lib.hs | 6 +++++ testsuite/tests/th/TH_dataD1.hs | 2 +- testsuite/tests/th/all.T | 5 +++- 11 files changed, 92 insertions(+), 48 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 04ab55d9a6fe311b7cb544211738caca6c00c720 From git at git.haskell.org Mon Dec 14 14:33:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 14 Dec 2015 14:33:35 +0000 (UTC) Subject: [commit: ghc] master: Suggest import Data.Kinds when * is out of scope (023f11f) Message-ID: <20151214143335.5D0D83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/023f11f562c7d08af121e4dac04ec66418e6923b/ghc >--------------------------------------------------------------- commit 023f11f562c7d08af121e4dac04ec66418e6923b Author: Richard Eisenberg Date: Mon Dec 14 15:02:54 2015 +0100 Suggest import Data.Kinds when * is out of scope With -XTypeInType, `*` must be imported to be used. This patch makes sure the user knows this. But I'm not sure this is the best way to deal with `*`. Feedback welcome on either this small fix or the approach to `*`, in general. You may wish to see `Note [HsAppsTy]` in HsTypes if you want to take a broader view. Test Plan: dependent/should_fail/RenamingStar Reviewers: simonpj, bgamari, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1610 >--------------------------------------------------------------- 023f11f562c7d08af121e4dac04ec66418e6923b compiler/rename/RnEnv.hs | 35 ++++++++++++++-------- .../tests/dependent/should_fail/RenamingStar.hs | 5 ++++ .../dependent/should_fail/RenamingStar.stderr | 11 +++++++ testsuite/tests/dependent/should_fail/all.T | 1 + 4 files changed, 40 insertions(+), 12 deletions(-) diff --git a/compiler/rename/RnEnv.hs b/compiler/rename/RnEnv.hs index a398e33..4337dbb 100644 --- a/compiler/rename/RnEnv.hs +++ b/compiler/rename/RnEnv.hs @@ -713,16 +713,12 @@ lookupKindOccRn :: RdrName -> RnM Name -- Looking up a name occurring in a kind lookupKindOccRn rdr_name = do { typeintype <- xoptM Opt_TypeInType - ; if | typeintype -> lookupTypeOccRn rdr_name - | is_star -> return starKindTyConName - | is_uni_star -> return unicodeStarKindTyConName - | otherwise -> lookupOccRn rdr_name } - where + ; if | typeintype -> lookupTypeOccRn rdr_name -- With -XNoTypeInType, treat any usage of * in kinds as in scope -- this is a dirty hack, but then again so was the old * kind. - fs_name = occNameFS $ rdrNameOcc rdr_name - is_star = fs_name == fsLit "*" - is_uni_star = fs_name == fsLit "?" + | is_star rdr_name -> return starKindTyConName + | is_uni_star rdr_name -> return unicodeStarKindTyConName + | otherwise -> lookupOccRn rdr_name } -- lookupPromotedOccRn looks up an optionally promoted RdrName. lookupTypeOccRn :: RdrName -> RnM Name @@ -731,16 +727,17 @@ lookupTypeOccRn rdr_name = do { mb_name <- lookupOccRn_maybe rdr_name ; case mb_name of { Just name -> return name ; - Nothing -> lookup_demoted rdr_name } } + Nothing -> do { dflags <- getDynFlags + ; lookup_demoted rdr_name dflags } } } -lookup_demoted :: RdrName -> RnM Name -lookup_demoted rdr_name +lookup_demoted :: RdrName -> DynFlags -> RnM Name +lookup_demoted rdr_name dflags | Just demoted_rdr <- demoteRdrName rdr_name -- Maybe it's the name of a *data* constructor = do { data_kinds <- xoptM Opt_DataKinds ; mb_demoted_name <- lookupOccRn_maybe demoted_rdr ; case mb_demoted_name of - Nothing -> reportUnboundName rdr_name + Nothing -> unboundNameX WL_Any rdr_name star_info Just demoted_name | data_kinds -> do { whenWOptM Opt_WarnUntickedPromotedConstructors $ @@ -761,6 +758,20 @@ lookup_demoted rdr_name , text "instead of" , quotes (ppr name) <> dot ] + star_info + | is_star rdr_name || is_uni_star rdr_name + = if xopt Opt_TypeInType dflags + then text "NB: With TypeInType, you must import" <+> + ppr rdr_name <+> text "from Data.Kind" + else empty + + | otherwise + = empty + +is_star, is_uni_star :: RdrName -> Bool +is_star = (fsLit "*" ==) . occNameFS . rdrNameOcc +is_uni_star = (fsLit "?" ==) . occNameFS . rdrNameOcc + {- Note [Demotion] ~~~~~~~~~~~~~~~ diff --git a/testsuite/tests/dependent/should_fail/RenamingStar.hs b/testsuite/tests/dependent/should_fail/RenamingStar.hs new file mode 100644 index 0000000..255021c --- /dev/null +++ b/testsuite/tests/dependent/should_fail/RenamingStar.hs @@ -0,0 +1,5 @@ +{-# LANGUAGE TypeInType #-} + +module RenamingStar where + +data Foo :: * diff --git a/testsuite/tests/dependent/should_fail/RenamingStar.stderr b/testsuite/tests/dependent/should_fail/RenamingStar.stderr new file mode 100644 index 0000000..5efda69 --- /dev/null +++ b/testsuite/tests/dependent/should_fail/RenamingStar.stderr @@ -0,0 +1,11 @@ + +RenamingStar.hs:5:13: error: + Not in scope: type constructor or class ?*? + NB: With TypeInType, you must import * from Data.Kind + +RenamingStar.hs:5:13: error: + Illegal operator ?*? in type ?*? + Use TypeOperators to allow operators in types + +RenamingStar.hs:5:13: error: + Operator applied to too few arguments: * diff --git a/testsuite/tests/dependent/should_fail/all.T b/testsuite/tests/dependent/should_fail/all.T index 8d4b288..8f9c9d0 100644 --- a/testsuite/tests/dependent/should_fail/all.T +++ b/testsuite/tests/dependent/should_fail/all.T @@ -7,3 +7,4 @@ test('BadTelescope3', normal, compile_fail, ['']) test('PromotedClass', normal, compile_fail, ['']) test('SelfDep', normal, compile_fail, ['']) test('BadTelescope4', normal, compile_fail, ['']) +test('RenamingStar', normal, compile_fail, ['']) From git at git.haskell.org Mon Dec 14 19:54:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 14 Dec 2015 19:54:48 +0000 (UTC) Subject: [commit: ghc] master: Add IsString Outputable.SDoc instance (402bbe6) Message-ID: <20151214195448.F323D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/402bbe6e2dddb96326e29b247adc40d9081ab224/ghc >--------------------------------------------------------------- commit 402bbe6e2dddb96326e29b247adc40d9081ab224 Author: Herbert Valerio Riedel Date: Mon Dec 14 20:55:08 2015 +0100 Add IsString Outputable.SDoc instance This allows to conveniently interpret string literals as `text` when `-XOverloadedStrings` is in effect. For what it's worth, `Text.PrettyPrint.Doc` also possesses such an instance. This is a spin-off from D1240 Reviewed By: bgamari Differential Revision: https://phabricator.haskell.org/D1618 >--------------------------------------------------------------- 402bbe6e2dddb96326e29b247adc40d9081ab224 compiler/utils/Outputable.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/compiler/utils/Outputable.hs b/compiler/utils/Outputable.hs index b539fa6..cda7475 100644 --- a/compiler/utils/Outputable.hs +++ b/compiler/utils/Outputable.hs @@ -103,6 +103,7 @@ import Data.Int import qualified Data.IntMap as IM import Data.Set (Set) import qualified Data.Set as Set +import Data.String import Data.Word import System.IO ( Handle ) import System.FilePath @@ -286,6 +287,9 @@ data SDocContext = SDC , sdocDynFlags :: !DynFlags } +instance IsString SDoc where + fromString = text + initSDocContext :: DynFlags -> PprStyle -> SDocContext initSDocContext dflags sty = SDC { sdocStyle = sty From git at git.haskell.org Mon Dec 14 20:59:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 14 Dec 2015 20:59:48 +0000 (UTC) Subject: [commit: ghc] master: Test #9632 in dependent/should_compile/T9632 (05fe546) Message-ID: <20151214205948.4B7E03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/05fe5463143769a2e84d5e3508a829792d5a1817/ghc >--------------------------------------------------------------- commit 05fe5463143769a2e84d5e3508a829792d5a1817 Author: Richard Eisenberg Date: Mon Dec 14 15:59:21 2015 -0500 Test #9632 in dependent/should_compile/T9632 >--------------------------------------------------------------- 05fe5463143769a2e84d5e3508a829792d5a1817 testsuite/tests/dependent/should_compile/T9632.hs | 11 +++++++++++ testsuite/tests/dependent/should_compile/all.T | 1 + 2 files changed, 12 insertions(+) diff --git a/testsuite/tests/dependent/should_compile/T9632.hs b/testsuite/tests/dependent/should_compile/T9632.hs new file mode 100644 index 0000000..bea468f --- /dev/null +++ b/testsuite/tests/dependent/should_compile/T9632.hs @@ -0,0 +1,11 @@ +{-# LANGUAGE TypeInType #-} + +module T9632 where + +import Data.Kind + +data B = T | F +data P :: B -> * + +type B' = B +data P' :: B' -> * diff --git a/testsuite/tests/dependent/should_compile/all.T b/testsuite/tests/dependent/should_compile/all.T index 1724ff6..e1e064a 100644 --- a/testsuite/tests/dependent/should_compile/all.T +++ b/testsuite/tests/dependent/should_compile/all.T @@ -9,3 +9,4 @@ test('KindLevels', normal, compile, ['']) test('RaeBlogPost', normal, compile, ['']) test('mkGADTVars', normal, compile, ['']) test('TypeLevelVec',normal,compile, ['']) +test('T9632', normal, compile, ['']) From git at git.haskell.org Tue Dec 15 00:37:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 00:37:43 +0000 (UTC) Subject: [commit: ghc] master: Document -XOverloadedLabels (f4dd486) Message-ID: <20151215003743.954143A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f4dd4862fd8cbb092f86dcaa97c937e0494fab36/ghc >--------------------------------------------------------------- commit f4dd4862fd8cbb092f86dcaa97c937e0494fab36 Author: Adam Gundry Date: Tue Dec 15 01:11:03 2015 +0100 Document -XOverloadedLabels This adds documentation of the new `OverloadedLabels` extension to the users' guide. Thanks to @bgamari for patiently reminding me to get this done. Feedback welcome. Test Plan: N/A Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1623 >--------------------------------------------------------------- f4dd4862fd8cbb092f86dcaa97c937e0494fab36 docs/users_guide/glasgow_exts.rst | 81 +++++++++++++++++++++++++++++++++++++++ 1 file changed, 81 insertions(+) diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index ebe1f75..b9ad620 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -5751,6 +5751,87 @@ A small example: Note that deriving ``Eq`` is necessary for the pattern matching to work since it gets translated into an equality comparison. +.. _overloaded-labels: + +Overloaded labels +----------------- + +GHC supports *overloaded labels*, a form of identifier whose interpretation may +depend both on its type and on its literal text. When the +``-XOverloadedLabels`` extension is enabled, an overloaded label can written +with a prefix hash, for example ``#foo``. The type of this expression is +``IsLabel "foo" a => a``. + +The class ``IsLabel`` is defined as: + +:: + + class IsLabel (x :: Symbol) a where + fromLabel :: Proxy# x -> a + +This is rather similar to the class ``IsString`` (see +:ref:`overloaded-strings`), but with an additional type parameter that makes the +text of the label available as a type-level string (see +:ref:`type-level-literals`). + +There are no predefined instances of this class. It is not in scope by default, +but can be brought into scope by importing +:base-ref:`GHC.OverloadedLabels `:. Unlike +``IsString``, there are no special defaulting rules for ``IsLabel``. + +During typechecking, GHC will replace an occurrence of an overloaded label like +``#foo`` with + +:: + + fromLabel (proxy# :: Proxy# "foo") + +This will have some type ``alpha`` and require the solution of a class +constraint ``IsLabel "foo" alpha``. + +The intention is for ``IsLabel`` to be used to support overloaded record fields +and perhaps anonymous records. Thus, it may be given instances for base +datatypes (in particular ``(->)``) in the future. + +When writing an overloaded label, there must be no space between the hash sign +and the following identifier. :ref:`magic-hash` makes use of postfix hash +signs; if ``OverloadedLabels`` and ``MagicHash`` are both enabled then ``x#y`` +means ``x# y``, but if only ``OverloadedLabels`` is enabled then it means ``x +#y``. To avoid confusion, you are strongly encouraged to put a space before the +hash when using ``OverloadedLabels``. + +When using ``OverloadedLabels`` (or ``MagicHash``) in a ``.hsc`` file (see +:ref:`hsc2hs`), the hash signs must be doubled (write ``##foo`` instead of +``#foo``) to avoid them being treated as ``hsc2hs`` directives. + +Here is an extension of the record access example in :ref:`type-level-literals` +showing how an overloaded label can be used as a record selector: + +:: + + {-# LANGUAGE DataKinds, KindSignatures, MultiParamTypeClasses, + FunctionalDependencies, FlexibleInstances, + OverloadedLabels, ScopedTypeVariables #-} + + import GHC.OverloadedLabels (IsLabel(..)) + import GHC.TypeLits (Symbol) + + data Label (l :: Symbol) = Get + + class Has a l b | a l -> b where + from :: a -> Label l -> b + + data Point = Point Int Int deriving Show + + instance Has Point "x" Int where from (Point x _) _ = x + instance Has Point "y" Int where from (Point _ y) _ = y + + instance Has a l b => IsLabel l (a -> b) where + fromLabel _ x = from x (Get :: Label l) + + example = #x (Point 1 2) + + .. _overloaded-lists: Overloaded lists From git at git.haskell.org Tue Dec 15 00:37:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 00:37:46 +0000 (UTC) Subject: [commit: ghc] master: Mention "handle is semi-closed" in error messages (9017f16) Message-ID: <20151215003746.4440D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9017f16a78d66fe5aaf0ec98aeb9add1792fd838/ghc >--------------------------------------------------------------- commit 9017f16a78d66fe5aaf0ec98aeb9add1792fd838 Author: Thomas Miedema Date: Tue Dec 15 01:02:39 2015 +0100 Mention "handle is semi-closed" in error messages Semi-closedness is mentioned in the Haskell report, so lets not hide it from users. Reviewers: austin, hvr, bgamari Reviewed By: bgamari Differential Revision: https://phabricator.haskell.org/D1624 >--------------------------------------------------------------- 9017f16a78d66fe5aaf0ec98aeb9add1792fd838 libraries/base/GHC/IO/Handle.hs | 10 +++++----- libraries/base/GHC/IO/Handle/Internals.hs | 14 +++++++++----- libraries/base/tests/IO/IOError001.stdout | 4 ++-- 3 files changed, 16 insertions(+), 12 deletions(-) diff --git a/libraries/base/GHC/IO/Handle.hs b/libraries/base/GHC/IO/Handle.hs index 23272ce..ac37ad4 100644 --- a/libraries/base/GHC/IO/Handle.hs +++ b/libraries/base/GHC/IO/Handle.hs @@ -113,7 +113,7 @@ hFileSize handle = withHandle_ "hFileSize" handle $ \ handle_ at Handle__{haDevice=dev} -> do case haType handle_ of ClosedHandle -> ioe_closedHandle - SemiClosedHandle -> ioe_closedHandle + SemiClosedHandle -> ioe_semiclosedHandle _ -> do flushWriteBuffer handle_ r <- IODevice.getSize dev if r /= -1 @@ -129,7 +129,7 @@ hSetFileSize handle size = withHandle_ "hSetFileSize" handle $ \ handle_ at Handle__{haDevice=dev} -> do case haType handle_ of ClosedHandle -> ioe_closedHandle - SemiClosedHandle -> ioe_closedHandle + SemiClosedHandle -> ioe_semiclosedHandle _ -> do flushWriteBuffer handle_ IODevice.setSize dev size return () @@ -473,7 +473,7 @@ hIsReadable handle = withHandle_ "hIsReadable" handle $ \ handle_ -> do case haType handle_ of ClosedHandle -> ioe_closedHandle - SemiClosedHandle -> ioe_closedHandle + SemiClosedHandle -> ioe_semiclosedHandle htype -> return (isReadableHandleType htype) hIsWritable :: Handle -> IO Bool @@ -482,7 +482,7 @@ hIsWritable handle = withHandle_ "hIsWritable" handle $ \ handle_ -> do case haType handle_ of ClosedHandle -> ioe_closedHandle - SemiClosedHandle -> ioe_closedHandle + SemiClosedHandle -> ioe_semiclosedHandle htype -> return (isWritableHandleType htype) -- | Computation 'hGetBuffering' @hdl@ returns the current buffering mode @@ -503,7 +503,7 @@ hIsSeekable handle = withHandle_ "hIsSeekable" handle $ \ handle_ at Handle__{..} -> do case haType of ClosedHandle -> ioe_closedHandle - SemiClosedHandle -> ioe_closedHandle + SemiClosedHandle -> ioe_semiclosedHandle AppendHandle -> return False _ -> IODevice.isSeekable haDevice diff --git a/libraries/base/GHC/IO/Handle/Internals.hs b/libraries/base/GHC/IO/Handle/Internals.hs index 99cfb31..37251ab 100644 --- a/libraries/base/GHC/IO/Handle/Internals.hs +++ b/libraries/base/GHC/IO/Handle/Internals.hs @@ -42,7 +42,8 @@ module GHC.IO.Handle.Internals ( decodeByteBuf, augmentIOError, - ioe_closedHandle, ioe_EOF, ioe_notReadable, ioe_notWritable, + ioe_closedHandle, ioe_semiclosedHandle, + ioe_EOF, ioe_notReadable, ioe_notWritable, ioe_finalizedHandle, ioe_bufsiz, hClose_help, hLookAhead_, @@ -238,7 +239,7 @@ checkWritableHandle :: (Handle__ -> IO a) -> Handle__ -> IO a checkWritableHandle act h_ at Handle__{..} = case haType of ClosedHandle -> ioe_closedHandle - SemiClosedHandle -> ioe_closedHandle + SemiClosedHandle -> ioe_semiclosedHandle ReadHandle -> ioe_notWritable ReadWriteHandle -> do buf <- readIORef haCharBuffer @@ -277,7 +278,7 @@ checkReadableHandle :: (Handle__ -> IO a) -> Handle__ -> IO a checkReadableHandle act h_ at Handle__{..} = case haType of ClosedHandle -> ioe_closedHandle - SemiClosedHandle -> ioe_closedHandle + SemiClosedHandle -> ioe_semiclosedHandle AppendHandle -> ioe_notReadable WriteHandle -> ioe_notReadable ReadWriteHandle -> do @@ -307,7 +308,7 @@ checkSeekableHandle :: (Handle__ -> IO a) -> Handle__ -> IO a checkSeekableHandle act handle_ at Handle__{haDevice=dev} = case haType handle_ of ClosedHandle -> ioe_closedHandle - SemiClosedHandle -> ioe_closedHandle + SemiClosedHandle -> ioe_semiclosedHandle AppendHandle -> ioe_notSeekable _ -> do b <- IODevice.isSeekable dev if b then act handle_ @@ -316,13 +317,16 @@ checkSeekableHandle act handle_ at Handle__{haDevice=dev} = -- ----------------------------------------------------------------------------- -- Handy IOErrors -ioe_closedHandle, ioe_EOF, +ioe_closedHandle, ioe_semiclosedHandle, ioe_EOF, ioe_notReadable, ioe_notWritable, ioe_cannotFlushNotSeekable, ioe_notSeekable :: IO a ioe_closedHandle = ioException (IOError Nothing IllegalOperation "" "handle is closed" Nothing Nothing) +ioe_semiclosedHandle = ioException + (IOError Nothing IllegalOperation "" + "handle is semi-closed" Nothing Nothing) ioe_EOF = ioException (IOError Nothing EOF "" "" Nothing Nothing) ioe_notReadable = ioException diff --git a/libraries/base/tests/IO/IOError001.stdout b/libraries/base/tests/IO/IOError001.stdout index 1e689bb..c235b62 100644 --- a/libraries/base/tests/IO/IOError001.stdout +++ b/libraries/base/tests/IO/IOError001.stdout @@ -1,2 +1,2 @@ -: hGetChar: illegal operation (handle is closed) -: hGetChar: illegal operation (handle is closed) +: hGetChar: illegal operation (handle is semi-closed) +: hGetChar: illegal operation (handle is semi-closed) From git at git.haskell.org Tue Dec 15 00:37:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 00:37:48 +0000 (UTC) Subject: [commit: ghc] master: Fix runghc when $1_$2_SHELL_WRAPPER = NO (05a5ebe) Message-ID: <20151215003748.F22713A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/05a5ebed916dc00bc5761224047440fefe10485e/ghc >--------------------------------------------------------------- commit 05a5ebed916dc00bc5761224047440fefe10485e Author: RyanGlScott Date: Tue Dec 15 01:02:46 2015 +0100 Fix runghc when $1_$2_SHELL_WRAPPER = NO When that variable isn't on (which is always the case on Windows), `runghc` naively attempts to invoke `ghc` by finding an executable simply named `ghc`. This won't work if `ghc` doesn't exist (e.g., if we're building GHC and using `ghc-stage2` instead). A simple fix is to test for the existence of `ghc` beforehand, and if that fails, fall back on `ghc-stage2`. Fixes #11185. Test Plan: ./validate Reviewers: austin, hvr, thomie, bgamari Reviewed By: thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1621 GHC Trac Issues: #11185 >--------------------------------------------------------------- 05a5ebed916dc00bc5761224047440fefe10485e utils/runghc/Main.hs | 22 ++++++++++++++++++---- utils/runghc/ghc.mk | 1 - 2 files changed, 18 insertions(+), 5 deletions(-) diff --git a/utils/runghc/Main.hs b/utils/runghc/Main.hs index 42ddb83..d048125 100644 --- a/utils/runghc/Main.hs +++ b/utils/runghc/Main.hs @@ -52,9 +52,24 @@ main = do mbPath <- getExecPath case mbPath of Nothing -> dieProg ("cannot find ghc") - Just path -> - let ghc = takeDirectory (normalise path) "ghc" - in uncurry (doIt ghc) $ getGhcArgs args' + Just path -> do + ghc <- findGhc path + uncurry (doIt ghc) $ getGhcArgs args' + +-- In some cases, runghc isn't given a path to ghc explicitly. This can occur +-- if $1_$2_SHELL_WRAPPER = NO (which is always the case on Windows). In such +-- a scenario, we must guess where ghc lives. Given a path where ghc might +-- live, we check for the existence of ghc. If we can't find it, we assume that +-- we're building ghc from source, in which case we fall back on ghc-stage2. +-- (See Trac #1185.) +findGhc :: FilePath -> IO FilePath +findGhc path = do + let ghcDir = takeDirectory (normalise path) + ghc = ghcDir "ghc" <.> exeExtension + ghcExists <- doesFileExist ghc + return $ if ghcExists + then ghc + else ghcDir "ghc-stage2" <.> exeExtension data RunGhcFlags = RunGhcFlags (Maybe FilePath) -- GHC location | Help -- Print help text @@ -177,4 +192,3 @@ foreign import WINDOWS_CCONV unsafe "windows.h GetModuleFileNameW" #else getExecPath = return Nothing #endif - diff --git a/utils/runghc/ghc.mk b/utils/runghc/ghc.mk index e981abf..9169ca2 100644 --- a/utils/runghc/ghc.mk +++ b/utils/runghc/ghc.mk @@ -42,4 +42,3 @@ install_runhaskell: $(call removeFiles,"$(DESTDIR)$(bindir)/runghc") $(LN_S) runghc-$(ProjectVersion) "$(DESTDIR)$(bindir)/runghc" endif - From git at git.haskell.org Tue Dec 15 00:37:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 00:37:51 +0000 (UTC) Subject: [commit: ghc] master: DynFlags: delete function that doesn't do anything (33742db) Message-ID: <20151215003751.9883F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/33742db5798ef09192e8468af7dd71d58b316ab9/ghc >--------------------------------------------------------------- commit 33742db5798ef09192e8468af7dd71d58b316ab9 Author: Thomas Miedema Date: Tue Dec 15 01:07:39 2015 +0100 DynFlags: delete function that doesn't do anything Reviewers: austin, bgamari Reviewed By: austin, bgamari Differential Revision: https://phabricator.haskell.org/D1606 >--------------------------------------------------------------- 33742db5798ef09192e8468af7dd71d58b316ab9 compiler/main/DynFlags.hs | 15 +++------------ 1 file changed, 3 insertions(+), 12 deletions(-) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 7003a6c..98a3631 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -1328,14 +1328,6 @@ wayUnsetGeneralFlags _ WayDyn = [-- There's no point splitting objects wayUnsetGeneralFlags _ WayProf = [] wayUnsetGeneralFlags _ WayEventLog = [] -wayExtras :: Platform -> Way -> DynFlags -> DynFlags -wayExtras _ (WayCustom {}) dflags = dflags -wayExtras _ WayThreaded dflags = dflags -wayExtras _ WayDebug dflags = dflags -wayExtras _ WayDyn dflags = dflags -wayExtras _ WayProf dflags = dflags -wayExtras _ WayEventLog dflags = dflags - wayOptc :: Platform -> Way -> [String] wayOptc _ (WayCustom {}) = [] wayOptc platform WayThreaded = case platformOS platform of @@ -3692,12 +3684,11 @@ addWay w = upd (addWay' w) addWay' :: Way -> DynFlags -> DynFlags addWay' w dflags0 = let platform = targetPlatform dflags0 dflags1 = dflags0 { ways = w : ways dflags0 } - dflags2 = wayExtras platform w dflags1 - dflags3 = foldr setGeneralFlag' dflags2 + dflags2 = foldr setGeneralFlag' dflags1 (wayGeneralFlags platform w) - dflags4 = foldr unSetGeneralFlag' dflags3 + dflags3 = foldr unSetGeneralFlag' dflags2 (wayUnsetGeneralFlags platform w) - in dflags4 + in dflags3 removeWayDyn :: DynP () removeWayDyn = upd (\dfs -> dfs { ways = filter (WayDyn /=) (ways dfs) }) From git at git.haskell.org Tue Dec 15 00:37:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 00:37:54 +0000 (UTC) Subject: [commit: ghc] master: DynFlags Remove -fwarn-context-quantification flag (ddde542) Message-ID: <20151215003754.4D73F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ddde542dbcb088e0a10aa3cdc3e0aef0a1c4a9b7/ghc >--------------------------------------------------------------- commit ddde542dbcb088e0a10aa3cdc3e0aef0a1c4a9b7 Author: Ben Gamari Date: Tue Dec 15 01:01:39 2015 +0100 DynFlags Remove -fwarn-context-quantification flag As mentioned in #4426 these warnings are now errors since the Great Wildcards Refactor of 2015 (1e041b7382b6aa329e4ad9625439f811e0f27232). I've opened #11221 to ensure we remove the last traces of the option in 8.2. Test Plan: validate Reviewers: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1615 GHC Trac Issues: #4426 >--------------------------------------------------------------- ddde542dbcb088e0a10aa3cdc3e0aef0a1c4a9b7 compiler/main/DynFlags.hs | 6 ++--- compiler/rename/RnTypes.hs | 4 ++-- docs/users_guide/glasgow_exts.rst | 4 ++-- docs/users_guide/using-warnings.rst | 26 ++-------------------- testsuite/tests/rename/should_compile/T4426.hs | 1 - testsuite/tests/rename/should_compile/T4426.stderr | 18 +++++++-------- 6 files changed, 18 insertions(+), 41 deletions(-) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 63cfe03..b306253 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -504,7 +504,7 @@ data WarningFlag = | Opt_WarnUnusedPatternBinds | Opt_WarnUnusedImports | Opt_WarnUnusedMatches - | Opt_WarnContextQuantification + | Opt_WarnContextQuantification -- remove in 8.2 | Opt_WarnWarningsDeprecations | Opt_WarnDeprecatedFlags | Opt_WarnAMP -- Introduced in GHC 7.8, obsolete since 7.10 @@ -2904,7 +2904,8 @@ fWarningFlags = [ flagSpec "warn-dodgy-foreign-imports" Opt_WarnDodgyForeignImports, flagSpec "warn-dodgy-imports" Opt_WarnDodgyImports, flagSpec "warn-empty-enumerations" Opt_WarnEmptyEnumerations, - flagSpec "warn-context-quantification" Opt_WarnContextQuantification, + flagSpec' "warn-context-quantification" Opt_WarnContextQuantification + (\_ -> deprecate "it is subsumed by an error message that cannot be disabled"), flagSpec' "warn-duplicate-constraints" Opt_WarnDuplicateConstraints (\_ -> deprecate "it is subsumed by -fwarn-redundant-constraints"), flagSpec "warn-redundant-constraints" Opt_WarnRedundantConstraints, @@ -3473,7 +3474,6 @@ standardWarnings -- see Note [Documenting warning flags] Opt_WarnInlineRuleShadowing, Opt_WarnAlternativeLayoutRuleTransitional, Opt_WarnUnsupportedLlvmVersion, - Opt_WarnContextQuantification, Opt_WarnTabs ] diff --git a/compiler/rename/RnTypes.hs b/compiler/rename/RnTypes.hs index fef7b67..4f7c291 100644 --- a/compiler/rename/RnTypes.hs +++ b/compiler/rename/RnTypes.hs @@ -264,8 +264,8 @@ f :: forall a. a -> b is an error f :: forall a. () => a -> b is an error f :: forall a. a -> (() => b) binds "a" and "b" -The -fwarn-context-quantification flag warns about -this situation. See rnHsTyKi for case HsForAllTy Qualified. +This situation is now considered to be an error. See rnHsTyKi for case +HsForAllTy Qualified. Note [Dealing with *] ~~~~~~~~~~~~~~~~~~~~~ diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index 3c98dc7..ebe1f75 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -8379,8 +8379,8 @@ example: As of GHC 7.10, this is deprecated. The ``-fwarn-context-quantification`` flag detects this situation and issues -a warning. In GHC 7.12, declarations such as ``MkSwizzle'`` will cause -an out-of-scope error. +a warning. In GHC 8.0 this flag was deprecated and declarations such as +``MkSwizzle'`` will cause an out-of-scope error. As for type signatures, implicit quantification happens for non-overloaded types too. So if you write this: diff --git a/docs/users_guide/using-warnings.rst b/docs/users_guide/using-warnings.rst index 9b98686..699c8fd 100644 --- a/docs/users_guide/using-warnings.rst +++ b/docs/users_guide/using-warnings.rst @@ -19,9 +19,8 @@ generally likely to indicate bugs in your program. These are: ``-fwarn-missing-methods``, ``-fwarn-wrong-do-bind``, ``-fwarn-unsupported-calling-conventions``, ``-fwarn-dodgy-foreign-imports``, ``-fwarn-inline-rule-shadowing``, -``-fwarn-unsupported-llvm-version``, ``-fwarn-context-quantification``, -and ``-fwarn-tabs``. The following flags are simple ways to select -standard ?packages? of warnings: +``-fwarn-unsupported-llvm-version`` and ``-fwarn-tabs``. The following flags are +simple ways to select standard ?packages? of warnings: ``-W`` .. index:: @@ -894,27 +893,6 @@ command line. do { mapM_ popInt xs ; return 10 } -``-fwarn-context-quantification`` - .. index:: - single: -fwarn-context-quantification - single: implicit context quantification, warning - single: context, implicit quantification - - Report if a variable is quantified only due to its presence in a - context (see :ref:`universal-quantification`). For example, - - :: - - type T a = Monad m => a -> f a - - It is recommended to write this polymorphic type as - - :: - - type T a = forall m. Monad m => a -> f a - - instead. - ``-fwarn-wrong-do-bind`` .. index:: single: -fwarn-wrong-do-bind diff --git a/testsuite/tests/rename/should_compile/T4426.hs b/testsuite/tests/rename/should_compile/T4426.hs index 610f670..49e5875 100644 --- a/testsuite/tests/rename/should_compile/T4426.hs +++ b/testsuite/tests/rename/should_compile/T4426.hs @@ -1,5 +1,4 @@ {-# LANGUAGE RankNTypes #-} -{- # OPTIONS_GHC -fwarn-context-quantification #-} module T4426 where diff --git a/testsuite/tests/rename/should_compile/T4426.stderr b/testsuite/tests/rename/should_compile/T4426.stderr index f731f35..0d0b706 100644 --- a/testsuite/tests/rename/should_compile/T4426.stderr +++ b/testsuite/tests/rename/should_compile/T4426.stderr @@ -1,18 +1,18 @@ -T4426.hs:11:18: error: Not in scope: type variable ?m? +T4426.hs:10:18: error: Not in scope: type variable ?m? -T4426.hs:11:28: error: Not in scope: type variable ?m? +T4426.hs:10:28: error: Not in scope: type variable ?m? -T4426.hs:13:18: error: Not in scope: type variable ?b? +T4426.hs:12:18: error: Not in scope: type variable ?b? -T4426.hs:13:28: error: Not in scope: type variable ?b? +T4426.hs:12:28: error: Not in scope: type variable ?b? -T4426.hs:15:24: error: Not in scope: type variable ?b? +T4426.hs:14:24: error: Not in scope: type variable ?b? -T4426.hs:15:34: error: Not in scope: type variable ?b? +T4426.hs:14:34: error: Not in scope: type variable ?b? -T4426.hs:15:39: error: Not in scope: type variable ?c? +T4426.hs:14:39: error: Not in scope: type variable ?c? -T4426.hs:17:23: error: Not in scope: type variable ?m? +T4426.hs:16:23: error: Not in scope: type variable ?m? -T4426.hs:17:28: error: Not in scope: type variable ?m? +T4426.hs:16:28: error: Not in scope: type variable ?m? From git at git.haskell.org Tue Dec 15 00:37:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 00:37:57 +0000 (UTC) Subject: [commit: ghc] master: DynFlags: remove Opt_Static (6d9c18c) Message-ID: <20151215003757.08C6B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6d9c18cb43c1fda95932ef0f640dcf41906a2773/ghc >--------------------------------------------------------------- commit 6d9c18cb43c1fda95932ef0f640dcf41906a2773 Author: Thomas Miedema Date: Tue Dec 15 01:07:24 2015 +0100 DynFlags: remove Opt_Static There are currently 2 different ways to test for a static or dynamic build: * Test if WayDyn is in ways * Test if Opt_Static is set The problem is that these can easily go out of sync, especially when using the GHC API. This commit replaces all queries of Opt_Static with an equivalent query of WayDyn. This would have prevented bug #8294 and fixes #11154. Reviewers: hvr, austin, bgamari Reviewed By: austin, bgamari Differential Revision: https://phabricator.haskell.org/D1607 GHC Trac Issues: #10636 >--------------------------------------------------------------- 6d9c18cb43c1fda95932ef0f640dcf41906a2773 compiler/cmm/CLabel.hs | 10 +++++----- compiler/ghci/Linker.hs | 11 ++++++----- compiler/main/DriverPipeline.hs | 8 ++++---- compiler/main/DynFlags.hs | 13 ++++--------- compiler/main/Packages.hs | 6 +++--- compiler/main/SysTools.hs | 2 +- compiler/nativeGen/PIC.hs | 14 +++++++------- 7 files changed, 30 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 6d9c18cb43c1fda95932ef0f640dcf41906a2773 From git at git.haskell.org Tue Dec 15 01:06:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 01:06:17 +0000 (UTC) Subject: [commit: ghc] master: TysWiredIn: Fix a comment - Note [TYPE] is in TysPrim (8e6f9bf) Message-ID: <20151215010617.1A7BB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8e6f9bf2fa436aa76a2f43dfca8503513af95b41/ghc >--------------------------------------------------------------- commit 8e6f9bf2fa436aa76a2f43dfca8503513af95b41 Author: ?mer Sinan A?acan Date: Mon Dec 14 20:05:43 2015 -0500 TysWiredIn: Fix a comment - Note [TYPE] is in TysPrim >--------------------------------------------------------------- 8e6f9bf2fa436aa76a2f43dfca8503513af95b41 compiler/prelude/TysWiredIn.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/prelude/TysWiredIn.hs b/compiler/prelude/TysWiredIn.hs index 1d0feab..d92c4cd 100644 --- a/compiler/prelude/TysWiredIn.hs +++ b/compiler/prelude/TysWiredIn.hs @@ -662,7 +662,7 @@ heqSCSelId, coercibleSCSelId :: Id sc_sel_id = mkDictSelId coercibleSCSelIdName klass -- For information about the usage of the following type, see Note [TYPE] --- in module Kind +-- in module TysPrim levityTy :: Type levityTy = mkTyConTy levityTyCon From git at git.haskell.org Tue Dec 15 10:52:42 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 10:52:42 +0000 (UTC) Subject: [commit: ghc] master: Update expected test output for 32 bit platforms (4c9d1ea) Message-ID: <20151215105242.A0AFE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4c9d1eab2479a40e759d086ed7069dbd970d1307/ghc >--------------------------------------------------------------- commit 4c9d1eab2479a40e759d086ed7069dbd970d1307 Author: Erik de Castro Lopo Date: Tue Dec 15 21:53:11 2015 +1100 Update expected test output for 32 bit platforms Test Plan: Run tests on a 32 bit platform Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1627 >--------------------------------------------------------------- 4c9d1eab2479a40e759d086ed7069dbd970d1307 .../deSugar/should_compile/T2431.stderr-ws-32 | 22 ++++-- .../tests/roles/should_compile/Roles1.stderr-ws-32 | 84 ++++++---------------- .../roles/should_compile/Roles13.stderr-ws-32 | 34 +++++---- .../roles/should_compile/Roles14.stderr-ws-32 | 9 +-- .../tests/roles/should_compile/Roles2.stderr-ws-32 | 18 ++--- .../tests/roles/should_compile/Roles3.stderr-ws-32 | 38 ++++------ .../tests/roles/should_compile/Roles4.stderr-ws-32 | 16 ++--- .../tests/roles/should_compile/T8958.stderr-ws-32 | 6 +- .../simplCore/should_compile/T7360.stderr-ws-32 | 58 ++++++++++++++- testsuite/tests/th/TH_Roles2.stderr-ws-32 | 1 + 10 files changed, 146 insertions(+), 140 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 4c9d1eab2479a40e759d086ed7069dbd970d1307 From git at git.haskell.org Tue Dec 15 11:03:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 11:03:39 +0000 (UTC) Subject: [commit: packages/xhtml] tag '3000.2.1' created Message-ID: <20151215110339.0AF903A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/xhtml New tag : 3000.2.1 Referencing: 6567d42aaf8a4b5da825056367d330a1797a811e From git at git.haskell.org Tue Dec 15 13:34:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 13:34:16 +0000 (UTC) Subject: [commit: packages/process] branch 'less-cpp' created Message-ID: <20151215133416.A5E503A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process New branch : less-cpp Referencing: 9dae7ad1b5688723f129cd9eb2b2b82f7f2f6ec4 From git at git.haskell.org Tue Dec 15 13:34:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 13:34:18 +0000 (UTC) Subject: [commit: packages/process] tag 'v1.4.1.0' created Message-ID: <20151215133418.A627B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process New tag : v1.4.1.0 Referencing: dac7908c884fefebd037cfcbadfd5c374cf10d90 From git at git.haskell.org Tue Dec 15 13:34:20 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 13:34:20 +0000 (UTC) Subject: [commit: packages/process] less-cpp, master: Refactor .Internals into .Common, .Windows, and .Posix (tested only on Windows) (78b807a) Message-ID: <20151215133420.B14D33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: less-cpp,master Link : http://ghc.haskell.org/trac/ghc/changeset/78b807a7574eada97d4126099ddfd2c42dfabd8a/process >--------------------------------------------------------------- commit 78b807a7574eada97d4126099ddfd2c42dfabd8a Author: Michael Snoyman Date: Mon Nov 2 08:12:16 2015 -0800 Refactor .Internals into .Common, .Windows, and .Posix (tested only on Windows) >--------------------------------------------------------------- 78b807a7574eada97d4126099ddfd2c42dfabd8a System/Process/Common.hs | 201 ++++++++++++++ System/Process/Internals.hs | 651 +------------------------------------------- System/Process/Posix.hs | 276 +++++++++++++++++++ System/Process/Windows.hs | 244 +++++++++++++++++ process.cabal | 6 + 5 files changed, 741 insertions(+), 637 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 78b807a7574eada97d4126099ddfd2c42dfabd8a From git at git.haskell.org Tue Dec 15 13:34:22 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 13:34:22 +0000 (UTC) Subject: [commit: packages/process] less-cpp,master: appveyor.yml (3b3ba4b) Message-ID: <20151215133422.B8B683A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: less-cpp,master Link : http://ghc.haskell.org/trac/ghc/changeset/3b3ba4b827060117324ab233a950e48eba3b45e5/process >--------------------------------------------------------------- commit 3b3ba4b827060117324ab233a950e48eba3b45e5 Author: Michael Snoyman Date: Mon Nov 2 08:12:53 2015 -0800 appveyor.yml >--------------------------------------------------------------- 3b3ba4b827060117324ab233a950e48eba3b45e5 appveyor.yml | 19 +++++++++++++++++++ 1 file changed, 19 insertions(+) diff --git a/appveyor.yml b/appveyor.yml new file mode 100644 index 0000000..671e09b --- /dev/null +++ b/appveyor.yml @@ -0,0 +1,19 @@ +cache: +- "c:\\sr" # stack root, short paths == less problems + +build: off + +before_test: +- curl -ostack.zip -L --insecure http://www.stackage.org/stack/windows-i386 +- 7z x stack.zip stack.exe + +clone_folder: "c:\\stack" +environment: + global: + STACK_ROOT: "c:\\sr" + +test_script: +- stack setup > nul +# The ugly echo "" hack is to avoid complaints about 0 being an invalid file +# descriptor +- echo "" | stack --no-terminal test --pedantic From git at git.haskell.org Tue Dec 15 13:34:24 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 13:34:24 +0000 (UTC) Subject: [commit: packages/process] less-cpp, master: Fail on all warnings on Travis (7738849) Message-ID: <20151215133424.BF8AC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: less-cpp,master Link : http://ghc.haskell.org/trac/ghc/changeset/77388495bad902fdc0757c774e7b1e16afbe53ed/process >--------------------------------------------------------------- commit 77388495bad902fdc0757c774e7b1e16afbe53ed Author: Michael Snoyman Date: Mon Nov 2 08:13:26 2015 -0800 Fail on all warnings on Travis >--------------------------------------------------------------- 77388495bad902fdc0757c774e7b1e16afbe53ed .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index ef55c45..911a546 100644 --- a/.travis.yml +++ b/.travis.yml @@ -28,7 +28,7 @@ install: script: - autoreconf -i - - cabal configure -v2 --enable-tests + - cabal configure -v2 --enable-tests --ghc-options="-Wall -Werror" - cabal build - cabal check || [ "$CABALVER" == "1.16" ] - ./dist/build/test/test # Using cabal test was giving trouble with cabal 1.22 From git at git.haskell.org Tue Dec 15 13:34:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 13:34:26 +0000 (UTC) Subject: [commit: packages/process] less-cpp, master: appveyor: do autoreconf (807e4e9) Message-ID: <20151215133426.C50B33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: less-cpp,master Link : http://ghc.haskell.org/trac/ghc/changeset/807e4e94bec9091c884357448b43c630bfd8cb08/process >--------------------------------------------------------------- commit 807e4e94bec9091c884357448b43c630bfd8cb08 Author: Michael Snoyman Date: Mon Nov 2 08:24:54 2015 -0800 appveyor: do autoreconf >--------------------------------------------------------------- 807e4e94bec9091c884357448b43c630bfd8cb08 appveyor.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/appveyor.yml b/appveyor.yml index 671e09b..806c078 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -16,4 +16,5 @@ test_script: - stack setup > nul # The ugly echo "" hack is to avoid complaints about 0 being an invalid file # descriptor +- echo "" | stack exec "bash -c 'pacman -S autoconf && autoreconf -i'" - echo "" | stack --no-terminal test --pedantic From git at git.haskell.org Tue Dec 15 13:34:28 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 13:34:28 +0000 (UTC) Subject: [commit: packages/process] less-cpp, master: Builds on non-Windows (46f0f27) Message-ID: <20151215133428.CBD373A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: less-cpp,master Link : http://ghc.haskell.org/trac/ghc/changeset/46f0f2778fbc3e62e9d36cd2aabfda2ef612e0cb/process >--------------------------------------------------------------- commit 46f0f2778fbc3e62e9d36cd2aabfda2ef612e0cb Author: Michael Snoyman Date: Mon Nov 2 16:30:17 2015 +0000 Builds on non-Windows >--------------------------------------------------------------- 46f0f2778fbc3e62e9d36cd2aabfda2ef612e0cb System/Process/Common.hs | 4 ++++ System/Process/Internals.hs | 14 +++----------- System/Process/Posix.hs | 45 +++++++++++++++++++++------------------------ System/Process/Windows.hs | 2 -- 4 files changed, 28 insertions(+), 37 deletions(-) diff --git a/System/Process/Common.hs b/System/Process/Common.hs index fd9f38b..e7ce4d9 100644 --- a/System/Process/Common.hs +++ b/System/Process/Common.hs @@ -40,6 +40,8 @@ import GHC.IO.IOMode #ifdef WINDOWS import Data.Word (Word32) import System.Win32.DebugApi (PHANDLE) +#else +import System.Posix.Types #endif #ifdef WINDOWS @@ -47,6 +49,8 @@ import System.Win32.DebugApi (PHANDLE) newtype CGid = CGid Word32 type GroupID = CGid type UserID = CGid +#else +type PHANDLE = CPid #endif data CreateProcess = CreateProcess{ diff --git a/System/Process/Internals.hs b/System/Process/Internals.hs index 04eb1d2..32052eb 100644 --- a/System/Process/Internals.hs +++ b/System/Process/Internals.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE CPP, RecordWildCards, BangPatterns #-} +{-# LANGUAGE CPP #-} {-# OPTIONS_HADDOCK not-home #-} #ifdef __GLASGOW_HASKELL__ {-# LANGUAGE Trustworthy #-} @@ -43,15 +43,8 @@ module System.Process.Internals ( translate, ) where -import Control.Concurrent -import Control.Exception -import Data.Bits import Foreign.C -import Foreign.Marshal -import Foreign.Ptr -import Foreign.Storable import System.IO -import System.IO.Unsafe #ifdef __GLASGOW_HASKELL__ import GHC.IO.Handle.FD (fdToHandle) @@ -65,9 +58,6 @@ import System.Process.Windows import System.Process.Posix #endif -#include "HsProcessConfig.h" -#include "processFlags.h" - -- ---------------------------------------------------------------------------- -- | This function is almost identical to @@ -88,6 +78,7 @@ createProcess_ -> CreateProcess -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) createProcess_ = createProcess_Internal +{-# INLINE createProcess_ #-} -- ------------------------------------------------------------------------ -- Escaping commands for shells @@ -146,6 +137,7 @@ use lpCommandLine alone, which CreateProcess supports. translate :: String -> String translate = translateInternal +{-# INLINE translate #-} -- ---------------------------------------------------------------------------- diff --git a/System/Process/Posix.hs b/System/Process/Posix.hs index 4619fd8..ec95743 100644 --- a/System/Process/Posix.hs +++ b/System/Process/Posix.hs @@ -1,5 +1,19 @@ +{-# LANGUAGE BangPatterns #-} +{-# LANGUAGE CPP #-} module System.Process.Posix - ( + ( mkProcessHandle + , translateInternal + , createProcess_Internal + , withCEnvironment + , closePHANDLE + , startDelegateControlC + , endDelegateControlC + , stopDelegateControlC + , isDefaultSignal + , ignoreSignal + , defaultSignal + , c_execvpe + , pPrPr_disableITimers ) where import Control.Concurrent @@ -11,43 +25,21 @@ import Foreign.Ptr import Foreign.Storable import System.IO.Unsafe -#if !defined(mingw32_HOST_OS) && !defined(__MINGW32__) import Control.Monad import Data.Char import System.IO import System.Posix.Process.Internals ( pPrPr_disableITimers, c_execvpe ) import System.Posix.Types -#endif -#ifdef __GLASGOW_HASKELL__ import System.Posix.Internals import GHC.IO.Exception -import GHC.IO.Encoding -import qualified GHC.IO.FD as FD -import GHC.IO.Device -import GHC.IO.Handle.FD -import GHC.IO.Handle.Internals -import GHC.IO.Handle.Types hiding (ClosedHandle) -import System.IO.Error -import Data.Typeable -# ifndef WINDOWS import System.Posix.Signals as Sig -# endif -#endif import System.Process.Common -#if WINDOWS -import System.Process.Windows -#else -import System.Process.Posix -#endif - #include "HsProcessConfig.h" #include "processFlags.h" -type PHANDLE = CPid - mkProcessHandle :: PHANDLE -> Bool -> IO ProcessHandle mkProcessHandle p mb_delegate_ctlc = do m <- newMVar (OpenHandle p) @@ -102,7 +94,12 @@ withCEnvironment envir act = -- ----------------------------------------------------------------------------- -- POSIX runProcess with signal handling in the child -createProcess_ fun CreateProcess{ cmdspec = cmdsp, +createProcess_Internal + :: String + -> CreateProcess + -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) +createProcess_Internal fun + CreateProcess{ cmdspec = cmdsp, cwd = mb_cwd, env = mb_env, std_in = mb_stdin, diff --git a/System/Process/Windows.hs b/System/Process/Windows.hs index 3afeeb3..bae63c6 100644 --- a/System/Process/Windows.hs +++ b/System/Process/Windows.hs @@ -75,7 +75,6 @@ foreign import WINDOWS_CCONV unsafe "CloseHandle" :: PHANDLE -> IO () -{-# INLINE createProcess_Internal #-} createProcess_Internal :: String -- ^ function name (for error messages) -> CreateProcess @@ -222,7 +221,6 @@ findCommandInterpreter = do "findCommandInterpreter" Nothing Nothing) Just cmd -> return cmd -{-# INLINE translateInternal #-} translateInternal :: String -> String translateInternal xs = '"' : snd (foldr escape (True,"\"") xs) where escape '"' (_, str) = (True, '\\' : '"' : str) From git at git.haskell.org Tue Dec 15 13:34:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 13:34:30 +0000 (UTC) Subject: [commit: packages/process] less-cpp, master: Add some clarifying comments (edaedae) Message-ID: <20151215133430.D26053A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: less-cpp,master Link : http://ghc.haskell.org/trac/ghc/changeset/edaedaee7461560cb3b9ca3a4ef0b3990d95cd7f/process >--------------------------------------------------------------- commit edaedaee7461560cb3b9ca3a4ef0b3990d95cd7f Author: Michael Snoyman Date: Mon Nov 2 16:35:09 2015 +0000 Add some clarifying comments >--------------------------------------------------------------- edaedaee7461560cb3b9ca3a4ef0b3990d95cd7f System/Process/Common.hs | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/System/Process/Common.hs b/System/Process/Common.hs index e7ce4d9..5d2e180 100644 --- a/System/Process/Common.hs +++ b/System/Process/Common.hs @@ -37,6 +37,8 @@ import System.IO.Error import Data.Typeable import GHC.IO.IOMode +-- We do a minimal amount of CPP here to provide uniform data types across +-- Windows and POSIX. #ifdef WINDOWS import Data.Word (Word32) import System.Win32.DebugApi (PHANDLE) @@ -45,7 +47,9 @@ import System.Posix.Types #endif #ifdef WINDOWS --- Define some missing types for Windows compatibility +-- Define some missing types for Windows compatibility. Note that these values +-- will never actually be used, as the setuid/setgid system calls are not +-- applicable on Windows. No value of this type will ever exist. newtype CGid = CGid Word32 type GroupID = CGid type UserID = CGid From git at git.haskell.org Tue Dec 15 13:34:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 13:34:32 +0000 (UTC) Subject: [commit: packages/process] less-cpp, master: appveyor: s/bash/sh (6715752) Message-ID: <20151215133432.D86AB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: less-cpp,master Link : http://ghc.haskell.org/trac/ghc/changeset/67157525e26de80933eded966865372ac52eb638/process >--------------------------------------------------------------- commit 67157525e26de80933eded966865372ac52eb638 Author: Michael Snoyman Date: Mon Nov 2 16:36:02 2015 +0000 appveyor: s/bash/sh >--------------------------------------------------------------- 67157525e26de80933eded966865372ac52eb638 appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index 806c078..3749543 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -16,5 +16,5 @@ test_script: - stack setup > nul # The ugly echo "" hack is to avoid complaints about 0 being an invalid file # descriptor -- echo "" | stack exec "bash -c 'pacman -S autoconf && autoreconf -i'" +- echo "" | stack exec "sh -c 'pacman -S autoconf && autoreconf -i'" - echo "" | stack --no-terminal test --pedantic From git at git.haskell.org Tue Dec 15 13:34:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 13:34:34 +0000 (UTC) Subject: [commit: packages/process] less-cpp, master: Fix some GHC 7.2 warnings (c12eb1c) Message-ID: <20151215133434.DED253A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: less-cpp,master Link : http://ghc.haskell.org/trac/ghc/changeset/c12eb1cd92b54333bec29356dd88a966ccf67ada/process >--------------------------------------------------------------- commit c12eb1cd92b54333bec29356dd88a966ccf67ada Author: Michael Snoyman Date: Mon Nov 2 16:40:17 2015 +0000 Fix some GHC 7.2 warnings >--------------------------------------------------------------- c12eb1cd92b54333bec29356dd88a966ccf67ada System/Process.hsc | 2 ++ System/Process/Common.hs | 10 ++++++++-- 2 files changed, 10 insertions(+), 2 deletions(-) diff --git a/System/Process.hsc b/System/Process.hsc index a390c74..f8431a4 100644 --- a/System/Process.hsc +++ b/System/Process.hsc @@ -94,8 +94,10 @@ import Control.Exception (onException) #else import System.Posix.Process (getProcessGroupIDOf) import qualified System.Posix.IO as Posix +#if MIN_VERSION_base(4,5,0) import System.Posix.Types #endif +#endif #ifdef __GLASGOW_HASKELL__ import GHC.IO.Exception ( ioException, IOErrorType(..), IOException(..) ) diff --git a/System/Process/Common.hs b/System/Process/Common.hs index 5d2e180..0c55ff1 100644 --- a/System/Process/Common.hs +++ b/System/Process/Common.hs @@ -1,8 +1,7 @@ {-# LANGUAGE CPP #-} {-# LANGUAGE RecordWildCards #-} module System.Process.Common - ( CGid (..) - , CreateProcess (..) + ( CreateProcess (..) , CmdSpec (..) , StdStream (..) , ProcessHandle(..) @@ -17,6 +16,13 @@ module System.Process.Common , mbFd , mbPipe , pfdToHandle + +-- Avoid a warning on Windows +#ifdef WINDOWS + , CGid (..) +#else + , CGid +#endif ) where import Control.Concurrent From git at git.haskell.org Tue Dec 15 13:34:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 13:34:36 +0000 (UTC) Subject: [commit: packages/process] less-cpp, master: Ignore Vim .swp files (c045a6e) Message-ID: <20151215133436.E50A83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: less-cpp,master Link : http://ghc.haskell.org/trac/ghc/changeset/c045a6ea1334dbfbf39c22cf06bede20f1b34cdd/process >--------------------------------------------------------------- commit c045a6ea1334dbfbf39c22cf06bede20f1b34cdd Author: Michael Snoyman Date: Mon Nov 2 16:43:21 2015 +0000 Ignore Vim .swp files >--------------------------------------------------------------- c045a6ea1334dbfbf39c22cf06bede20f1b34cdd .gitignore | 1 + 1 file changed, 1 insertion(+) diff --git a/.gitignore b/.gitignore index 63b58e1..a123a67 100644 --- a/.gitignore +++ b/.gitignore @@ -1,5 +1,6 @@ /dist/ /.stack-work/ +*.swp # Specific generated files GNUmakefile From git at git.haskell.org Tue Dec 15 13:34:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 13:34:38 +0000 (UTC) Subject: [commit: packages/process] less-cpp, master: appveyor: I'll get this right eventually (5d81377) Message-ID: <20151215133438.EB1C93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: less-cpp,master Link : http://ghc.haskell.org/trac/ghc/changeset/5d813773e409b1146de44fe4337cf458358ba9c2/process >--------------------------------------------------------------- commit 5d813773e409b1146de44fe4337cf458358ba9c2 Author: Michael Snoyman Date: Mon Nov 2 16:54:00 2015 +0000 appveyor: I'll get this right eventually >--------------------------------------------------------------- 5d813773e409b1146de44fe4337cf458358ba9c2 appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index 3749543..4117809 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -16,5 +16,5 @@ test_script: - stack setup > nul # The ugly echo "" hack is to avoid complaints about 0 being an invalid file # descriptor -- echo "" | stack exec "sh -c 'pacman -S autoconf && autoreconf -i'" +- echo "" | stack exec -- sh -c "pacman -S autoconf && autoreconf -i" - echo "" | stack --no-terminal test --pedantic From git at git.haskell.org Tue Dec 15 13:34:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 13:34:40 +0000 (UTC) Subject: [commit: packages/process] less-cpp, master: Move createPipe to per-OS modules (e63f474) Message-ID: <20151215133440.F2EBA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: less-cpp,master Link : http://ghc.haskell.org/trac/ghc/changeset/e63f47445f50c64496c71171d938f511dd1a6d4d/process >--------------------------------------------------------------- commit e63f47445f50c64496c71171d938f511dd1a6d4d Author: Michael Snoyman Date: Mon Nov 2 16:57:45 2015 +0000 Move createPipe to per-OS modules >--------------------------------------------------------------- e63f47445f50c64496c71171d938f511dd1a6d4d System/Process.hsc | 38 -------------------------------------- System/Process/Internals.hs | 12 ++++++++++++ System/Process/Posix.hs | 9 +++++++++ System/Process/Windows.hs | 22 ++++++++++++++++++++++ 4 files changed, 43 insertions(+), 38 deletions(-) diff --git a/System/Process.hsc b/System/Process.hsc index f8431a4..c0b08ee 100644 --- a/System/Process.hsc +++ b/System/Process.hsc @@ -88,12 +88,9 @@ import System.IO import System.IO.Error (mkIOError, ioeSetErrorString) #if defined(mingw32_HOST_OS) -# include /* for _close and _pipe */ # include /* for _O_BINARY */ -import Control.Exception (onException) #else import System.Posix.Process (getProcessGroupIDOf) -import qualified System.Posix.IO as Posix #if MIN_VERSION_base(4,5,0) import System.Posix.Types #endif @@ -934,38 +931,3 @@ rawSystem cmd args = system (showCommandForUser cmd args) #else rawSystem cmd args = system (showCommandForUser cmd args) #endif - --- --------------------------------------------------------------------------- --- createPipe - --- | Create a pipe for interprocess communication and return a --- @(readEnd, writeEnd)@ `Handle` pair. --- --- @since 1.2.1.0 -createPipe :: IO (Handle, Handle) -#if !mingw32_HOST_OS -createPipe = do - (readfd, writefd) <- Posix.createPipe - readh <- Posix.fdToHandle readfd - writeh <- Posix.fdToHandle writefd - return (readh, writeh) -#else -createPipe = do - (readfd, writefd) <- allocaArray 2 $ \ pfds -> do - throwErrnoIfMinus1_ "_pipe" $ c__pipe pfds 2 (#const _O_BINARY) - readfd <- peek pfds - writefd <- peekElemOff pfds 1 - return (readfd, writefd) - (do readh <- fdToHandle readfd - writeh <- fdToHandle writefd - return (readh, writeh)) `onException` (close readfd >> close writefd) - -close :: CInt -> IO () -close = throwErrnoIfMinus1_ "_close" . c__close - -foreign import ccall "io.h _pipe" c__pipe :: - Ptr CInt -> CUInt -> CInt -> IO CInt - -foreign import ccall "io.h _close" c__close :: - CInt -> IO CInt -#endif diff --git a/System/Process/Internals.hs b/System/Process/Internals.hs index 32052eb..3a673c7 100644 --- a/System/Process/Internals.hs +++ b/System/Process/Internals.hs @@ -41,6 +41,7 @@ module System.Process.Internals ( #endif withFilePathException, withCEnvironment, translate, + createPipe, ) where import Foreign.C @@ -158,3 +159,14 @@ runGenProcess_ fun c (Just sig) (Just sig') | isDefaultSignal sig && sig == sig' runGenProcess_ fun c _ _ = createProcess_ fun c #endif + +-- --------------------------------------------------------------------------- +-- createPipe + +-- | Create a pipe for interprocess communication and return a +-- @(readEnd, writeEnd)@ `Handle` pair. +-- +-- @since 1.2.1.0 +createPipe :: IO (Handle, Handle) +createPipe = createPipeInternal +{-# INLINE createPipe #-} diff --git a/System/Process/Posix.hs b/System/Process/Posix.hs index ec95743..e9d1e31 100644 --- a/System/Process/Posix.hs +++ b/System/Process/Posix.hs @@ -14,6 +14,7 @@ module System.Process.Posix , defaultSignal , c_execvpe , pPrPr_disableITimers + , createPipeInternal ) where import Control.Concurrent @@ -34,6 +35,7 @@ import System.Posix.Types import System.Posix.Internals import GHC.IO.Exception import System.Posix.Signals as Sig +import qualified System.Posix.IO as Posix import System.Process.Common @@ -271,3 +273,10 @@ defaultSignal = CONST_SIG_DFL isDefaultSignal :: CLong -> Bool isDefaultSignal = (== defaultSignal) + +createPipeInternal :: IO (Handle, Handle) +createPipeInternal = do + (readfd, writefd) <- Posix.createPipe + readh <- Posix.fdToHandle readfd + writeh <- Posix.fdToHandle writefd + return (readh, writeh) diff --git a/System/Process/Windows.hs b/System/Process/Windows.hs index bae63c6..676ecbe 100644 --- a/System/Process/Windows.hs +++ b/System/Process/Windows.hs @@ -9,6 +9,7 @@ module System.Process.Windows , endDelegateControlC , stopDelegateControlC , isDefaultSignal + , createPipeInternal ) where import System.Process.Common @@ -45,6 +46,7 @@ import System.Process.Common # define WINDOWS_CCONV ccall #endif +#include /* for _close and _pipe */ #include "HsProcessConfig.h" #include "processFlags.h" @@ -240,3 +242,23 @@ withCEnvironment envir act = isDefaultSignal :: CLong -> Bool isDefaultSignal = const False + +createPipeInternal :: IO (Handle, Handle) +createPipeInternal = do + (readfd, writefd) <- allocaArray 2 $ \ pfds -> do + throwErrnoIfMinus1_ "_pipe" $ c__pipe pfds 2 (#const _O_BINARY) + readfd <- peek pfds + writefd <- peekElemOff pfds 1 + return (readfd, writefd) + (do readh <- fdToHandle readfd + writeh <- fdToHandle writefd + return (readh, writeh)) `onException` (close readfd >> close writefd) + +close :: CInt -> IO () +close = throwErrnoIfMinus1_ "_close" . c__close + +foreign import ccall "io.h _pipe" c__pipe :: + Ptr CInt -> CUInt -> CInt -> IO CInt + +foreign import ccall "io.h _close" c__close :: + CInt -> IO CInt From git at git.haskell.org Tue Dec 15 13:34:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 13:34:43 +0000 (UTC) Subject: [commit: packages/process] less-cpp, master: Move interruptProcessGroupOf into per-OS modules (6a8ca1e) Message-ID: <20151215133443.054413A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: less-cpp,master Link : http://ghc.haskell.org/trac/ghc/changeset/6a8ca1ea4376bf93ac8fcfe88ffa6d9f860c9687/process >--------------------------------------------------------------- commit 6a8ca1ea4376bf93ac8fcfe88ffa6d9f860c9687 Author: Michael Snoyman Date: Mon Nov 2 17:02:44 2015 +0000 Move interruptProcessGroupOf into per-OS modules >--------------------------------------------------------------- 6a8ca1ea4376bf93ac8fcfe88ffa6d9f860c9687 System/Process.hsc | 38 -------------------------------------- System/Process/Internals.hs | 17 +++++++++++++++++ System/Process/Posix.hs | 13 +++++++++++++ System/Process/Windows.hs | 23 +++++++++++++++++++++++ 4 files changed, 53 insertions(+), 38 deletions(-) diff --git a/System/Process.hsc b/System/Process.hsc index c0b08ee..de07225 100644 --- a/System/Process.hsc +++ b/System/Process.hsc @@ -90,7 +90,6 @@ import System.IO.Error (mkIOError, ioeSetErrorString) #if defined(mingw32_HOST_OS) # include /* for _O_BINARY */ #else -import System.Posix.Process (getProcessGroupIDOf) #if MIN_VERSION_base(4,5,0) import System.Posix.Types #endif @@ -98,12 +97,6 @@ import System.Posix.Types #ifdef __GLASGOW_HASKELL__ import GHC.IO.Exception ( ioException, IOErrorType(..), IOException(..) ) -# if defined(mingw32_HOST_OS) -import System.Win32.Console (generateConsoleCtrlEvent, cTRL_BREAK_EVENT) -import System.Win32.Process (getProcessId) -# else -import System.Posix.Signals -# endif #endif -- ---------------------------------------------------------------------------- @@ -689,37 +682,6 @@ terminateProcess ph = do -- ---------------------------------------------------------------------------- --- interruptProcessGroupOf - --- | Sends an interrupt signal to the process group of the given process. --- --- On Unix systems, it sends the group the SIGINT signal. --- --- On Windows systems, it generates a CTRL_BREAK_EVENT and will only work for --- processes created using 'createProcess' and setting the 'create_group' flag - -interruptProcessGroupOf - :: ProcessHandle -- ^ A process in the process group - -> IO () -interruptProcessGroupOf ph = do - withProcessHandle ph $ \p_ -> do - case p_ of - ClosedHandle _ -> return () - OpenHandle h -> do -#if mingw32_HOST_OS - pid <- getProcessId h - generateConsoleCtrlEvent cTRL_BREAK_EVENT pid --- We can't use an #elif here, because MIN_VERSION_unix isn't defined --- on Windows, so on Windows cpp fails: --- error: missing binary operator before token "(" -#else - pgid <- getProcessGroupIDOf h - signalProcessGroup sigINT pgid -#endif - return () - - --- ---------------------------------------------------------------------------- -- Interface to C bits foreign import ccall unsafe "terminateProcess" diff --git a/System/Process/Internals.hs b/System/Process/Internals.hs index 3a673c7..69ecd2b 100644 --- a/System/Process/Internals.hs +++ b/System/Process/Internals.hs @@ -42,6 +42,7 @@ module System.Process.Internals ( withFilePathException, withCEnvironment, translate, createPipe, + interruptProcessGroupOf, ) where import Foreign.C @@ -170,3 +171,19 @@ runGenProcess_ fun c _ _ = createProcess_ fun c createPipe :: IO (Handle, Handle) createPipe = createPipeInternal {-# INLINE createPipe #-} + + +-- ---------------------------------------------------------------------------- +-- interruptProcessGroupOf + +-- | Sends an interrupt signal to the process group of the given process. +-- +-- On Unix systems, it sends the group the SIGINT signal. +-- +-- On Windows systems, it generates a CTRL_BREAK_EVENT and will only work for +-- processes created using 'createProcess' and setting the 'create_group' flag + +interruptProcessGroupOf + :: ProcessHandle -- ^ A process in the process group + -> IO () +interruptProcessGroupOf = interruptProcessGroupOfInternal diff --git a/System/Process/Posix.hs b/System/Process/Posix.hs index e9d1e31..a68d942 100644 --- a/System/Process/Posix.hs +++ b/System/Process/Posix.hs @@ -15,6 +15,7 @@ module System.Process.Posix , c_execvpe , pPrPr_disableITimers , createPipeInternal + , interruptProcessGroupOfInternal ) where import Control.Concurrent @@ -36,6 +37,7 @@ import System.Posix.Internals import GHC.IO.Exception import System.Posix.Signals as Sig import qualified System.Posix.IO as Posix +import System.Posix.Process (getProcessGroupIDOf) import System.Process.Common @@ -280,3 +282,14 @@ createPipeInternal = do readh <- Posix.fdToHandle readfd writeh <- Posix.fdToHandle writefd return (readh, writeh) + +interruptProcessGroupOfInternal + :: ProcessHandle -- ^ A process in the process group + -> IO () +interruptProcessGroupOfInternal ph = do + withProcessHandle ph $ \p_ -> do + case p_ of + ClosedHandle _ -> return () + OpenHandle h -> do + pgid <- getProcessGroupIDOf h + signalProcessGroup sigINT pgid diff --git a/System/Process/Windows.hs b/System/Process/Windows.hs index 676ecbe..51a4c51 100644 --- a/System/Process/Windows.hs +++ b/System/Process/Windows.hs @@ -10,6 +10,7 @@ module System.Process.Windows , stopDelegateControlC , isDefaultSignal , createPipeInternal + , interruptProcessGroupOfInternal ) where import System.Process.Common @@ -37,6 +38,8 @@ import GHC.IO.IOMode import System.Directory ( doesFileExist ) import System.Environment ( getEnv ) import System.FilePath +import System.Win32.Console (generateConsoleCtrlEvent, cTRL_BREAK_EVENT) +import System.Win32.Process (getProcessId) import System.Process.Common @@ -262,3 +265,23 @@ foreign import ccall "io.h _pipe" c__pipe :: foreign import ccall "io.h _close" c__close :: CInt -> IO CInt + +interruptProcessGroupOfInternal + :: ProcessHandle -- ^ A process in the process group + -> IO () +interruptProcessGroupOfInternal ph = do + withProcessHandle ph $ \p_ -> do + case p_ of + ClosedHandle _ -> return () + OpenHandle h -> do +#if mingw32_HOST_OS + pid <- getProcessId h + generateConsoleCtrlEvent cTRL_BREAK_EVENT pid +-- We can't use an #elif here, because MIN_VERSION_unix isn't defined +-- on Windows, so on Windows cpp fails: +-- error: missing binary operator before token "(" +#else + pgid <- getProcessGroupIDOf h + signalProcessGroup sigINT pgid +#endif + return () From git at git.haskell.org Tue Dec 15 13:34:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 13:34:45 +0000 (UTC) Subject: [commit: packages/process] less-cpp, master: Pass -y to pacman (34a6894) Message-ID: <20151215133445.0B5F93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: less-cpp,master Link : http://ghc.haskell.org/trac/ghc/changeset/34a68947d2efc3c1a3076745328a9d5a0fb39649/process >--------------------------------------------------------------- commit 34a68947d2efc3c1a3076745328a9d5a0fb39649 Author: Michael Snoyman Date: Mon Nov 2 17:13:33 2015 +0000 Pass -y to pacman >--------------------------------------------------------------- 34a68947d2efc3c1a3076745328a9d5a0fb39649 appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index 4117809..195e8e2 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -16,5 +16,5 @@ test_script: - stack setup > nul # The ugly echo "" hack is to avoid complaints about 0 being an invalid file # descriptor -- echo "" | stack exec -- sh -c "pacman -S autoconf && autoreconf -i" +- echo "" | stack exec -- sh -c "pacman -Sy autoconf && autoreconf -i" - echo "" | stack --no-terminal test --pedantic From git at git.haskell.org Tue Dec 15 13:34:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 13:34:47 +0000 (UTC) Subject: [commit: packages/process] less-cpp, master: Even less CPP in System.Process (81243af) Message-ID: <20151215133447.125CC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: less-cpp,master Link : http://ghc.haskell.org/trac/ghc/changeset/81243afb78e8672c869d4806da5a9c410a346433/process >--------------------------------------------------------------- commit 81243afb78e8672c869d4806da5a9c410a346433 Author: Michael Snoyman Date: Mon Nov 2 17:13:56 2015 +0000 Even less CPP in System.Process >--------------------------------------------------------------- 81243afb78e8672c869d4806da5a9c410a346433 System/Process.hsc | 13 ++++--------- System/Process/Windows.hs | 1 + 2 files changed, 5 insertions(+), 9 deletions(-) diff --git a/System/Process.hsc b/System/Process.hsc index de07225..0673ca5 100644 --- a/System/Process.hsc +++ b/System/Process.hsc @@ -87,12 +87,9 @@ import System.Exit ( ExitCode(..) ) import System.IO import System.IO.Error (mkIOError, ioeSetErrorString) -#if defined(mingw32_HOST_OS) -# include /* for _O_BINARY */ -#else -#if MIN_VERSION_base(4,5,0) -import System.Posix.Types -#endif +-- Provide the data constructors for CPid on GHC 7.4 and later +#if !defined(WINDOWS) && MIN_VERSION_base(4,5,0) +import System.Posix.Types (CPid (..)) #endif #ifdef __GLASGOW_HASKELL__ @@ -887,9 +884,7 @@ rawSystem :: String -> [String] -> IO ExitCode rawSystem cmd args = do (_,_,_,p) <- createProcess_ "rawSystem" (proc cmd args) { delegate_ctlc = True } waitForProcess p -#elif !mingw32_HOST_OS --- crude fallback implementation: could do much better than this under Unix -rawSystem cmd args = system (showCommandForUser cmd args) #else +-- crude fallback implementation: could do much better than this under Unix rawSystem cmd args = system (showCommandForUser cmd args) #endif diff --git a/System/Process/Windows.hs b/System/Process/Windows.hs index 51a4c51..4c1d7ce 100644 --- a/System/Process/Windows.hs +++ b/System/Process/Windows.hs @@ -40,6 +40,7 @@ import System.Environment ( getEnv ) import System.FilePath import System.Win32.Console (generateConsoleCtrlEvent, cTRL_BREAK_EVENT) import System.Win32.Process (getProcessId) +# include /* for _O_BINARY */ import System.Process.Common From git at git.haskell.org Tue Dec 15 13:34:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 13:34:49 +0000 (UTC) Subject: [commit: packages/process] less-cpp, master: Fix Windows build again (9d923c5) Message-ID: <20151215133449.197023A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: less-cpp,master Link : http://ghc.haskell.org/trac/ghc/changeset/9d923c57adfa75626ee4c2c9d3d76bf137414233/process >--------------------------------------------------------------- commit 9d923c57adfa75626ee4c2c9d3d76bf137414233 Author: Michael Snoyman Date: Mon Nov 2 11:29:10 2015 -0800 Fix Windows build again >--------------------------------------------------------------- 9d923c57adfa75626ee4c2c9d3d76bf137414233 System/Process/{Windows.hs => Windows.hsc} | 37 +++++++++++++----------------- 1 file changed, 16 insertions(+), 21 deletions(-) diff --git a/System/Process/Windows.hs b/System/Process/Windows.hsc similarity index 93% rename from System/Process/Windows.hs rename to System/Process/Windows.hsc index 4c1d7ce..a984bae 100644 --- a/System/Process/Windows.hs +++ b/System/Process/Windows.hsc @@ -25,14 +25,9 @@ import System.IO.Unsafe import System.Posix.Internals import GHC.IO.Exception -import GHC.IO.Encoding -import qualified GHC.IO.FD as FD -import GHC.IO.Device import GHC.IO.Handle.FD -import GHC.IO.Handle.Internals import GHC.IO.Handle.Types hiding (ClosedHandle) import System.IO.Error -import Data.Typeable import GHC.IO.IOMode import System.Directory ( doesFileExist ) @@ -40,19 +35,11 @@ import System.Environment ( getEnv ) import System.FilePath import System.Win32.Console (generateConsoleCtrlEvent, cTRL_BREAK_EVENT) import System.Win32.Process (getProcessId) -# include /* for _O_BINARY */ -import System.Process.Common - -#if defined(i386_HOST_ARCH) -# define WINDOWS_CCONV stdcall -#elif defined(x86_64_HOST_ARCH) -# define WINDOWS_CCONV ccall -#endif +-- The double hash is used so that hsc does not process this include file +##include "processFlags.h" -#include /* for _close and _pipe */ -#include "HsProcessConfig.h" -#include "processFlags.h" +#include /* for _O_BINARY */ throwErrnoIfBadPHandle :: String -> IO PHANDLE -> IO PHANDLE throwErrnoIfBadPHandle = throwErrnoIfNull @@ -76,7 +63,15 @@ processHandleFinaliser m = closePHANDLE :: PHANDLE -> IO () closePHANDLE ph = c_CloseHandle ph -foreign import WINDOWS_CCONV unsafe "CloseHandle" +foreign import +#if defined(i386_HOST_ARCH) + stdcall +#elif defined(x86_64_HOST_ARCH) + ccall +#else +#error "Unknown architecture" +#endif + unsafe "CloseHandle" c_CloseHandle :: PHANDLE -> IO () @@ -241,7 +236,7 @@ translateInternal xs = '"' : snd (foldr escape (True,"\"") xs) withCEnvironment :: [(String,String)] -> (Ptr CWString -> IO a) -> IO a withCEnvironment envir act = - let env' = foldr (\(name, val) env -> name ++ ('=':val)++'\0':env) "\0" envir + let env' = foldr (\(name, val) env0 -> name ++ ('=':val)++'\0':env0) "\0" envir in withCWString env' (act . castPtr) isDefaultSignal :: CLong -> Bool @@ -256,10 +251,10 @@ createPipeInternal = do return (readfd, writefd) (do readh <- fdToHandle readfd writeh <- fdToHandle writefd - return (readh, writeh)) `onException` (close readfd >> close writefd) + return (readh, writeh)) `onException` (close' readfd >> close' writefd) -close :: CInt -> IO () -close = throwErrnoIfMinus1_ "_close" . c__close +close' :: CInt -> IO () +close' = throwErrnoIfMinus1_ "_close" . c__close foreign import ccall "io.h _pipe" c__pipe :: Ptr CInt -> CUInt -> CInt -> IO CInt From git at git.haskell.org Tue Dec 15 13:34:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 13:34:51 +0000 (UTC) Subject: [commit: packages/process] less-cpp,master: echo y (8b58ee0) Message-ID: <20151215133451.20A173A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: less-cpp,master Link : http://ghc.haskell.org/trac/ghc/changeset/8b58ee06394cc778ae34dfeec44b38253759c75a/process >--------------------------------------------------------------- commit 8b58ee06394cc778ae34dfeec44b38253759c75a Author: Michael Snoyman Date: Mon Nov 2 21:11:35 2015 +0000 echo y >--------------------------------------------------------------- 8b58ee06394cc778ae34dfeec44b38253759c75a appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index 195e8e2..0db89ce 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -16,5 +16,5 @@ test_script: - stack setup > nul # The ugly echo "" hack is to avoid complaints about 0 being an invalid file # descriptor -- echo "" | stack exec -- sh -c "pacman -Sy autoconf && autoreconf -i" +- echo "y" | stack exec -- sh -c "pacman -Sy autoconf && autoreconf -i" - echo "" | stack --no-terminal test --pedantic From git at git.haskell.org Tue Dec 15 13:34:53 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 13:34:53 +0000 (UTC) Subject: [commit: packages/process] less-cpp, master: Remove (broken) support for non-GHC compilers (60dbdb9) Message-ID: <20151215133453.263C23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: less-cpp,master Link : http://ghc.haskell.org/trac/ghc/changeset/60dbdb959996e49b8a61b249c7e96971295f0cca/process >--------------------------------------------------------------- commit 60dbdb959996e49b8a61b249c7e96971295f0cca Author: Michael Snoyman Date: Mon Nov 2 21:20:40 2015 +0000 Remove (broken) support for non-GHC compilers >--------------------------------------------------------------- 60dbdb959996e49b8a61b249c7e96971295f0cca System/Process.hsc | 15 --------------- System/Process/Internals.hs | 9 --------- System/Process/Posix.hs | 4 ---- process.cabal | 24 ++++++++++-------------- 4 files changed, 10 insertions(+), 42 deletions(-) diff --git a/System/Process.hsc b/System/Process.hsc index 0673ca5..6b870fd 100644 --- a/System/Process.hsc +++ b/System/Process.hsc @@ -1,12 +1,10 @@ {-# LANGUAGE CPP, ForeignFunctionInterface #-} -#ifdef __GLASGOW_HASKELL__ #if __GLASGOW_HASKELL__ >= 709 {-# LANGUAGE Safe #-} #else {-# LANGUAGE Trustworthy #-} #endif {-# LANGUAGE InterruptibleFFI #-} -#endif ----------------------------------------------------------------------------- -- | @@ -92,9 +90,7 @@ import System.IO.Error (mkIOError, ioeSetErrorString) import System.Posix.Types (CPid (..)) #endif -#ifdef __GLASGOW_HASKELL__ import GHC.IO.Exception ( ioException, IOErrorType(..), IOException(..) ) -#endif -- ---------------------------------------------------------------------------- -- createProcess @@ -548,15 +544,11 @@ withForkWait async body = do restore (body wait) `C.onException` killThread tid ignoreSigPipe :: IO () -> IO () -#if defined(__GLASGOW_HASKELL__) ignoreSigPipe = C.handle $ \e -> case e of IOError { ioe_type = ResourceVanished , ioe_errno = Just ioe } | Errno ioe == ePIPE -> return () _ -> throwIO e -#else -ignoreSigPipe = id -#endif -- ---------------------------------------------------------------------------- -- showCommandForUser @@ -860,13 +852,11 @@ will not work. On Unix systems, see 'waitForProcess' for the meaning of exit codes when the process died as the result of a signal. -} -#ifdef __GLASGOW_HASKELL__ system :: String -> IO ExitCode system "" = ioException (ioeSetErrorString (mkIOError InvalidArgument "system" Nothing Nothing) "null command") system str = do (_,_,_,p) <- createProcess_ "system" (shell str) { delegate_ctlc = True } waitForProcess p -#endif /* __GLASGOW_HASKELL__ */ --TODO: in a later release {-# DEPRECATED rawSystem "Use 'callProcess' (or 'spawnProcess' and 'waitForProcess') instead" #-} @@ -880,11 +870,6 @@ It will therefore behave more portably between operating systems than 'system'. The return codes and possible failures are the same as for 'system'. -} rawSystem :: String -> [String] -> IO ExitCode -#ifdef __GLASGOW_HASKELL__ rawSystem cmd args = do (_,_,_,p) <- createProcess_ "rawSystem" (proc cmd args) { delegate_ctlc = True } waitForProcess p -#else --- crude fallback implementation: could do much better than this under Unix -rawSystem cmd args = system (showCommandForUser cmd args) -#endif diff --git a/System/Process/Internals.hs b/System/Process/Internals.hs index 69ecd2b..ef8ff8f 100644 --- a/System/Process/Internals.hs +++ b/System/Process/Internals.hs @@ -1,9 +1,7 @@ {-# LANGUAGE CPP #-} {-# OPTIONS_HADDOCK not-home #-} -#ifdef __GLASGOW_HASKELL__ {-# LANGUAGE Trustworthy #-} {-# LANGUAGE InterruptibleFFI #-} -#endif ----------------------------------------------------------------------------- -- | @@ -25,13 +23,11 @@ module System.Process.Internals ( ProcessHandle(..), ProcessHandle__(..), PHANDLE, closePHANDLE, mkProcessHandle, modifyProcessHandle, withProcessHandle, -#ifdef __GLASGOW_HASKELL__ CreateProcess(..), CmdSpec(..), StdStream(..), createProcess_, runGenProcess_, --deprecated fdToHandle, -#endif startDelegateControlC, endDelegateControlC, stopDelegateControlC, @@ -48,9 +44,7 @@ module System.Process.Internals ( import Foreign.C import System.IO -#ifdef __GLASGOW_HASKELL__ import GHC.IO.Handle.FD (fdToHandle) -#endif import System.Process.Common @@ -145,7 +139,6 @@ translate = translateInternal -- ---------------------------------------------------------------------------- -- Deprecated / compat -#ifdef __GLASGOW_HASKELL__ {-# DEPRECATED runGenProcess_ "Please do not use this anymore, use the ordinary 'System.Process.createProcess'. If you need the SIGINT handling, use delegate_ctlc = True (runGenProcess_ is now just an imperfectly emulated stub that probably duplicates or overrides your own signal handling)." #-} runGenProcess_ @@ -159,8 +152,6 @@ runGenProcess_ fun c (Just sig) (Just sig') | isDefaultSignal sig && sig == sig' = createProcess_ fun c { delegate_ctlc = True } runGenProcess_ fun c _ _ = createProcess_ fun c -#endif - -- --------------------------------------------------------------------------- -- createPipe diff --git a/System/Process/Posix.hs b/System/Process/Posix.hs index a68d942..6129197 100644 --- a/System/Process/Posix.hs +++ b/System/Process/Posix.hs @@ -93,8 +93,6 @@ withCEnvironment envir act = let env' = map (\(name, val) -> name ++ ('=':val)) envir in withMany withCString env' (\pEnv -> withArray0 nullPtr pEnv act) -#ifdef __GLASGOW_HASKELL__ - -- ----------------------------------------------------------------------------- -- POSIX runProcess with signal handling in the child @@ -267,8 +265,6 @@ foreign import ccall unsafe "runInteractiveProcess" -> Ptr CString -> IO PHANDLE -#endif /* __GLASGOW_HASKELL__ */ - ignoreSignal, defaultSignal :: CLong ignoreSignal = CONST_SIG_IGN defaultSignal = CONST_SIG_DFL diff --git a/process.cabal b/process.cabal index ee79452..0b4ffd7 100644 --- a/process.cabal +++ b/process.cabal @@ -44,14 +44,16 @@ library exposed-modules: System.Cmd System.Process - if impl(ghc) - exposed-modules: - System.Process.Internals - other-modules: System.Process.Common - if os(windows) - other-modules: System.Process.Windows - else - other-modules: System.Process.Posix + System.Process.Internals + other-modules: System.Process.Common + if os(windows) + other-modules: System.Process.Windows + build-depends: Win32 >=2.2 && < 2.4 + extra-libraries: kernel32 + cpp-options: -DWINDOWS + else + other-modules: System.Process.Posix + build-depends: unix >= 2.5 && < 2.8 c-sources: cbits/runProcess.c @@ -68,12 +70,6 @@ library directory >= 1.1 && < 1.3, filepath >= 1.2 && < 1.5, deepseq >= 1.1 && < 1.5 - if os(windows) - build-depends: Win32 >=2.2 && < 2.4 - extra-libraries: kernel32 - cpp-options: -DWINDOWS - else - build-depends: unix >= 2.5 && < 2.8 test-suite test default-language: Haskell2010 From git at git.haskell.org Tue Dec 15 13:34:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 13:34:55 +0000 (UTC) Subject: [commit: packages/process] less-cpp, master: Another shot at appveyor (88a63dd) Message-ID: <20151215133455.2C7653A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: less-cpp,master Link : http://ghc.haskell.org/trac/ghc/changeset/88a63dd1ee821471654ff008a804b0c518af8941/process >--------------------------------------------------------------- commit 88a63dd1ee821471654ff008a804b0c518af8941 Author: Michael Snoyman Date: Mon Nov 2 23:27:35 2015 +0000 Another shot at appveyor >--------------------------------------------------------------- 88a63dd1ee821471654ff008a804b0c518af8941 appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index 0db89ce..91ade29 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -16,5 +16,5 @@ test_script: - stack setup > nul # The ugly echo "" hack is to avoid complaints about 0 being an invalid file # descriptor -- echo "y" | stack exec -- sh -c "pacman -Sy autoconf && autoreconf -i" +- echo y | stack exec -- sh -c "pacman -Sy autoconf && autoreconf -i" - echo "" | stack --no-terminal test --pedantic From git at git.haskell.org Tue Dec 15 13:34:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 13:34:57 +0000 (UTC) Subject: [commit: packages/process] less-cpp, master: appveyor: install perl (3c73538) Message-ID: <20151215133457.322CA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: less-cpp,master Link : http://ghc.haskell.org/trac/ghc/changeset/3c73538d48ea6ca2b988dbd74290893019fb9318/process >--------------------------------------------------------------- commit 3c73538d48ea6ca2b988dbd74290893019fb9318 Author: Michael Snoyman Date: Mon Nov 2 23:52:51 2015 +0000 appveyor: install perl >--------------------------------------------------------------- 3c73538d48ea6ca2b988dbd74290893019fb9318 appveyor.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/appveyor.yml b/appveyor.yml index 91ade29..2c313d4 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -16,5 +16,5 @@ test_script: - stack setup > nul # The ugly echo "" hack is to avoid complaints about 0 being an invalid file # descriptor -- echo y | stack exec -- sh -c "pacman -Sy autoconf && autoreconf -i" +- echo y | stack exec -- sh -c "pacman -Sy autoconf perl && autoreconf -i" - echo "" | stack --no-terminal test --pedantic From git at git.haskell.org Tue Dec 15 13:34:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 13:34:59 +0000 (UTC) Subject: [commit: packages/process] less-cpp, master: Add appveyor badge (9dae7ad) Message-ID: <20151215133459.3900F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branches: less-cpp,master Link : http://ghc.haskell.org/trac/ghc/changeset/9dae7ad1b5688723f129cd9eb2b2b82f7f2f6ec4/process >--------------------------------------------------------------- commit 9dae7ad1b5688723f129cd9eb2b2b82f7f2f6ec4 Author: Michael Snoyman Date: Tue Nov 3 16:56:24 2015 +0000 Add appveyor badge >--------------------------------------------------------------- 9dae7ad1b5688723f129cd9eb2b2b82f7f2f6ec4 README.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/README.md b/README.md index f0698ea..0244c4e 100644 --- a/README.md +++ b/README.md @@ -1,4 +1,4 @@ -The `process` Package [![Hackage](https://img.shields.io/hackage/v/process.svg)](https://hackage.haskell.org/package/process) [![Build Status](https://travis-ci.org/haskell/process.svg)](https://travis-ci.org/haskell/process) +The `process` Package [![Hackage](https://img.shields.io/hackage/v/process.svg)](https://hackage.haskell.org/package/process) [![Build Status](https://travis-ci.org/haskell/process.svg)](https://travis-ci.org/haskell/process) [![Windows build status](https://ci.appveyor.com/api/projects/status/0o4c3w99frtxyrht?svg=true)](https://ci.appveyor.com/project/snoyberg/process) ===================== See [`process` on Hackage](http://hackage.haskell.org/package/process) for From git at git.haskell.org Tue Dec 15 13:35:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 13:35:01 +0000 (UTC) Subject: [commit: packages/process] master: Merge pull request #47 from haskell/less-cpp (e5a7ee3) Message-ID: <20151215133501.428323A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e5a7ee3189028d12a57391388184f20d0d257c08/process >--------------------------------------------------------------- commit e5a7ee3189028d12a57391388184f20d0d257c08 Merge: 7428b61 9dae7ad Author: Michael Snoyman Date: Tue Nov 17 05:28:35 2015 +0200 Merge pull request #47 from haskell/less-cpp Use less CPP >--------------------------------------------------------------- e5a7ee3189028d12a57391388184f20d0d257c08 .gitignore | 1 + .travis.yml | 2 +- README.md | 2 +- System/Process.hsc | 100 +------ System/Process/Common.hs | 215 ++++++++++++++ System/Process/Internals.hs | 695 +++----------------------------------------- System/Process/Posix.hs | 291 +++++++++++++++++++ System/Process/Windows.hsc | 283 ++++++++++++++++++ appveyor.yml | 20 ++ process.cabal | 18 +- 10 files changed, 867 insertions(+), 760 deletions(-) From git at git.haskell.org Tue Dec 15 13:35:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 13:35:03 +0000 (UTC) Subject: [commit: packages/process] master: Version bump (0edb978) Message-ID: <20151215133503.495683A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0edb97876c2f783b33f9a69089ca9d26a061e112/process >--------------------------------------------------------------- commit 0edb97876c2f783b33f9a69089ca9d26a061e112 Author: Michael Snoyman Date: Tue Nov 17 15:34:47 2015 +0200 Version bump >--------------------------------------------------------------- 0edb97876c2f783b33f9a69089ca9d26a061e112 changelog.md | 6 ++++++ process.cabal | 2 +- 2 files changed, 7 insertions(+), 1 deletion(-) diff --git a/changelog.md b/changelog.md index 6507bf8..b01b324 100644 --- a/changelog.md +++ b/changelog.md @@ -1,5 +1,11 @@ # Changelog for [`process` package](http://hackage.haskell.org/package/process) +## 1.4.1.0 *November 2015* + +* Use less CPP [#47](https://github.com/haskell/process/pull/47) + * Refactor to have separate Windows and POSIX modules internally + * Remove the broken non-GHC code paths + ## 1.4.0.0 *November 2015* * Added `child_user` and `child_group` to `CreateProcess` for unix. [#45](https://github.com/haskell/process/pull/45) diff --git a/process.cabal b/process.cabal index 0b4ffd7..ee69285 100644 --- a/process.cabal +++ b/process.cabal @@ -1,5 +1,5 @@ name: process -version: 1.4.0.0 +version: 1.4.1.0 -- NOTE: Don't forget to update ./changelog.md license: BSD3 license-file: LICENSE From git at git.haskell.org Tue Dec 15 13:35:05 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 13:35:05 +0000 (UTC) Subject: [commit: packages/process] master: Remove obsolete `--with-cc` flag from configure.ac (e594712) Message-ID: <20151215133505.4EB093A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e594712a8fe49c94ff43ab016739e0fa63f0de00/process >--------------------------------------------------------------- commit e594712a8fe49c94ff43ab016739e0fa63f0de00 Author: Herbert Valerio Riedel Date: Mon Dec 14 07:40:56 2015 +0100 Remove obsolete `--with-cc` flag from configure.ac This non-standard flag was used previously by GHC's build-system to set the `CC` variable. See https://phabricator.haskell.org/D1608 for more details >--------------------------------------------------------------- e594712a8fe49c94ff43ab016739e0fa63f0de00 configure.ac | 5 +---- 1 file changed, 1 insertion(+), 4 deletions(-) diff --git a/configure.ac b/configure.ac index 5f0731d..7599986 100644 --- a/configure.ac +++ b/configure.ac @@ -5,10 +5,7 @@ AC_CONFIG_SRCDIR([include/runProcess.h]) AC_CONFIG_HEADERS([include/HsProcessConfig.h]) -AC_ARG_WITH([cc], - [C compiler], - [CC=$withval]) -AC_PROG_CC() +AC_PROG_CC dnl ** Working vfork? AC_FUNC_FORK From git at git.haskell.org Tue Dec 15 13:40:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 13:40:13 +0000 (UTC) Subject: [commit: ghc] master: Reset process submodule to v1.4.1.0 release tag (f4d90f9) Message-ID: <20151215134013.4768B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f4d90f96433ae7cc4f7d4051e5adc1b9d739a523/ghc >--------------------------------------------------------------- commit f4d90f96433ae7cc4f7d4051e5adc1b9d739a523 Author: Herbert Valerio Riedel Date: Tue Dec 15 14:37:55 2015 +0100 Reset process submodule to v1.4.1.0 release tag The `process-1.4.1.0` release is the version designated for GHC 8.0.1 /cc @snoyberg >--------------------------------------------------------------- f4d90f96433ae7cc4f7d4051e5adc1b9d739a523 libraries/process | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/process b/libraries/process index e594712..0edb978 160000 --- a/libraries/process +++ b/libraries/process @@ -1 +1 @@ -Subproject commit e594712a8fe49c94ff43ab016739e0fa63f0de00 +Subproject commit 0edb97876c2f783b33f9a69089ca9d26a061e112 From git at git.haskell.org Tue Dec 15 14:33:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 14:33:38 +0000 (UTC) Subject: [commit: ghc] master: Allow recursive (undecidable) superclasses (6eabb6d) Message-ID: <20151215143338.7E9A63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6eabb6ddb7c53784792ee26b1e0657bde7eee7fb/ghc >--------------------------------------------------------------- commit 6eabb6ddb7c53784792ee26b1e0657bde7eee7fb Author: Simon Peyton Jones Date: Tue Dec 15 14:26:13 2015 +0000 Allow recursive (undecidable) superclasses This patch fulfils the request in Trac #11067, #10318, and #10592, by lifting the conservative restrictions on superclass constraints. These restrictions are there (and have been since Haskell was born) to ensure that the transitive superclasses of a class constraint is a finite set. However (a) this restriction is conservative, and can be annoying when there really is no recursion, and (b) sometimes genuinely recursive superclasses are useful (see the tickets). Dimitrios and I worked out that there is actually a relatively simple way to do the job. It?s described in some detail in Note [The superclass story] in TcCanonical Note [Expanding superclasses] in TcType In brief, the idea is to expand superclasses only finitely, but to iterate (using a loop that already existed) if there are more superclasses to explore. Other small things - I improved grouping of error messages a bit in TcErrors - I re-centred the haddock.compiler test, which was at 9.8% above the norm, and which this patch pushed slightly over >--------------------------------------------------------------- 6eabb6ddb7c53784792ee26b1e0657bde7eee7fb compiler/main/DynFlags.hs | 2 + compiler/typecheck/TcCanonical.hs | 256 ++++++++++++++------- compiler/typecheck/TcErrors.hs | 84 +++++-- compiler/typecheck/TcInteract.hs | 18 +- compiler/typecheck/TcRnTypes.hs | 18 +- compiler/typecheck/TcSMonad.hs | 37 ++- compiler/typecheck/TcSimplify.hs | 113 ++++++--- compiler/typecheck/TcTyClsDecls.hs | 21 +- compiler/typecheck/TcTyDecls.hs | 207 ++++++++--------- compiler/typecheck/TcType.hs | 90 ++++++-- compiler/utils/Bag.hs | 16 +- docs/users_guide/glasgow_exts.rst | 49 ++++ libraries/ghc-prim/GHC/Classes.hs | 2 + testsuite/tests/ado/ado004.stderr | 10 +- testsuite/tests/driver/T4437.hs | 1 + testsuite/tests/ghci/scripts/ghci013.stdout | 2 +- .../tests/indexed-types/should_compile/T10318.hs | 35 +++ .../tests/indexed-types/should_compile/T11067.hs | 35 +++ .../indexed-types/should_compile/T3017.stderr | 2 +- .../indexed-types/should_compile/T3208b.stderr | 10 - .../indexed-types/should_compile/T8889.stderr | 4 +- testsuite/tests/indexed-types/should_compile/all.T | 2 + .../tests/indexed-types/should_fail/T1897b.stderr | 22 +- .../tests/indexed-types/should_fail/T3330a.stderr | 22 +- .../tests/indexed-types/should_fail/T4174.stderr | 16 -- .../tests/indexed-types/should_fail/T8227.stderr | 35 +-- .../tests/indexed-types/should_fail/T9662.stderr | 80 +------ testsuite/tests/module/mod40.stderr | 18 +- .../should_compile/ExtraConstraints1.stderr | 6 +- .../should_compile/ExtraConstraints3.stderr | 38 +-- .../WarningWildcardInstantiations.stderr | 2 +- .../InstantiatedNamedWildcardsInConstraints.stderr | 2 +- .../tests/partial-sigs/should_fail/T10999.stderr | 6 +- .../should_fail/WildcardInstantiations.stderr | 2 +- testsuite/tests/perf/haddock/all.T | 3 +- testsuite/tests/pmcheck/should_compile/T3927b.hs | 1 + testsuite/tests/polykinds/T7332.hs | 30 ++- testsuite/tests/polykinds/T7594.hs | 2 + testsuite/tests/polykinds/T7594.stderr | 27 +-- testsuite/tests/polykinds/T9017.stderr | 13 -- .../tests/simplCore/should_compile/T4398.stderr | 2 +- testsuite/tests/typecheck/should_compile/T10100.hs | 1 + testsuite/tests/typecheck/should_compile/T10109.hs | 1 + testsuite/tests/typecheck/should_compile/T10564.hs | 1 + .../tests/typecheck/should_compile/T9834.stderr | 45 +--- testsuite/tests/typecheck/should_compile/tc256.hs | 2 +- testsuite/tests/typecheck/should_fail/T2714.stderr | 35 +-- testsuite/tests/typecheck/should_fail/T5853.stderr | 22 +- testsuite/tests/typecheck/should_fail/T7869.stderr | 43 ++-- testsuite/tests/typecheck/should_fail/T8883.stderr | 12 +- testsuite/tests/typecheck/should_fail/T9415.stderr | 18 +- testsuite/tests/typecheck/should_fail/T9739.stderr | 20 +- .../tests/typecheck/should_fail/tcfail027.stderr | 18 +- testsuite/tests/typecheck/should_fail/tcfail216.hs | 1 - .../tests/typecheck/should_fail/tcfail216.stderr | 9 +- testsuite/tests/typecheck/should_fail/tcfail217.hs | 2 +- .../tests/typecheck/should_fail/tcfail217.stderr | 6 +- 57 files changed, 895 insertions(+), 682 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 6eabb6ddb7c53784792ee26b1e0657bde7eee7fb From git at git.haskell.org Tue Dec 15 14:33:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 14:33:41 +0000 (UTC) Subject: [commit: ghc] master: Comments on equality types and classes (b8ca645) Message-ID: <20151215143341.37C8E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b8ca64592e331005def4f734e026d5418950e6e1/ghc >--------------------------------------------------------------- commit b8ca64592e331005def4f734e026d5418950e6e1 Author: Simon Peyton Jones Date: Tue Dec 15 14:22:37 2015 +0000 Comments on equality types and classes This is really just doucumenting one aspect of the kind-equality patch. See especially Note [Equality types and classes] in TysWiredIn. Other places should just point to this Note. Richard please check for veracity. >--------------------------------------------------------------- b8ca64592e331005def4f734e026d5418950e6e1 compiler/prelude/TysPrim.hs | 57 ++++++++++++++++++++---------------- compiler/prelude/TysWiredIn.hs | 50 ++++++++++++++++++++++++++++--- libraries/base/Data/Type/Equality.hs | 20 +++++++++---- libraries/ghc-prim/GHC/Types.hs | 6 ++-- 4 files changed, 96 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 b8ca64592e331005def4f734e026d5418950e6e1 From git at git.haskell.org Tue Dec 15 14:33:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 14:33:43 +0000 (UTC) Subject: [commit: ghc] master: Fix formatting complaint from Sphinx (d1ca5d2) Message-ID: <20151215143343.E4AB63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d1ca5d215591a89dbfba7b87887b1197d03f567f/ghc >--------------------------------------------------------------- commit d1ca5d215591a89dbfba7b87887b1197d03f567f Author: Simon Peyton Jones Date: Tue Dec 15 14:19:12 2015 +0000 Fix formatting complaint from Sphinx >--------------------------------------------------------------- d1ca5d215591a89dbfba7b87887b1197d03f567f docs/users_guide/glasgow_exts.rst | 2 ++ 1 file changed, 2 insertions(+) diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index b9ad620..853397a 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -8238,6 +8238,7 @@ the source location of the call to the ``CallStack`` in the environment. For example :: + myerror :: (?callStack :: CallStack) => String -> a myerror msg = error (msg ++ "\n" ++ prettyCallStack ?callStack) @@ -8254,6 +8255,7 @@ The ``CallStack`` will only extend as far as the types allow it, for example :: + head :: (?callStack :: CallStack) => [a] -> a head [] = myerror "empty" head (x:xs) = x From git at git.haskell.org Tue Dec 15 14:33:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 14:33:46 +0000 (UTC) Subject: [commit: ghc] master: Improve documentation for -XStrict (98cdaee) Message-ID: <20151215143346.93B133A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/98cdaee73038094eea25d994f1fd0828b3c8dd0e/ghc >--------------------------------------------------------------- commit 98cdaee73038094eea25d994f1fd0828b3c8dd0e Author: Simon Peyton Jones Date: Tue Dec 15 14:19:52 2015 +0000 Improve documentation for -XStrict In particular, highlight that we do not put bangs on nested patterns >--------------------------------------------------------------- 98cdaee73038094eea25d994f1fd0828b3c8dd0e docs/users_guide/glasgow_exts.rst | 55 +++++++++++++++++++++++++-------------- 1 file changed, 36 insertions(+), 19 deletions(-) diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index 853397a..566ecda 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -12917,27 +12917,17 @@ optionally had by adding ``!`` in front of a variable. let !pat = ... Adding ``~`` in front of ``x`` gives the regular lazy - behavior. Notice that we do not put bangs on nested patterns. For - example :: - - let (p,q) = if flob then (undefined, undefined) else (True, False) - in ... - - will behave like :: - - let !(p,q) = if flob then (undefined, undefined) else (True,False) - in ... + behavior. + The general rule is that we add an implicit bang on the outermost pattern, + unless disabled with ``~``. - which will strictly evaluate the right hand side, and bind ``p`` - and ``q`` to the components of the pair. But the pair itself is - lazy (unless we also compile the ``Prelude`` with ``Strict``; see - :ref:`strict-modularity` below). So ``p`` and ``q`` may end up bound to - undefined. See also :ref:`recursive-and-polymorphic-let-bindings` below. +- **Pattern matching in case expressions, lambdas, do-notation, etc** -- **Case expressions.** - - The patterns of a case expression get an implicit bang, unless - disabled with ``~``. For example :: + The outermost pattern of all pattern matches gets an implicit bang, + unless disabled with ``~``. + This applies to case expressions, patterns in lambda, do-notation, + list comprehension, and so on. + For example :: case x of (a,b) -> rhs @@ -12962,6 +12952,33 @@ optionally had by adding ``!`` in front of a variable. is lazy in Haskell; but with ``Strict`` the added bang makes it strict. + Similarly :: + + \ x -> body + do { x <- rhs; blah } + [ e | x <- rhs; blah } + + all get implicit bangs on the ``x`` pattern. + +- ** Nested patterns ** + + Notice that we do *not* put bangs on nested patterns. For + example :: + + let (p,q) = if flob then (undefined, undefined) else (True, False) + in ... + + will behave like :: + + let !(p,q) = if flob then (undefined, undefined) else (True,False) + in ... + + which will strictly evaluate the right hand side, and bind ``p`` + and ``q`` to the components of the pair. But the pair itself is + lazy (unless we also compile the ``Prelude`` with ``Strict``; see + :ref:`strict-modularity` below). So ``p`` and ``q`` may end up bound to + undefined. See also :ref:`recursive-and-polymorphic-let-bindings` below. + - **Top level bindings.** are unaffected by ``Strict``. For example: :: From git at git.haskell.org Tue Dec 15 14:33:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 14:33:49 +0000 (UTC) Subject: [commit: ghc] master: Comment layout only (947e44f) Message-ID: <20151215143349.54CCF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/947e44feebb4e979d7d476ff2aa5c7054a1c0899/ghc >--------------------------------------------------------------- commit 947e44feebb4e979d7d476ff2aa5c7054a1c0899 Author: Simon Peyton Jones Date: Tue Dec 15 14:26:34 2015 +0000 Comment layout only >--------------------------------------------------------------- 947e44feebb4e979d7d476ff2aa5c7054a1c0899 compiler/deSugar/DsUtils.hs | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/compiler/deSugar/DsUtils.hs b/compiler/deSugar/DsUtils.hs index 053fc13..6d47af3 100644 --- a/compiler/deSugar/DsUtils.hs +++ b/compiler/deSugar/DsUtils.hs @@ -871,11 +871,11 @@ mkBinaryTickBox ixT ixF e = do -- also make irrefutable patterns ordinary patterns if -XStrict. -- -- Example: --- ~pat => False, pat -- when -XStrict --- ~pat => False, ~pat -- without -XStrict --- ~(~pat) => False, ~pat -- when -XStrict --- pat => True, pat -- when -XStrict --- !pat => True, pat -- always +-- ~pat => False, pat -- when -XStrict +-- ~pat => False, ~pat -- without -XStrict +-- ~(~pat) => False, ~pat -- when -XStrict +-- pat => True, pat -- when -XStrict +-- !pat => True, pat -- always getUnBangedLPat :: DynFlags -> LPat id -- ^ Original pattern -> (Bool, LPat id) -- is bind strict?, pattern without bangs From git at git.haskell.org Tue Dec 15 20:06:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 20:06:01 +0000 (UTC) Subject: [commit: packages/array] master: Update testsuite for D1617 (f643793) Message-ID: <20151215200601.C1DDA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/array On branch : master Link : http://git.haskell.org/packages/array.git/commitdiff/f643793b3fbffd7419f403bedc65b7ac06dff0cd >--------------------------------------------------------------- commit f643793b3fbffd7419f403bedc65b7ac06dff0cd Author: Ben Gamari Date: Tue Dec 15 14:01:30 2015 -0500 Update testsuite for D1617 >--------------------------------------------------------------- f643793b3fbffd7419f403bedc65b7ac06dff0cd tests/T9220.stdout | 17 ++++++++++------- 1 file changed, 10 insertions(+), 7 deletions(-) diff --git a/tests/T9220.stdout b/tests/T9220.stdout index 41287b1..71582f2 100644 --- a/tests/T9220.stdout +++ b/tests/T9220.stdout @@ -1,23 +1,26 @@ type role Data.Array.Base.UArray nominal nominal data Data.Array.Base.UArray i e - = Data.Array.Base.UArray !i !i {-# UNPACK #-}Int ByteArray# + = Data.Array.Base.UArray !i + !i + {-# UNPACK #-}Int + GHC.Prim.ByteArray# -- Defined in ?Data.Array.Base? -instance (Ix ix, Eq e, +instance (GHC.Arr.Ix ix, Eq e, Data.Array.Base.IArray Data.Array.Base.UArray e) => Eq (Data.Array.Base.UArray ix e) -- Defined in ?Data.Array.Base? -instance (Ix ix, Ord e, +instance (GHC.Arr.Ix ix, Ord e, Data.Array.Base.IArray Data.Array.Base.UArray e) => Ord (Data.Array.Base.UArray ix e) -- Defined in ?Data.Array.Base? -instance (Ix ix, Show ix, Show e, +instance (GHC.Arr.Ix ix, Show ix, Show e, Data.Array.Base.IArray Data.Array.Base.UArray e) => Show (Data.Array.Base.UArray ix e) -- Defined in ?Data.Array.Base? type role Data.Array.IO.Internals.IOUArray nominal nominal newtype Data.Array.IO.Internals.IOUArray i e = Data.Array.IO.Internals.IOUArray (Data.Array.Base.STUArray - RealWorld i e) + GHC.Prim.RealWorld i e) -- Defined in ?Data.Array.IO.Internals? instance Eq (Data.Array.IO.Internals.IOUArray i e) -- Defined in ?Data.Array.IO.Internals? @@ -26,7 +29,7 @@ data Data.Array.Base.STUArray s i e = Data.Array.Base.STUArray !i !i {-# UNPACK #-}Int - (MutableByteArray# s) + (GHC.Prim.MutableByteArray# s) -- Defined in ?Data.Array.Base? instance Eq (Data.Array.Base.STUArray s i e) -- Defined in ?Data.Array.Base? @@ -35,5 +38,5 @@ data Data.Array.Storable.Internals.StorableArray i e = Data.Array.Storable.Internals.StorableArray !i !i Int - !(ForeignPtr e) + !(GHC.ForeignPtr.ForeignPtr e) -- Defined in ?Data.Array.Storable.Internals? From git at git.haskell.org Tue Dec 15 20:06:22 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 20:06:22 +0000 (UTC) Subject: [commit: ghc] master: Narrow scope of special-case for unqualified printing of names in core libraries (e2c9173) Message-ID: <20151215200622.130A53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e2c917381ff099820b1ee30fcfa8bc0c20cf5c1f/ghc >--------------------------------------------------------------- commit e2c917381ff099820b1ee30fcfa8bc0c20cf5c1f Author: Ben Gamari Date: Tue Dec 15 16:08:52 2015 +0100 Narrow scope of special-case for unqualified printing of names in core libraries Commit 547c597112954353cef7157cb0a389bc4f6303eb modifies the pretty-printer to render names from a set of core packages (`base`, `ghc-prim`, `template-haskell`) as unqualified. The idea here was that many of these names typically are not in scope but are well-known by the user and therefore qualification merely introduces noise. This, however, is a very large hammer and potentially breaks any consumer who relies on parsing GHC output (hence #11208). This commit partially reverts this change, now only printing `Constraint` (which appears quite often in errors) as unqualified. Fixes #11208. Updates tests in `array` submodule. Test Plan: validate Reviewers: hvr, thomie, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1619 GHC Trac Issues: #11208 >--------------------------------------------------------------- e2c917381ff099820b1ee30fcfa8bc0c20cf5c1f compiler/main/HscTypes.hs | 42 ++++--- compiler/prelude/TysWiredIn.hs | 3 +- libraries/array | 2 +- .../tests/annotations/should_fail/annfail05.stderr | 7 +- .../tests/annotations/should_fail/annfail08.stderr | 13 ++- .../tests/annotations/should_fail/annfail10.stderr | 49 ++++---- .../tests/deSugar/should_compile/T2431.stderr | 33 +++--- testsuite/tests/deriving/should_fail/T4846.stderr | 19 ++-- testsuite/tests/ghc-api/annotations/T10268.stderr | 3 +- .../tests/ghci.debugger/scripts/break006.stderr | 56 +++++---- .../tests/ghci.debugger/scripts/break024.stdout | 9 +- .../tests/ghci.debugger/scripts/print019.stderr | 23 ++-- .../tests/ghci.debugger/scripts/print028.stdout | 7 +- .../tests/ghci.debugger/scripts/print033.stdout | 3 +- testsuite/tests/ghci/scripts/T11208.hs | 8 ++ testsuite/tests/ghci/scripts/T11208.script | 2 + testsuite/tests/ghci/scripts/T11208.stdout | 2 + testsuite/tests/ghci/scripts/T2182ghci2.stderr | 14 ++- testsuite/tests/ghci/scripts/T7873.stdout | 4 +- testsuite/tests/ghci/scripts/T8469.stdout | 2 +- testsuite/tests/ghci/scripts/T8959.stdout | 8 +- testsuite/tests/ghci/scripts/T9181.stdout | 105 ++++++++++------- testsuite/tests/ghci/scripts/T9881.stdout | 3 +- testsuite/tests/ghci/scripts/ghci008.stdout | 12 +- testsuite/tests/ghci/scripts/ghci013.stdout | 3 +- testsuite/tests/ghci/scripts/ghci019.stderr | 8 +- testsuite/tests/ghci/scripts/ghci019.stdout | 2 +- testsuite/tests/ghci/scripts/ghci023.stdout | 16 +-- testsuite/tests/ghci/scripts/ghci025.stdout | 26 +++-- testsuite/tests/ghci/scripts/ghci027.stdout | 8 +- testsuite/tests/ghci/scripts/ghci046.stdout | 4 +- testsuite/tests/ghci/scripts/ghci055.stdout | 2 +- testsuite/tests/module/mod87.stderr | 6 +- testsuite/tests/module/mod97.stderr | 7 +- .../tests/numeric/should_compile/T7116.stdout | 37 ++++-- .../should_fail/overloadedlistsfail01.stderr | 67 +++++------ .../should_fail/overloadedlistsfail02.stderr | 20 ++-- .../ghci/overloadedlabelsghci01.stdout | 2 +- .../should_compile/ExtraConstraints3.stderr | 52 +++++---- .../tests/partial-sigs/should_fail/T10999.stderr | 7 +- testsuite/tests/quotes/TH_localname.stderr | 50 ++++---- testsuite/tests/rebindable/rebindable6.stderr | 126 ++++++++++----------- .../should_fail/RnStaticPointersFail02.stderr | 7 +- testsuite/tests/roles/should_compile/Roles1.stderr | 60 +++++++--- .../tests/roles/should_compile/Roles13.stderr | 44 +++---- .../tests/roles/should_compile/Roles14.stderr | 11 +- testsuite/tests/roles/should_compile/Roles2.stderr | 20 +++- testsuite/tests/roles/should_compile/Roles3.stderr | 36 ++++-- testsuite/tests/roles/should_compile/Roles4.stderr | 20 +++- testsuite/tests/roles/should_compile/T8958.stderr | 24 ++-- .../tests/simplCore/should_compile/T3717.stderr | 28 ++--- .../tests/simplCore/should_compile/T3772.stdout | 28 ++--- .../tests/simplCore/should_compile/T4908.stderr | 17 +-- .../tests/simplCore/should_compile/T4930.stderr | 38 ++++--- .../tests/simplCore/should_compile/T5366.stdout | 2 +- .../tests/simplCore/should_compile/T7360.stderr | 71 +++++++----- .../tests/simplCore/should_compile/T7865.stdout | 4 +- .../tests/simplCore/should_compile/T8274.stdout | 20 ++-- .../tests/simplCore/should_compile/T8832.stdout | 20 ++-- .../simplCore/should_compile/T8832.stdout-ws-32 | 16 +-- .../tests/simplCore/should_compile/T9400.stderr | 9 +- .../simplCore/should_compile/spec-inline.stderr | 101 ++++++++++------- testsuite/tests/stranal/should_compile/Makefile | 6 +- .../tests/stranal/should_compile/T10482.stdout | 2 +- .../tests/stranal/should_compile/T10482a.stdout | 8 +- testsuite/tests/th/T3319.stderr | 2 +- testsuite/tests/th/T5700.stderr | 2 +- testsuite/tests/th/T7276.stderr | 13 ++- testsuite/tests/th/TH_Roles2.stderr | 9 +- testsuite/tests/th/TH_foreignInterruptible.stderr | 3 +- .../tests/typecheck/should_compile/holes2.stderr | 35 +++--- .../tests/typecheck/should_fail/T10971b.stderr | 124 ++++++++++---------- testsuite/tests/typecheck/should_fail/T5095.stderr | 28 ++--- testsuite/tests/typecheck/should_fail/T8262.stderr | 2 +- .../typecheck/should_fail/TcCoercibleFail.stderr | 3 +- .../should_fail/TcStaticPointersFail02.stderr | 20 ++-- .../tests/typecheck/should_fail/tcfail068.stderr | 28 ++--- .../tests/typecheck/should_fail/tcfail072.stderr | 32 +++--- .../tests/typecheck/should_fail/tcfail123.stderr | 10 +- .../tests/typecheck/should_fail/tcfail128.stderr | 40 +++---- .../tests/typecheck/should_fail/tcfail133.stderr | 42 +++---- .../tests/typecheck/should_fail/tcfail200.stderr | 2 +- .../tests/typecheck/should_fail/tcfail220.stderr | 2 +- testsuite/tests/typecheck/should_run/T8119.stdout | 2 +- .../wcompat-warnings/WCompatWarningsOn.stderr | 6 +- 85 files changed, 1055 insertions(+), 814 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc e2c917381ff099820b1ee30fcfa8bc0c20cf5c1f From git at git.haskell.org Tue Dec 15 20:50:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 20:50:31 +0000 (UTC) Subject: [commit: ghc] master: base: NonEmpty: Fix documentation example (758e6b3) Message-ID: <20151215205031.E5DD23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/758e6b3a935242acacfa5f1c23ecd1b0e9310e28/ghc >--------------------------------------------------------------- commit 758e6b3a935242acacfa5f1c23ecd1b0e9310e28 Author: Ben Gamari Date: Tue Dec 15 21:50:36 2015 +0100 base: NonEmpty: Fix documentation example Fixes #11178. >--------------------------------------------------------------- 758e6b3a935242acacfa5f1c23ecd1b0e9310e28 libraries/base/Data/List/NonEmpty.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/base/Data/List/NonEmpty.hs b/libraries/base/Data/List/NonEmpty.hs index a66ea8f..1553836 100644 --- a/libraries/base/Data/List/NonEmpty.hs +++ b/libraries/base/Data/List/NonEmpty.hs @@ -313,7 +313,7 @@ iterate f a = a :| List.iterate f (f a) -- | @'cycle' xs@ returns the infinite repetition of @xs@: -- --- > cycle [1,2,3] = 1 :| [2,3,1,2,3,...] +-- > cycle (1 :| [2,3]) = 1 :| [2,3,1,2,3,...] cycle :: NonEmpty a -> NonEmpty a cycle = fromList . List.cycle . toList From git at git.haskell.org Tue Dec 15 20:51:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 20:51:43 +0000 (UTC) Subject: [commit: ghc] master: Add testcase for #11224 (a701694) Message-ID: <20151215205143.288FB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a701694b27143d094f9de0a78757bbdeaa07daa6/ghc >--------------------------------------------------------------- commit a701694b27143d094f9de0a78757bbdeaa07daa6 Author: Ben Gamari Date: Tue Dec 15 20:50:40 2015 +0000 Add testcase for #11224 Test Plan: Validate Reviewers: austin, mpickering Reviewed By: mpickering Subscribers: mpickering, thomie Differential Revision: https://phabricator.haskell.org/D1622 GHC Trac Issues: #11224 >--------------------------------------------------------------- a701694b27143d094f9de0a78757bbdeaa07daa6 testsuite/tests/patsyn/should_run/T11224.hs | 28 +++++++++++++++++++++++++ testsuite/tests/patsyn/should_run/T11224.stdout | 6 ++++++ testsuite/tests/patsyn/should_run/all.T | 1 + 3 files changed, 35 insertions(+) diff --git a/testsuite/tests/patsyn/should_run/T11224.hs b/testsuite/tests/patsyn/should_run/T11224.hs new file mode 100644 index 0000000..f834e9b --- /dev/null +++ b/testsuite/tests/patsyn/should_run/T11224.hs @@ -0,0 +1,28 @@ +{-# LANGUAGE PatternSynonyms , ViewPatterns #-} + +-- inlining a pattern synonym shouldn't change semantics + +import Text.Read + +-- pattern PRead :: () => Read a => a -> String +pattern PRead a <- (readMaybe -> Just a) + +foo :: String -> Int +foo (PRead x) = (x::Int) +foo (PRead xs) = sum (xs::[Int]) +foo _ = 666 + +bar :: String -> Int +bar (readMaybe -> Just x) = (x::Int) +bar (readMaybe -> Just xs) = sum (xs::[Int]) +bar _ = 666 + +main :: IO () +main = do + print $ foo "1" -- 1 + print $ foo "[1,2,3]" -- 666 -- ??? + print $ foo "xxx" -- 666 + + print $ bar "1" -- 1 + print $ bar "[1,2,3]" -- 6 + print $ bar "xxx" -- 666 diff --git a/testsuite/tests/patsyn/should_run/T11224.stdout b/testsuite/tests/patsyn/should_run/T11224.stdout new file mode 100644 index 0000000..3a42854 --- /dev/null +++ b/testsuite/tests/patsyn/should_run/T11224.stdout @@ -0,0 +1,6 @@ +1 +6 +666 +1 +6 +666 diff --git a/testsuite/tests/patsyn/should_run/all.T b/testsuite/tests/patsyn/should_run/all.T index 45c48fb..c12bfc6 100644 --- a/testsuite/tests/patsyn/should_run/all.T +++ b/testsuite/tests/patsyn/should_run/all.T @@ -12,3 +12,4 @@ test('match-unboxed', normal, compile_and_run, ['']) test('unboxed-wrapper', normal, compile_and_run, ['']) test('records-run', normal, compile_and_run, ['']) test('ghci', just_ghci, ghci_script, ['ghci.script']) +test('T11224', [expect_broken(11224)], compile_and_run, ['']) \ No newline at end of file From git at git.haskell.org Tue Dec 15 21:22:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 21:22:45 +0000 (UTC) Subject: [commit: ghc] master: primops: Mark actions evaluated by `catch*` as lazy (28638df) Message-ID: <20151215212245.61E8E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/28638dfe79e915f33d75a1b22c5adce9e2b62b97/ghc >--------------------------------------------------------------- commit 28638dfe79e915f33d75a1b22c5adce9e2b62b97 Author: Ben Gamari Date: Tue Dec 15 20:08:17 2015 +0100 primops: Mark actions evaluated by `catch*` as lazy There is something very peculiar about the `catch` family of operations with respect to strictness analysis: they turn divergence into non-divergence. For this reason, it isn't safe to mark them as strict in the expression whose exceptions they are catching. The reason is this: Consider, let r = \st -> raiseIO# blah st in catch (\st -> ...(r st)..) handler st If we give the first argument of catch a strict signature, we'll get a demand 'C(S)' for 'r'; that is, 'r' is definitely called with one argument, which indeed it is. The trouble comes when we feed 'C(S)' into 'r's RHS as the demand of the body as this will lead us to conclude that the whole 'let' will diverge; clearly this isn't right. This is essentially the problem in #10712, which arose when 7c0fff41789669450b02dc1db7f5d7babba5dee6 marked the `catch*` primops as being strict in the thing to be evaluated. Here I've partially reverted this commit, again marking the first argument of these primops as lazy. Fixes #10712. Test Plan: Validate checking `exceptionsrun001` Reviewers: simonpj, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1616 GHC Trac Issues: #10712, #11222 >--------------------------------------------------------------- 28638dfe79e915f33d75a1b22c5adce9e2b62b97 compiler/prelude/primops.txt.pp | 30 ++++++++++++++++++++---------- testsuite/tests/perf/should_run/all.T | 3 ++- 2 files changed, 22 insertions(+), 11 deletions(-) diff --git a/compiler/prelude/primops.txt.pp b/compiler/prelude/primops.txt.pp index c16646e..de14e30 100644 --- a/compiler/prelude/primops.txt.pp +++ b/compiler/prelude/primops.txt.pp @@ -1946,17 +1946,27 @@ necessarily the second. Hence strictApply1Dmd and lazyApply1Dmd Howver, consider catch# (\st -> case x of ...) (..handler..) st We'll see that the entire thing is strict in 'x', so 'x' may be evaluated -before the catch#. So fi evaluting 'x' causes a divide-by-zero exception, +before the catch#. So if evaluting 'x' causes a divide-by-zero exception, it won't be caught. This seems acceptable: + - x might be evaluated somewhere else outside the catch# anyway - It's an imprecise eception anyway. Synchronous exceptions (in the IO monad) will never move in this way. -There was originally a comment - "Catch is actually strict in its first argument - but we don't want to tell the strictness - analyser about that, so that exceptions stay inside it." -but tracing it back through the commit logs did not give any -rationale. And making catch# lazy has performance costs for everyone. + +Unfortunately, there is a tricky wrinkle here, as pointed out in #10712. +Consider, + + let r = \st -> raiseIO# blah st + in catch (\st -> ...(r st)..) handler st + +If we give the first argument of catch a strict signature, we'll get +a demand 'C(S)' for 'r'; that is, 'r' is definitely called with one +argument, which indeed it is. The trouble comes when we feed 'C(S)' +into 'r's RHS as the demand of the body as this will lead us to conclude that +the whole 'let' will diverge; clearly this isn't right. + +There's something very special about catch: it turns divergence into +non-divergence. -} primop CatchOp "catch#" GenPrimOp @@ -1965,7 +1975,7 @@ primop CatchOp "catch#" GenPrimOp -> State# RealWorld -> (# State# RealWorld, a #) with - strictness = { \ _arity -> mkClosedStrictSig [strictApply1Dmd,lazyApply2Dmd,topDmd] topRes } + strictness = { \ _arity -> mkClosedStrictSig [lazyApply1Dmd,lazyApply2Dmd,topDmd] topRes } -- See Note [Strictness for mask/unmask/catch] out_of_line = True has_side_effects = True @@ -2069,7 +2079,7 @@ primop CatchRetryOp "catchRetry#" GenPrimOp -> (State# RealWorld -> (# State# RealWorld, a #) ) -> (State# RealWorld -> (# State# RealWorld, a #) ) with - strictness = { \ _arity -> mkClosedStrictSig [strictApply1Dmd,lazyApply1Dmd,topDmd] topRes } + strictness = { \ _arity -> mkClosedStrictSig [lazyApply1Dmd,lazyApply1Dmd,topDmd] topRes } -- See Note [Strictness for mask/unmask/catch] out_of_line = True has_side_effects = True @@ -2079,7 +2089,7 @@ primop CatchSTMOp "catchSTM#" GenPrimOp -> (b -> State# RealWorld -> (# State# RealWorld, a #) ) -> (State# RealWorld -> (# State# RealWorld, a #) ) with - strictness = { \ _arity -> mkClosedStrictSig [strictApply1Dmd,lazyApply2Dmd,topDmd] topRes } + strictness = { \ _arity -> mkClosedStrictSig [lazyApply1Dmd,lazyApply2Dmd,topDmd] topRes } -- See Note [Strictness for mask/unmask/catch] out_of_line = True has_side_effects = True diff --git a/testsuite/tests/perf/should_run/all.T b/testsuite/tests/perf/should_run/all.T index a86d61f..8260ee1 100644 --- a/testsuite/tests/perf/should_run/all.T +++ b/testsuite/tests/perf/should_run/all.T @@ -53,12 +53,13 @@ test('lazy-bs-alloc', [stats_num_field('peak_megabytes_allocated', (2, 1)), # expected value: 2 (amd64/Linux) stats_num_field('bytes allocated', - [(wordsize(64), 431500, 3), + [(wordsize(64), 444720, 3), # 489776 (amd64/Linux) # 2013-02-07: 429744 (amd64/Linux) # 2013-12-12: 425400 (amd64/Linux) # 2015-04-04: Widen 1->3% (amd64/Windows was failing) # 2015-08-15: 431500 (Windows not good enough. avg of Windows&Linux) + # 2015-12-15: 444720 (amd64/Linux, D1616) (wordsize(32), 411500, 2)]), # 2013-02-10: 421296 (x86/Windows) # 2013-02-10: 414180 (x86/OSX) From git at git.haskell.org Tue Dec 15 23:03:24 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 15 Dec 2015 23:03:24 +0000 (UTC) Subject: [commit: ghc] master: Expose enabled language extensions to TH (c1e2553) Message-ID: <20151215230324.310423A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c1e25536d67fba33ad6ddae5556115340d99000a/ghc >--------------------------------------------------------------- commit c1e25536d67fba33ad6ddae5556115340d99000a Author: Ben Gamari Date: Tue Dec 15 23:57:46 2015 +0100 Expose enabled language extensions to TH This exposes `template-haskell` functions for querying the language extensions which are enabled when compiling a module, - an `isExtEnabled` function to check whether an extension is enabled - an `extsEnabled` function to obtain a full list of enabled extensions To avoid code duplication this adds a `GHC.LanguageExtensions` module to `ghc-boot` and moves `DynFlags.ExtensionFlag` into it. A happy consequence of this is that the ungainly `DynFlags` lost around 500 lines. Moreover, flags corresponding to language extensions are now clearly distinguished from other flags due to the `LangExt.*` prefix. Updates haddock submodule. This fixes #10820. Test Plan: validate Reviewers: austin, spinda, hvr, goldfire, alanz Reviewed By: goldfire Subscribers: mpickering, RyanGlScott, hvr, simonpj, thomie Differential Revision: https://phabricator.haskell.org/D1200 GHC Trac Issues: #10820 >--------------------------------------------------------------- c1e25536d67fba33ad6ddae5556115340d99000a compiler/basicTypes/MkId.hs | 7 +- compiler/deSugar/DsBinds.hs | 7 +- compiler/deSugar/DsMonad.hs | 3 +- compiler/deSugar/DsUtils.hs | 5 +- compiler/deSugar/MatchLit.hs | 5 +- compiler/main/DriverPipeline.hs | 11 +- compiler/main/DynFlags.hs | 568 +++++++++------------ compiler/main/GHC.hs | 3 +- compiler/main/GhcMake.hs | 3 +- compiler/main/HeaderInfo.hs | 3 +- compiler/parser/Lexer.x | 75 +-- compiler/parser/Parser.y | 7 +- compiler/parser/RdrHsSyn.hs | 7 +- compiler/rename/RnBinds.hs | 16 +- compiler/rename/RnEnv.hs | 18 +- compiler/rename/RnExpr.hs | 25 +- compiler/rename/RnNames.hs | 5 +- compiler/rename/RnPat.hs | 23 +- compiler/rename/RnSource.hs | 7 +- compiler/rename/RnSplice.hs | 6 +- compiler/rename/RnTypes.hs | 28 +- compiler/typecheck/Inst.hs | 6 +- compiler/typecheck/TcBinds.hs | 7 +- compiler/typecheck/TcDefaults.hs | 4 +- compiler/typecheck/TcDeriv.hs | 35 +- compiler/typecheck/TcEnv.hs | 14 +- compiler/typecheck/TcErrors.hs | 3 +- compiler/typecheck/TcExpr.hs | 6 +- compiler/typecheck/TcForeign.hs | 3 +- compiler/typecheck/TcHsSyn.hs | 4 +- compiler/typecheck/TcHsType.hs | 15 +- compiler/typecheck/TcInstDcls.hs | 7 +- compiler/typecheck/TcInteract.hs | 3 +- compiler/typecheck/TcMType.hs | 4 +- compiler/typecheck/TcMatches.hs | 5 +- compiler/typecheck/TcPat.hs | 5 +- compiler/typecheck/TcRnDriver.hs | 5 +- compiler/typecheck/TcRnMonad.hs | 8 +- compiler/typecheck/TcSimplify.hs | 6 +- compiler/typecheck/TcSplice.hs | 6 + compiler/typecheck/TcTyClsDecls.hs | 31 +- compiler/typecheck/TcType.hs | 5 +- compiler/typecheck/TcValidity.hs | 40 +- docs/users_guide/7.12.1-notes.rst | 8 + ghc/InteractiveUI.hs | 11 +- ghc/ghc-bin.cabal.in | 1 + libraries/ghc-boot/GHC/LanguageExtensions.hs | 122 +++++ libraries/ghc-boot/ghc-boot.cabal | 1 + libraries/template-haskell/Language/Haskell/TH.hs | 3 + .../Language/Haskell/TH/LanguageExtensions.hs | 22 + .../template-haskell/Language/Haskell/TH/Syntax.hs | 26 +- libraries/template-haskell/template-haskell.cabal | 1 + testsuite/tests/ghc-api/T10508_api.hs | 3 +- testsuite/tests/th/T10820.hs | 16 + .../scripts/ghci053.stdout => th/T10820.stdout} | 1 + testsuite/tests/th/all.T | 1 + utils/haddock | 2 +- utils/mkUserGuidePart/Main.hs | 7 +- 58 files changed, 709 insertions(+), 570 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c1e25536d67fba33ad6ddae5556115340d99000a From git at git.haskell.org Wed Dec 16 07:11:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 07:11:31 +0000 (UTC) Subject: [commit: packages/pretty] tag 'pretty-1.1.3.2-release' created Message-ID: <20151216071131.624F13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty New tag : pretty-1.1.3.2-release Referencing: 489d58643c5781bd221ccf21f5537b29c4011db8 From git at git.haskell.org Wed Dec 16 07:11:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 07:11:33 +0000 (UTC) Subject: [commit: packages/pretty] master: Fix missing files from test-suite. (9f462e1) Message-ID: <20151216071133.682D13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branch : master Link : http://git.haskell.org/packages/pretty.git/commitdiff/9f462e10739655eb80a1141c22dae13c9595fdc1 >--------------------------------------------------------------- commit 9f462e10739655eb80a1141c22dae13c9595fdc1 Author: David Terei Date: Sat Jan 17 14:52:33 2015 -0800 Fix missing files from test-suite. >--------------------------------------------------------------- 9f462e10739655eb80a1141c22dae13c9595fdc1 pretty.cabal | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/pretty.cabal b/pretty.cabal index 8b81005..e1bf6a9 100644 --- a/pretty.cabal +++ b/pretty.cabal @@ -47,11 +47,13 @@ Test-Suite test-pretty QuickCheck >= 2.5 && <3 main-is: Test.hs other-modules: + PrettyTestVersion TestGenerators TestStructures + TestUtils + UnitLargeDoc UnitPP1 UnitT3911 - UnitLargeDoc extensions: CPP, BangPatterns, DeriveGeneric include-dirs: src/Text/PrettyPrint From git at git.haskell.org Wed Dec 16 07:11:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 07:11:35 +0000 (UTC) Subject: [commit: packages/pretty] master: Bump to version 1.1.2.1 (7deb64c) Message-ID: <20151216071135.6E8213A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branch : master Link : http://git.haskell.org/packages/pretty.git/commitdiff/7deb64ce5f18a14ca99752feecfd4b52f7fc9a99 >--------------------------------------------------------------- commit 7deb64ce5f18a14ca99752feecfd4b52f7fc9a99 Author: David Terei Date: Fri Dec 26 01:05:37 2014 -0800 Bump to version 1.1.2.1 >--------------------------------------------------------------- 7deb64ce5f18a14ca99752feecfd4b52f7fc9a99 CHANGELOG.md | 5 +++++ pretty.cabal | 2 +- 2 files changed, 6 insertions(+), 1 deletion(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index 5cb8069..1dbdce5 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -1,5 +1,10 @@ # Pretty library change log +## 1.1.2.1 -- 25th December, 2014 + +* Fix overly-strict issue preventing use of pretty for very large + docs (by Eyal Lotem). + ## 1.1.2.0 -- 25th December, 2014 * Merge in prettyclass package -- new Text.PrettyPrint.HughesPHClass. diff --git a/pretty.cabal b/pretty.cabal index e1bf6a9..25898c4 100644 --- a/pretty.cabal +++ b/pretty.cabal @@ -1,5 +1,5 @@ name: pretty -version: 1.1.2.0 +version: 1.1.2.1 synopsis: Pretty-printing library description: This package contains a pretty-printing library, a set of API's From git at git.haskell.org Wed Dec 16 07:11:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 07:11:37 +0000 (UTC) Subject: [commit: packages/pretty] master: Improve module description for HughesPJ (b093b1e) Message-ID: <20151216071137.742B03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branch : master Link : http://git.haskell.org/packages/pretty.git/commitdiff/b093b1e2eebd0023e6cdf003fd0723d32ecda968 >--------------------------------------------------------------- commit b093b1e2eebd0023e6cdf003fd0723d32ecda968 Author: David Terei Date: Fri Dec 26 00:38:36 2014 -0800 Improve module description for HughesPJ >--------------------------------------------------------------- b093b1e2eebd0023e6cdf003fd0723d32ecda968 src/Text/PrettyPrint/HughesPJ.hs | 16 ++++++++++------ 1 file changed, 10 insertions(+), 6 deletions(-) diff --git a/src/Text/PrettyPrint/HughesPJ.hs b/src/Text/PrettyPrint/HughesPJ.hs index c45f691..a091bdd 100644 --- a/src/Text/PrettyPrint/HughesPJ.hs +++ b/src/Text/PrettyPrint/HughesPJ.hs @@ -15,12 +15,17 @@ -- Stability : stable -- Portability : portable -- --- John Hughes's and Simon Peyton Jones's Pretty Printer Combinators +-- Provides a collection of pretty printer combinators, a set of API's +-- that provides a way to easily print out text in a consistent format +-- of your choosing. -- --- Based on /The Design of a Pretty-printing Library/ --- in Advanced Functional Programming, --- Johan Jeuring and Erik Meijer (eds), LNCS 925 --- +-- Originally designed by John Hughes's and Simon Peyton Jones's. +-- +-- For more information you can refer to the +-- that +-- serves as the basis for this libraries design: +-- /The Design -- of a Pretty-printing Library/ by John Hughes, in Advanced +-- Functional Programming, 1995 -- ----------------------------------------------------------------------------- @@ -58,7 +63,6 @@ module Text.PrettyPrint.HughesPJ ( -- * Utility functions for documents first, reduceDoc, - -- TODO: Should these be exported? Previously they weren't -- * Rendering documents From git at git.haskell.org Wed Dec 16 07:11:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 07:11:39 +0000 (UTC) Subject: [commit: packages/pretty] master: Bump base dependency to >= 4.5 (#18). (e34ba99) Message-ID: <20151216071139.79E483A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branch : master Link : http://git.haskell.org/packages/pretty.git/commitdiff/e34ba99e109259b66f188bb25c2cfe3bca664522 >--------------------------------------------------------------- commit e34ba99e109259b66f188bb25c2cfe3bca664522 Author: David Terei Date: Mon Jan 19 00:11:19 2015 -0800 Bump base dependency to >= 4.5 (#18). Support SafeHaskell and Generics, both of which require GHC 7.4 or greater. >--------------------------------------------------------------- e34ba99e109259b66f188bb25c2cfe3bca664522 pretty.cabal | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/pretty.cabal b/pretty.cabal index 25898c4..89e739c 100644 --- a/pretty.cabal +++ b/pretty.cabal @@ -31,7 +31,7 @@ Library Text.PrettyPrint Text.PrettyPrint.HughesPJ Text.PrettyPrint.HughesPJClass - build-depends: base >= 3 && < 5, + build-depends: base >= 4.5 && < 5, deepseq >= 1.1, ghc-prim extensions: CPP, BangPatterns, DeriveGeneric @@ -41,7 +41,7 @@ Test-Suite test-pretty type: exitcode-stdio-1.0 hs-source-dirs: tests src - build-depends: base >= 3 && < 5, + build-depends: base >= 4.5 && < 5, deepseq >= 1.1, ghc-prim, QuickCheck >= 2.5 && <3 From git at git.haskell.org Wed Dec 16 07:11:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 07:11:41 +0000 (UTC) Subject: [commit: packages/pretty] master: Add annotations to the Doc type (49b786d) Message-ID: <20151216071141.80ABE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branch : master Link : http://git.haskell.org/packages/pretty.git/commitdiff/49b786dcdc9add53ad494615ae6bbe4b263c9766 >--------------------------------------------------------------- commit 49b786dcdc9add53ad494615ae6bbe4b263c9766 Author: Trevor Elliott Date: Sat Jan 24 10:29:20 2015 -0800 Add annotations to the Doc type * Parameterize the Doc type by the type of annotations present * Add the Span type for describing annotated regions in the resulting String * Add renderSpans, and fullRenderAnn, for rendering with annotations >--------------------------------------------------------------- 49b786dcdc9add53ad494615ae6bbe4b263c9766 src/Text/PrettyPrint/HughesPJ.hs | 388 ++++++++++++++++++++++------------ src/Text/PrettyPrint/HughesPJClass.hs | 10 +- 2 files changed, 256 insertions(+), 142 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 49b786dcdc9add53ad494615ae6bbe4b263c9766 From git at git.haskell.org Wed Dec 16 07:11:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 07:11:43 +0000 (UTC) Subject: [commit: packages/pretty] master: Build in compatibility with the old pretty API (a1b780c) Message-ID: <20151216071143.8D51E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branch : master Link : http://git.haskell.org/packages/pretty.git/commitdiff/a1b780c5a3a335a369a7149c1145bdb8d0212aeb >--------------------------------------------------------------- commit a1b780c5a3a335a369a7149c1145bdb8d0212aeb Author: Trevor Elliott Date: Sat Jan 24 12:19:19 2015 -0800 Build in compatibility with the old pretty API >--------------------------------------------------------------- a1b780c5a3a335a369a7149c1145bdb8d0212aeb .../{PrettyPrint.hs => PrettyPrint/Annotated.hs} | 13 +- src/Text/PrettyPrint/{ => Annotated}/HughesPJ.hs | 4 +- .../PrettyPrint/{ => Annotated}/HughesPJClass.hs | 8 +- src/Text/PrettyPrint/HughesPJ.hs | 898 +++------------------ src/Text/PrettyPrint/HughesPJClass.hs | 10 +- 5 files changed, 143 insertions(+), 790 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a1b780c5a3a335a369a7149c1145bdb8d0212aeb From git at git.haskell.org Wed Dec 16 07:11:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 07:11:45 +0000 (UTC) Subject: [commit: packages/pretty] master: Export the Annotated modules (08d8913) Message-ID: <20151216071145.9354B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branch : master Link : http://git.haskell.org/packages/pretty.git/commitdiff/08d8913f11e7087a45fcde8b08adf59e44107d25 >--------------------------------------------------------------- commit 08d8913f11e7087a45fcde8b08adf59e44107d25 Author: Trevor Elliott Date: Sat Jan 24 12:31:15 2015 -0800 Export the Annotated modules >--------------------------------------------------------------- 08d8913f11e7087a45fcde8b08adf59e44107d25 pretty.cabal | 3 +++ src/Text/PrettyPrint/Annotated.hs | 2 +- 2 files changed, 4 insertions(+), 1 deletion(-) diff --git a/pretty.cabal b/pretty.cabal index 89e739c..38a12b1 100644 --- a/pretty.cabal +++ b/pretty.cabal @@ -31,6 +31,9 @@ Library Text.PrettyPrint Text.PrettyPrint.HughesPJ Text.PrettyPrint.HughesPJClass + Text.PrettyPrint.Annotated + Text.PrettyPrint.Annotated.HughesPJ + Text.PrettyPrint.Annotated.HughesPJClass build-depends: base >= 4.5 && < 5, deepseq >= 1.1, ghc-prim diff --git a/src/Text/PrettyPrint/Annotated.hs b/src/Text/PrettyPrint/Annotated.hs index 3bfc353..dc967e6 100644 --- a/src/Text/PrettyPrint/Annotated.hs +++ b/src/Text/PrettyPrint/Annotated.hs @@ -21,7 +21,7 @@ -- ----------------------------------------------------------------------------- -module Text.PrettyPrintAnnotated ( +module Text.PrettyPrint.Annotated ( -- * The document type Doc, From git at git.haskell.org Wed Dec 16 07:11:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 07:11:47 +0000 (UTC) Subject: [commit: packages/pretty] master: Update the test suite (b96d2aa) Message-ID: <20151216071147.9C2793A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branch : master Link : http://git.haskell.org/packages/pretty.git/commitdiff/b96d2aaddb133391a0d17e8d2a0004eaf8f1dd77 >--------------------------------------------------------------- commit b96d2aaddb133391a0d17e8d2a0004eaf8f1dd77 Author: Trevor Elliott Date: Sat Jan 24 12:58:34 2015 -0800 Update the test suite >--------------------------------------------------------------- b96d2aaddb133391a0d17e8d2a0004eaf8f1dd77 pretty.cabal | 2 +- tests/Test.hs | 170 ++++++++++++++++++++++++------------------------ tests/TestStructures.hs | 18 +++-- 3 files changed, 98 insertions(+), 92 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b96d2aaddb133391a0d17e8d2a0004eaf8f1dd77 From git at git.haskell.org Wed Dec 16 07:11:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 07:11:49 +0000 (UTC) Subject: [commit: packages/pretty] master: Add renderDecorated, and renderDecoratedM (aca8d01) Message-ID: <20151216071149.A246B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branch : master Link : http://git.haskell.org/packages/pretty.git/commitdiff/aca8d0163b0d4f0e06856d6dde22da40546ca8c2 >--------------------------------------------------------------- commit aca8d0163b0d4f0e06856d6dde22da40546ca8c2 Author: Trevor Elliott Date: Sat Jan 24 13:47:04 2015 -0800 Add renderDecorated, and renderDecoratedM Also, go back to storing the annotation value in the AnnotEnd constructor, as that makes it easier to use that value when processing both the start and end of an annotation. >--------------------------------------------------------------- aca8d0163b0d4f0e06856d6dde22da40546ca8c2 src/Text/PrettyPrint/Annotated/HughesPJ.hs | 88 +++++++++++++++++++++++++----- 1 file changed, 74 insertions(+), 14 deletions(-) diff --git a/src/Text/PrettyPrint/Annotated/HughesPJ.hs b/src/Text/PrettyPrint/Annotated/HughesPJ.hs index 971a53f..de89c8e 100644 --- a/src/Text/PrettyPrint/Annotated/HughesPJ.hs +++ b/src/Text/PrettyPrint/Annotated/HughesPJ.hs @@ -74,6 +74,8 @@ module Text.PrettyPrint.Annotated.HughesPJ ( -- ** Annotation rendering renderSpans, Span(..), + renderDecorated, + renderDecoratedM, -- ** Rendering with a particular style Style(..), @@ -235,15 +237,15 @@ Notice the difference between -- | RDoc is a "reduced GDoc", guaranteed not to have a top-level Above or Beside. type RDoc = Doc -data AnnotDetails a = AnnotStart a +data AnnotDetails a = AnnotStart | NoAnnot TextDetails {-# UNPACK #-} !Int - | AnnotEnd + | AnnotEnd a deriving (Show,Eq) instance Functor AnnotDetails where - fmap f (AnnotStart a) = AnnotStart (f a) + fmap _ AnnotStart = AnnotStart fmap _ (NoAnnot d i) = NoAnnot d i - fmap _ AnnotEnd = AnnotEnd + fmap f (AnnotEnd a) = AnnotEnd (f a) -- NOTE: Annotations are assumed to have zero length; only text has a length. annotSize :: AnnotDetails a -> Int @@ -300,9 +302,9 @@ instance NFData a => NFData (Doc a) where rnf (Above ud s ld) = rnf ud `seq` rnf s `seq` rnf ld instance NFData a => NFData (AnnotDetails a) where - rnf (AnnotStart a) = rnf a + rnf AnnotStart = () rnf (NoAnnot d sl) = rnf d `seq` rnf sl - rnf AnnotEnd = () + rnf (AnnotEnd a) = rnf a instance NFData TextDetails where rnf (Chr c) = rnf c @@ -314,9 +316,9 @@ instance NFData TextDetails where -- | Attach an annotation to a document. annotate :: a -> Doc a -> Doc a -annotate a d = TextBeside (AnnotStart a) +annotate a d = TextBeside AnnotStart $ beside (reduceDoc d) False - $ TextBeside AnnotEnd Empty + $ TextBeside (AnnotEnd a) Empty -- | A document of height and width 1, containing a literal character. @@ -1056,7 +1058,7 @@ instance Functor Span where -- State required for generating document spans. data Spans a = Spans { sOffset :: !Int -- ^ Current offset from the end of the document - , sStack :: [Int -> a -> Span a] + , sStack :: [Int -> Span a] -- ^ Currently open spans , sSpans :: [Span a] -- ^ Collected annotation regions @@ -1075,7 +1077,7 @@ renderSpans = finalize where adjust s = s { spanStart = size - spanStart s } - mkSpan end start a = Span { spanStart = start + mkSpan a end start = Span { spanStart = start , spanLength = start - end -- ^ this seems wrong, but remember that it's -- working backwards at this point @@ -1083,16 +1085,74 @@ renderSpans = finalize -- the document gets generated in reverse, which is why the starting -- annotation ends the annotation. - spanPrinter (AnnotStart a) s = + spanPrinter AnnotStart s = case sStack s of - sp : rest -> s { sSpans = sp (sOffset s) a : sSpans s, sStack = rest } + sp : rest -> s { sSpans = sp (sOffset s) : sSpans s, sStack = rest } _ -> error "renderSpans: stack underflow" - spanPrinter AnnotEnd s = - s { sStack = mkSpan (sOffset s) : sStack s } + spanPrinter (AnnotEnd a) s = + s { sStack = mkSpan a (sOffset s) : sStack s } spanPrinter (NoAnnot td l) s = case td of Chr c -> s { sOutput = c : sOutput s, sOffset = sOffset s + l } Str t -> s { sOutput = t ++ sOutput s, sOffset = sOffset s + l } PStr t -> s { sOutput = t ++ sOutput s, sOffset = sOffset s + l } + + +-- | Render out a String, interpreting the annotations as part of the resulting +-- document. +-- +-- IMPORTANT: the size of the annotation string does NOT figure into the layout +-- of the document, so the document will lay out as though the annotations are +-- not present. +renderDecorated :: (ann -> String) -- ^ Starting an annotation + -> (ann -> String) -- ^ Ending an annotation + -> Doc ann -> String +renderDecorated startAnn endAnn = + finalize . fullRenderAnn (mode style) (lineLength style) (ribbonsPerLine style) + annPrinter + ("", []) + where + annPrinter AnnotStart (rest,stack) = + case stack of + a : as -> (startAnn a ++ rest, as) + _ -> error "renderDecorated: stack underflow" + + annPrinter (AnnotEnd a) (rest,stack) = + (endAnn a ++ rest, a : stack) + + annPrinter (NoAnnot s _) (rest,stack) = + (txtPrinter s rest, stack) + + finalize (str,_) = str + + +-- | Render a document with annotations, by interpreting the start and end of +-- the annotations, as well as the text details in the context of a monad. +renderDecoratedM :: Monad m + => (ann -> m r) -- ^ Starting an annotation + -> (ann -> m r) -- ^ Ending an annotation + -> (String -> m r) -- ^ Text formatting + -> m r -- ^ Document end + -> Doc ann -> m r +renderDecoratedM startAnn endAnn txt docEnd = + finalize . fullRenderAnn (mode style) (lineLength style) (ribbonsPerLine style) + annPrinter + (docEnd, []) + where + annPrinter AnnotStart (rest,stack) = + case stack of + a : as -> (startAnn a >> rest, as) + _ -> error "renderDecorated: stack underflow" + + annPrinter (AnnotEnd a) (rest,stack) = + (endAnn a >> rest, a : stack) + + annPrinter (NoAnnot td _) (rest,stack) = + case td of + Chr c -> (txt [c] >> rest, stack) + Str s -> (txt s >> rest, stack) + PStr s -> (txt s >> rest, stack) + + finalize (m,_) = m From git at git.haskell.org Wed Dec 16 07:11:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 07:11:51 +0000 (UTC) Subject: [commit: packages/pretty] master: Make TextDetails strict in the NoAnnot constructor (764213f) Message-ID: <20151216071151.A80663A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branch : master Link : http://git.haskell.org/packages/pretty.git/commitdiff/764213f8632571a2ba1dbc559242249f7c04d318 >--------------------------------------------------------------- commit 764213f8632571a2ba1dbc559242249f7c04d318 Author: Trevor Elliott Date: Mon Jan 26 17:07:43 2015 -0800 Make TextDetails strict in the NoAnnot constructor >--------------------------------------------------------------- 764213f8632571a2ba1dbc559242249f7c04d318 src/Text/PrettyPrint/Annotated/HughesPJ.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Text/PrettyPrint/Annotated/HughesPJ.hs b/src/Text/PrettyPrint/Annotated/HughesPJ.hs index de89c8e..8670fbd 100644 --- a/src/Text/PrettyPrint/Annotated/HughesPJ.hs +++ b/src/Text/PrettyPrint/Annotated/HughesPJ.hs @@ -238,7 +238,7 @@ Notice the difference between type RDoc = Doc data AnnotDetails a = AnnotStart - | NoAnnot TextDetails {-# UNPACK #-} !Int + | NoAnnot !TextDetails {-# UNPACK #-} !Int | AnnotEnd a deriving (Show,Eq) From git at git.haskell.org Wed Dec 16 07:11:53 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 07:11:53 +0000 (UTC) Subject: [commit: packages/pretty] master: Merge pull request #19 from elliottt/annotations (b718d1f) Message-ID: <20151216071153.B25C03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branch : master Link : http://git.haskell.org/packages/pretty.git/commitdiff/b718d1f65acd5d153820d78684b6b139ac36b8d6 >--------------------------------------------------------------- commit b718d1f65acd5d153820d78684b6b139ac36b8d6 Merge: e34ba99 764213f Author: David Terei Date: Mon Jan 26 17:33:51 2015 -0800 Merge pull request #19 from elliottt/annotations Add an annotation API >--------------------------------------------------------------- b718d1f65acd5d153820d78684b6b139ac36b8d6 pretty.cabal | 5 +- .../{PrettyPrint.hs => PrettyPrint/Annotated.hs} | 13 +- src/Text/PrettyPrint/{ => Annotated}/HughesPJ.hs | 452 +++++++++----- .../PrettyPrint/{ => Annotated}/HughesPJClass.hs | 18 +- src/Text/PrettyPrint/HughesPJ.hs | 664 ++------------------- tests/Test.hs | 170 +++--- tests/TestStructures.hs | 18 +- 7 files changed, 495 insertions(+), 845 deletions(-) From git at git.haskell.org Wed Dec 16 07:11:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 07:11:55 +0000 (UTC) Subject: [commit: packages/pretty] master: Bump version to 1.1.3.1 (f93bc6f) Message-ID: <20151216071155.B7DD63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branch : master Link : http://git.haskell.org/packages/pretty.git/commitdiff/f93bc6fd5a3065c7e54fec44a80895ea3af3d706 >--------------------------------------------------------------- commit f93bc6fd5a3065c7e54fec44a80895ea3af3d706 Author: David Terei Date: Wed Mar 11 11:49:45 2015 -0700 Bump version to 1.1.3.1 >--------------------------------------------------------------- f93bc6fd5a3065c7e54fec44a80895ea3af3d706 pretty.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/pretty.cabal b/pretty.cabal index 1598faa..c4ac991 100644 --- a/pretty.cabal +++ b/pretty.cabal @@ -1,5 +1,5 @@ name: pretty -version: 1.1.2.1 +version: 1.1.3.1 synopsis: Pretty-printing library description: This package contains a pretty-printing library, a set of API's From git at git.haskell.org Wed Dec 16 07:11:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 07:11:57 +0000 (UTC) Subject: [commit: packages/pretty] master: fix a comment that confuses Haddock (1b06c69) Message-ID: <20151216071157.BDE0A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branch : master Link : http://git.haskell.org/packages/pretty.git/commitdiff/1b06c695fb56d360afa39fdc47c67c0fe06b0825 >--------------------------------------------------------------- commit 1b06c695fb56d360afa39fdc47c67c0fe06b0825 Author: ?mer Sinan A?acan Date: Fri Mar 13 17:54:23 2015 -0400 fix a comment that confuses Haddock >--------------------------------------------------------------- 1b06c695fb56d360afa39fdc47c67c0fe06b0825 src/Text/PrettyPrint/Annotated/HughesPJ.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Text/PrettyPrint/Annotated/HughesPJ.hs b/src/Text/PrettyPrint/Annotated/HughesPJ.hs index 8670fbd..dfc48dd 100644 --- a/src/Text/PrettyPrint/Annotated/HughesPJ.hs +++ b/src/Text/PrettyPrint/Annotated/HughesPJ.hs @@ -1079,7 +1079,7 @@ renderSpans = finalize mkSpan a end start = Span { spanStart = start , spanLength = start - end - -- ^ this seems wrong, but remember that it's + -- this seems wrong, but remember that it's -- working backwards at this point , spanAnnotation = a } From git at git.haskell.org Wed Dec 16 07:11:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 07:11:59 +0000 (UTC) Subject: [commit: packages/pretty] master: test haddock generation in CI (60a5241) Message-ID: <20151216071159.C35DB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branch : master Link : http://git.haskell.org/packages/pretty.git/commitdiff/60a5241c6e21a4a593e650088a165feca7962619 >--------------------------------------------------------------- commit 60a5241c6e21a4a593e650088a165feca7962619 Author: ?mer Sinan A?acan Date: Fri Mar 13 17:58:47 2015 -0400 test haddock generation in CI >--------------------------------------------------------------- 60a5241c6e21a4a593e650088a165feca7962619 .travis.yml | 1 + 1 file changed, 1 insertion(+) diff --git a/.travis.yml b/.travis.yml index de5fe5b..2790e4b 100644 --- a/.travis.yml +++ b/.travis.yml @@ -34,6 +34,7 @@ script: - cabal check - ([ "$CABALVER" == "1.20" ] && cabal test --show-details=streaming) || ([ "$CABALVER" != "1.20" ] && cabal test) - cabal sdist + - cabal haddock - export SRC_TGZ=$(cabal info . | awk '{print $2 ".tar.gz";exit}') ; cd dist/; if [ -f "$SRC_TGZ" ]; then From git at git.haskell.org Wed Dec 16 07:12:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 07:12:01 +0000 (UTC) Subject: [commit: packages/pretty] master: Merge pull request #24 from osa1/master (bfc6295) Message-ID: <20151216071201.C91923A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branch : master Link : http://git.haskell.org/packages/pretty.git/commitdiff/bfc6295ed2d9755e824b9e148bf7d0b6d63d0130 >--------------------------------------------------------------- commit bfc6295ed2d9755e824b9e148bf7d0b6d63d0130 Merge: f93bc6f 60a5241 Author: David Terei Date: Thu Mar 19 01:46:35 2015 -0700 Merge pull request #24 from osa1/master fix a comment that confuses Haddock >--------------------------------------------------------------- bfc6295ed2d9755e824b9e148bf7d0b6d63d0130 .travis.yml | 1 + src/Text/PrettyPrint/Annotated/HughesPJ.hs | 2 +- 2 files changed, 2 insertions(+), 1 deletion(-) From git at git.haskell.org Wed Dec 16 07:12:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 07:12:03 +0000 (UTC) Subject: [commit: packages/pretty] master: Clean up module intro documentation. (2ce46a5) Message-ID: <20151216071203.D0E713A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branch : master Link : http://git.haskell.org/packages/pretty.git/commitdiff/2ce46a57385ef480ba0777d790ed5ed554d4544b >--------------------------------------------------------------- commit 2ce46a57385ef480ba0777d790ed5ed554d4544b Author: David Terei Date: Thu Mar 19 02:03:01 2015 -0700 Clean up module intro documentation. >--------------------------------------------------------------- 2ce46a57385ef480ba0777d790ed5ed554d4544b src/Text/PrettyPrint.hs | 2 +- src/Text/PrettyPrint/Annotated.hs | 14 +++++++------- src/Text/PrettyPrint/Annotated/HughesPJ.hs | 16 ++++------------ src/Text/PrettyPrint/Annotated/HughesPJClass.hs | 5 +++-- 4 files changed, 15 insertions(+), 22 deletions(-) diff --git a/src/Text/PrettyPrint.hs b/src/Text/PrettyPrint.hs index 0d6b6d4..6c65111 100644 --- a/src/Text/PrettyPrint.hs +++ b/src/Text/PrettyPrint.hs @@ -15,7 +15,7 @@ -- that provides a way to easily print out text in a consistent format -- of your choosing. -- --- This module should be used as opposed to the "Text.PrettyPrint.HughesPJ" +-- This module should be used as opposed to the 'Text.PrettyPrint.HughesPJ' -- module. Both are equivalent though as this module simply re-exports the -- other. -- diff --git a/src/Text/PrettyPrint/Annotated.hs b/src/Text/PrettyPrint/Annotated.hs index dc967e6..a9e5862 100644 --- a/src/Text/PrettyPrint/Annotated.hs +++ b/src/Text/PrettyPrint/Annotated.hs @@ -4,20 +4,20 @@ ----------------------------------------------------------------------------- -- | -- Module : Text.PrettyPrint.Annotated --- Copyright : (c) The University of Glasgow 2001 +-- Copyright : (c) Trevor Elliott 2015 -- License : BSD-style (see the file LICENSE) -- -- Maintainer : David Terei -- Stability : stable -- Portability : portable -- --- Provides a collection of pretty printer combinators, a set of API's --- that provides a way to easily print out text in a consistent format --- of your choosing. +-- This module provides a version of pretty that allows for annotations to be +-- attached to documents. Annotations are arbitrary pieces of metadata that can +-- be attached to sub-documents. -- --- This module should be used as opposed to the "Text.PrettyPrint.HughesPJ" --- module. Both are equivalent though as this module simply re-exports the --- other. +-- This module should be used as opposed to the +-- 'Text.PrettyPrint.Annotated.HughesPJ' module. Both are equivalent though as +-- this module simply re-exports the other. -- ----------------------------------------------------------------------------- diff --git a/src/Text/PrettyPrint/Annotated/HughesPJ.hs b/src/Text/PrettyPrint/Annotated/HughesPJ.hs index dfc48dd..02fe34c 100644 --- a/src/Text/PrettyPrint/Annotated/HughesPJ.hs +++ b/src/Text/PrettyPrint/Annotated/HughesPJ.hs @@ -8,24 +8,16 @@ ----------------------------------------------------------------------------- -- | -- Module : Text.PrettyPrint.Annotated.HughesPJ --- Copyright : (c) The University of Glasgow 2001 +-- Copyright : (c) Trevor Elliott 2015 -- License : BSD-style (see the file LICENSE) -- -- Maintainer : David Terei -- Stability : stable -- Portability : portable -- --- Provides a collection of pretty printer combinators, a set of API's --- that provides a way to easily print out text in a consistent format --- of your choosing. --- --- Originally designed by John Hughes's and Simon Peyton Jones's. --- --- For more information you can refer to the --- that --- serves as the basis for this libraries design: --- /The Design -- of a Pretty-printing Library/ by John Hughes, in Advanced --- Functional Programming, 1995 +-- This module provides a version of pretty that allows for annotations to be +-- attached to documents. Annotations are arbitrary pieces of metadata that can +-- be attached to sub-documents. -- ----------------------------------------------------------------------------- diff --git a/src/Text/PrettyPrint/Annotated/HughesPJClass.hs b/src/Text/PrettyPrint/Annotated/HughesPJClass.hs index 4e2b2c7..1aefc49 100644 --- a/src/Text/PrettyPrint/Annotated/HughesPJClass.hs +++ b/src/Text/PrettyPrint/Annotated/HughesPJClass.hs @@ -5,7 +5,7 @@ ----------------------------------------------------------------------------- -- | -- Module : Text.PrettyPrint.Annotated.HughesPJClass --- Copyright : (c) Lennart Augustsson 2014 +-- Copyright : (c) Trevor Elliott 2015 -- License : BSD-style (see the file LICENSE) -- -- Maintainer : David Terei @@ -15,7 +15,8 @@ -- Pretty printing class, simlar to 'Show' but nicer looking. -- -- Note that the precedence level is a 'Rational' so there is an unlimited --- number of levels. This module re-exports 'Text.PrettyPrint.HughesPJ'. +-- number of levels. This module re-exports +-- 'Text.PrettyPrint.Annotated.HughesPJ'. -- ----------------------------------------------------------------------------- From git at git.haskell.org Wed Dec 16 07:12:05 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 07:12:05 +0000 (UTC) Subject: [commit: packages/pretty] master: Bump to version 1.1.3.2 (9fd5f2b) Message-ID: <20151216071205.D6D933A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty On branch : master Link : http://git.haskell.org/packages/pretty.git/commitdiff/9fd5f2b596bdfbce0414f973009b579d5d2430fa >--------------------------------------------------------------- commit 9fd5f2b596bdfbce0414f973009b579d5d2430fa Author: David Terei Date: Thu Mar 19 02:03:31 2015 -0700 Bump to version 1.1.3.2 >--------------------------------------------------------------- 9fd5f2b596bdfbce0414f973009b579d5d2430fa CHANGELOG.md | 9 +++++++++ pretty.cabal | 2 +- 2 files changed, 10 insertions(+), 1 deletion(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index 1dbdce5..8524efe 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -1,5 +1,14 @@ # Pretty library change log +## 1.1.3.2 -- 19th March, 2015 + +* Fix bug with haddock documentation. +* Clean up module intro documentation. + +## 1.1.3.1 -- 11th March, 2015 + +* Add support for annotations in pretty (by Trevor Elliott). + ## 1.1.2.1 -- 25th December, 2014 * Fix overly-strict issue preventing use of pretty for very large diff --git a/pretty.cabal b/pretty.cabal index c4ac991..d336635 100644 --- a/pretty.cabal +++ b/pretty.cabal @@ -1,5 +1,5 @@ name: pretty -version: 1.1.3.1 +version: 1.1.3.2 synopsis: Pretty-printing library description: This package contains a pretty-printing library, a set of API's From git at git.haskell.org Wed Dec 16 07:12:08 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 07:12:08 +0000 (UTC) Subject: [commit: packages/pretty] master's head updated: Bump to version 1.1.3.2 (9fd5f2b) Message-ID: <20151216071208.058903A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty Branch 'master' now includes: 4ce5928 add minimal pragma to pretty class 912f63c Add appropriate Show, Eq and Generic instances ac4c532 fix hslint warnings f6b2e75 work around bug with `cabal test` ead25e7 remove some unused helper functions from test-suite 459bca1 fix travis for bug in cabal 1.20 02503a3 Improve test-suite, merging in GHC tests 04ca57e Fix compilation under GHC 7.10 8be7d73 Update changelog 7eb7c6c Bump to version 1.1.2.0 dfc5ff9 Add failing test for large vcat 307b817 Resolve foldr-strictness stack overflow bug 9ebd518 Put large_doc test (slowest) last c57c7a9 Special-case reduce for horiz/vert 0a0b534 Improve bench1 cabal support b036410 Clean up UnitLargeDoc style to be like rest of test-suite b093b1e Improve module description for HughesPJ 9f462e1 Fix missing files from test-suite. 7deb64c Bump to version 1.1.2.1 e34ba99 Bump base dependency to >= 4.5 (#18). 49b786d Add annotations to the Doc type a1b780c Build in compatibility with the old pretty API 08d8913 Export the Annotated modules b96d2aa Update the test suite aca8d01 Add renderDecorated, and renderDecoratedM 764213f Make TextDetails strict in the NoAnnot constructor b718d1f Merge pull request #19 from elliottt/annotations f93bc6f Bump version to 1.1.3.1 1b06c69 fix a comment that confuses Haddock 60a5241 test haddock generation in CI bfc6295 Merge pull request #24 from osa1/master 2ce46a5 Clean up module intro documentation. 9fd5f2b Bump to version 1.1.3.2 From git at git.haskell.org Wed Dec 16 07:54:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 07:54:00 +0000 (UTC) Subject: [commit: ghc] master: Update pretty submodule to v1.1.3.2 release (50c795c) Message-ID: <20151216075400.5AC7A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/50c795c1a4ce021652d682b08579596dc458ccbc/ghc >--------------------------------------------------------------- commit 50c795c1a4ce021652d682b08579596dc458ccbc Author: Herbert Valerio Riedel Date: Wed Dec 16 00:12:32 2015 +0100 Update pretty submodule to v1.1.3.2 release The `pretty-1.1.3.2` release is the version designated for GHC 8.0.1 /cc @dterei Differential Revision: https://phabricator.haskell.org/D1633 >--------------------------------------------------------------- 50c795c1a4ce021652d682b08579596dc458ccbc libraries/pretty | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/pretty b/libraries/pretty index 7eb7c6c..9fd5f2b 160000 --- a/libraries/pretty +++ b/libraries/pretty @@ -1 +1 @@ -Subproject commit 7eb7c6c01be4596da3dae9ca57d8adac37cc33fc +Subproject commit 9fd5f2b596bdfbce0414f973009b579d5d2430fa From git at git.haskell.org Wed Dec 16 09:42:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:42:16 +0000 (UTC) Subject: [commit: packages/binary] master: Instance for GHC.Fingerprint, which is part of base. (551515e) Message-ID: <20151216094216.E2B433A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/551515ec34daf416b69a17eb843a202662b5b0a1 >--------------------------------------------------------------- commit 551515ec34daf416b69a17eb843a202662b5b0a1 Author: Mathieu Boespflug Date: Sat May 23 23:08:57 2015 +0200 Instance for GHC.Fingerprint, which is part of base. >--------------------------------------------------------------- 551515ec34daf416b69a17eb843a202662b5b0a1 src/Data/Binary/Class.hs | 18 ++++++++++++++++++ 1 file changed, 18 insertions(+) diff --git a/src/Data/Binary/Class.hs b/src/Data/Binary/Class.hs index 2477056..1cba18a 100644 --- a/src/Data/Binary/Class.hs +++ b/src/Data/Binary/Class.hs @@ -77,6 +77,10 @@ import qualified Data.Sequence as Seq import qualified Data.Foldable as Fold #endif +#if __GLASGOW_HASKELL__ >= 704 +import GHC.Fingerprint +#endif + ------------------------------------------------------------------------ #ifdef GENERICS @@ -577,3 +581,17 @@ instance (Binary i, Ix i, Binary e, IArray UArray e) => Binary (UArray i e) wher n <- get xs <- getMany n return (listArray bs xs) + +------------------------------------------------------------------------ +-- Fingerprints + +#if __GLASGOW_HASKELL__ >= 704 +instance Binary Fingerprint where + put (Fingerprint x1 x2) = do + put x1 + put x2 + get = do + x1 <- get + x2 <- get + return (Fingerprint x1 x2) +#endif From git at git.haskell.org Wed Dec 16 09:42:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:42:18 +0000 (UTC) Subject: [commit: packages/binary] master: Merge branch 'instance-fingerprint' of https://github.com/mboes/binary (0cd1529) Message-ID: <20151216094218.E8D003A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/0cd152901e8d296cfb2994f01a363e23e7d0e469 >--------------------------------------------------------------- commit 0cd152901e8d296cfb2994f01a363e23e7d0e469 Merge: 86e4c9a 551515e Author: Lennart Kolmodin Date: Wed Jun 3 11:37:38 2015 -0700 Merge branch 'instance-fingerprint' of https://github.com/mboes/binary >--------------------------------------------------------------- 0cd152901e8d296cfb2994f01a363e23e7d0e469 src/Data/Binary/Class.hs | 18 ++++++++++++++++++ 1 file changed, 18 insertions(+) From git at git.haskell.org Wed Dec 16 09:42:20 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:42:20 +0000 (UTC) Subject: [commit: packages/binary] master: Force the Fingerprint constructor to reduce memory usage. (66146ae) Message-ID: <20151216094220.EF15A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/66146ae3423fbbd62a24246f591cfba46ce3a0d4 >--------------------------------------------------------------- commit 66146ae3423fbbd62a24246f591cfba46ce3a0d4 Author: Lennart Kolmodin Date: Wed Jun 3 11:50:56 2015 -0700 Force the Fingerprint constructor to reduce memory usage. The two fields are unpacked, so this saves a couple of words per field until the Fingerprint value gets used. >--------------------------------------------------------------- 66146ae3423fbbd62a24246f591cfba46ce3a0d4 src/Data/Binary/Class.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Data/Binary/Class.hs b/src/Data/Binary/Class.hs index 8904381..79a30b2 100644 --- a/src/Data/Binary/Class.hs +++ b/src/Data/Binary/Class.hs @@ -599,5 +599,5 @@ instance Binary Fingerprint where get = do x1 <- get x2 <- get - return (Fingerprint x1 x2) + return $! Fingerprint x1 x2 #endif From git at git.haskell.org Wed Dec 16 09:42:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:42:23 +0000 (UTC) Subject: [commit: packages/binary] master: Add roundtrip tests for GHC.Fingerprint. (2a84d67) Message-ID: <20151216094223.019EB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/2a84d6707a72fb21891ba842bcfff240d52e16cb >--------------------------------------------------------------- commit 2a84d6707a72fb21891ba842bcfff240d52e16cb Author: Lennart Kolmodin Date: Wed Jun 3 11:52:46 2015 -0700 Add roundtrip tests for GHC.Fingerprint. >--------------------------------------------------------------- 2a84d6707a72fb21891ba842bcfff240d52e16cb src/Data/Binary/Class.hs | 8 ++++++-- tests/QC.hs | 25 +++++++++++++++++++++++-- 2 files changed, 29 insertions(+), 4 deletions(-) diff --git a/src/Data/Binary/Class.hs b/src/Data/Binary/Class.hs index 79a30b2..4259165 100644 --- a/src/Data/Binary/Class.hs +++ b/src/Data/Binary/Class.hs @@ -10,6 +10,10 @@ #define HAS_NATURAL #endif +#if __GLASGOW_HASKELL__ >= 704 +#define HAS_GHC_FINGERPRINT +#endif + ----------------------------------------------------------------------------- -- | -- Module : Data.Binary.Class @@ -77,7 +81,7 @@ import qualified Data.Sequence as Seq import qualified Data.Foldable as Fold #endif -#if __GLASGOW_HASKELL__ >= 704 +#ifdef HAS_GHC_FINGERPRINT import GHC.Fingerprint #endif @@ -591,7 +595,7 @@ instance (Binary i, Ix i, Binary e, IArray UArray e) => Binary (UArray i e) wher ------------------------------------------------------------------------ -- Fingerprints -#if __GLASGOW_HASKELL__ >= 704 +#ifdef HAS_GHC_FINGERPRINT instance Binary Fingerprint where put (Fingerprint x1 x2) = do put x1 diff --git a/tests/QC.hs b/tests/QC.hs index addf185..58991a4 100644 --- a/tests/QC.hs +++ b/tests/QC.hs @@ -5,10 +5,14 @@ module Main ( main ) where #define HAS_NATURAL #endif +#if __GLASGOW_HASKELL__ >= 704 +#define HAS_GHC_FINGERPRINT +#endif + import Control.Applicative import Control.Exception as C (SomeException, catch, evaluate) -import Control.Monad (unless) +import Control.Monad (unless, liftM2) import qualified Data.ByteString as B import qualified Data.ByteString.Lazy as L import qualified Data.ByteString.Lazy.Internal as L @@ -20,6 +24,10 @@ import System.IO.Unsafe import Numeric.Natural #endif +#ifdef HAS_GHC_FINGERPRINT +import GHC.Fingerprint +#endif + import Test.Framework import Test.Framework.Providers.QuickCheck2 import Test.QuickCheck @@ -376,6 +384,16 @@ prop_test_Natural = forAll (gen :: Gen Natural) test ------------------------------------------------------------------------ +#ifdef HAS_GHC_FINGERPRINT +prop_test_GHC_Fingerprint :: Property +prop_test_GHC_Fingerprint = forAll gen test + where + gen :: Gen Fingerprint + gen = liftM2 Fingerprint arbitrary arbitrary +#endif + +------------------------------------------------------------------------ + type T a = a -> Property type B a = a -> Bool @@ -454,7 +472,10 @@ tests = , ("Int", p (test :: T Int )) , ("Integer", p (test :: T Integer )) #ifdef HAS_NATURAL - , ("Natural", (prop_test_Natural :: Property )) + , ("Natural", prop_test_Natural ) +#endif +#ifdef HAS_GHC_FINGERPRINT + , ("GHC.Fingerprint", prop_test_GHC_Fingerprint ) #endif , ("Float", p (test :: T Float )) From git at git.haskell.org Wed Dec 16 09:42:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:42:25 +0000 (UTC) Subject: [commit: packages/binary] master: Add Show instance for Fingerprint on GHC < 7.8. (8debedd) Message-ID: <20151216094225.07DD73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/8debedd3fcb6525ac0d7de2dd49217dce2abc0d9 >--------------------------------------------------------------- commit 8debedd3fcb6525ac0d7de2dd49217dce2abc0d9 Author: Lennart Kolmodin Date: Wed Jun 3 14:46:21 2015 -0700 Add Show instance for Fingerprint on GHC < 7.8. 'forAll' needs Fingerprint to have a Show instance. Starting from GHC 7.8 (base-4.7) Fingerprint has a Show instance, but for older versions we need to provide one ourselves. >--------------------------------------------------------------- 8debedd3fcb6525ac0d7de2dd49217dce2abc0d9 tests/QC.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/tests/QC.hs b/tests/QC.hs index 58991a4..493d2aa 100644 --- a/tests/QC.hs +++ b/tests/QC.hs @@ -390,6 +390,10 @@ prop_test_GHC_Fingerprint = forAll gen test where gen :: Gen Fingerprint gen = liftM2 Fingerprint arbitrary arbitrary +#if !MIN_VERSION_base(4,7,0) +instance Show Fingerprint where + show (Fingerprint x1 x2) = show (x1,x2) +#endif #endif ------------------------------------------------------------------------ From git at git.haskell.org Wed Dec 16 09:42:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:42:27 +0000 (UTC) Subject: [commit: packages/binary] master: Fix AMP and Safe Haskell related warnings in GHC 7.10. (7524d87) Message-ID: <20151216094227.0EACD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/7524d87040395793375c8752ef2ae4314d8d69f5 >--------------------------------------------------------------- commit 7524d87040395793375c8752ef2ae4314d8d69f5 Author: Mathieu Boespflug Date: Sat Jun 6 23:30:05 2015 +0200 Fix AMP and Safe Haskell related warnings in GHC 7.10. >--------------------------------------------------------------- 7524d87040395793375c8752ef2ae4314d8d69f5 src/Data/Binary/Builder/Base.hs | 1 + src/Data/Binary/Builder/Internal.hs | 2 +- src/Data/Binary/Generic.hs | 1 + src/Data/Binary/Get.hs | 2 -- src/Data/Binary/Put.hs | 1 + 5 files changed, 4 insertions(+), 3 deletions(-) diff --git a/src/Data/Binary/Builder/Base.hs b/src/Data/Binary/Builder/Base.hs index 897aa2b..c4f0790 100644 --- a/src/Data/Binary/Builder/Base.hs +++ b/src/Data/Binary/Builder/Base.hs @@ -87,6 +87,7 @@ import GHC.Word (Word32(..),Word16(..),Word64(..)) import GHC.Word (uncheckedShiftRL64#) # endif #endif +import Prelude -- Silence AMP warning. ------------------------------------------------------------------------ diff --git a/src/Data/Binary/Builder/Internal.hs b/src/Data/Binary/Builder/Internal.hs index c9d2fbf..2a28539 100644 --- a/src/Data/Binary/Builder/Internal.hs +++ b/src/Data/Binary/Builder/Internal.hs @@ -1,6 +1,6 @@ {-# LANGUAGE CPP #-} #if __GLASGOW_HASKELL__ >= 701 -{-# LANGUAGE Trustworthy #-} +{-# LANGUAGE Safe #-} #endif ----------------------------------------------------------------------------- -- | diff --git a/src/Data/Binary/Generic.hs b/src/Data/Binary/Generic.hs index a2eb6ea..e1a3a1c 100644 --- a/src/Data/Binary/Generic.hs +++ b/src/Data/Binary/Generic.hs @@ -26,6 +26,7 @@ import Data.Binary.Put import Data.Bits import Data.Word import GHC.Generics +import Prelude -- Silence AMP warning. -- Type without constructors instance GBinary V1 where diff --git a/src/Data/Binary/Get.hs b/src/Data/Binary/Get.hs index afff081..0541efb 100644 --- a/src/Data/Binary/Get.hs +++ b/src/Data/Binary/Get.hs @@ -203,8 +203,6 @@ import qualified Data.ByteString.Unsafe as B import qualified Data.ByteString.Lazy as L import qualified Data.ByteString.Lazy.Internal as L -import Control.Applicative - import Data.Binary.Get.Internal hiding ( Decoder(..), runGetIncremental ) import qualified Data.Binary.Get.Internal as I diff --git a/src/Data/Binary/Put.hs b/src/Data/Binary/Put.hs index 38a1b31..004c15a 100644 --- a/src/Data/Binary/Put.hs +++ b/src/Data/Binary/Put.hs @@ -62,6 +62,7 @@ import qualified Data.ByteString as S import qualified Data.ByteString.Lazy as L import Control.Applicative +import Prelude -- Silence AMP warning. ------------------------------------------------------------------------ From git at git.haskell.org Wed Dec 16 09:42:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:42:29 +0000 (UTC) Subject: [commit: packages/binary] master: Declare a few modules as Safe rather than Trustworthy. (5714385) Message-ID: <20151216094229.145963A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/571438513fdf060e56fd73883c590a926fdde948 >--------------------------------------------------------------- commit 571438513fdf060e56fd73883c590a926fdde948 Author: Mathieu Boespflug Date: Sat Jun 6 23:31:29 2015 +0200 Declare a few modules as Safe rather than Trustworthy. This silences a GHC 7.10 warning that indicates that these modules are marked trustworthy when in fact they don't need to, since they are safe. >--------------------------------------------------------------- 571438513fdf060e56fd73883c590a926fdde948 src/Data/Binary/Class.hs | 5 +++-- src/Data/Binary/Generic.hs | 2 +- src/Data/Binary/Put.hs | 2 +- 3 files changed, 5 insertions(+), 4 deletions(-) diff --git a/src/Data/Binary/Class.hs b/src/Data/Binary/Class.hs index 4259165..0807c5f 100644 --- a/src/Data/Binary/Class.hs +++ b/src/Data/Binary/Class.hs @@ -1,6 +1,6 @@ {-# LANGUAGE CPP, FlexibleContexts #-} #if __GLASGOW_HASKELL__ >= 701 -{-# LANGUAGE Trustworthy #-} +{-# LANGUAGE Safe #-} #endif #ifdef GENERICS {-# LANGUAGE DefaultSignatures #-} @@ -41,12 +41,13 @@ module Data.Binary.Class ( ) where import Data.Word +import Data.Bits +import Data.Int import Data.Binary.Put import Data.Binary.Get import Control.Monad -import Foreign import Data.ByteString.Lazy (ByteString) import qualified Data.ByteString.Lazy as L diff --git a/src/Data/Binary/Generic.hs b/src/Data/Binary/Generic.hs index e1a3a1c..2077772 100644 --- a/src/Data/Binary/Generic.hs +++ b/src/Data/Binary/Generic.hs @@ -1,5 +1,5 @@ {-# LANGUAGE BangPatterns, CPP, FlexibleInstances, KindSignatures, - ScopedTypeVariables, Trustworthy, TypeOperators, TypeSynonymInstances #-} + ScopedTypeVariables, Safe, TypeOperators, TypeSynonymInstances #-} {-# OPTIONS_GHC -fno-warn-orphans #-} ----------------------------------------------------------------------------- diff --git a/src/Data/Binary/Put.hs b/src/Data/Binary/Put.hs index 004c15a..112d145 100644 --- a/src/Data/Binary/Put.hs +++ b/src/Data/Binary/Put.hs @@ -1,6 +1,6 @@ {-# LANGUAGE CPP #-} #if __GLASGOW_HASKELL__ >= 701 -{-# LANGUAGE Trustworthy #-} +{-# LANGUAGE Safe #-} #endif ----------------------------------------------------------------------------- From git at git.haskell.org Wed Dec 16 09:42:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:42:31 +0000 (UTC) Subject: [commit: packages/binary] master: Merge pull request #77 from mboes/ghc710-warnings (6892225) Message-ID: <20151216094231.1ACA23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/6892225ebc38c8bb7fee85b903fafcae3cbbfd8e >--------------------------------------------------------------- commit 6892225ebc38c8bb7fee85b903fafcae3cbbfd8e Merge: 8debedd 5714385 Author: Lennart Kolmodin Date: Sun Jun 7 20:17:31 2015 -0700 Merge pull request #77 from mboes/ghc710-warnings Fix AMP and Safe Haskell related warnings in GHC 7.10. >--------------------------------------------------------------- 6892225ebc38c8bb7fee85b903fafcae3cbbfd8e src/Data/Binary/Builder/Base.hs | 1 + src/Data/Binary/Builder/Internal.hs | 2 +- src/Data/Binary/Class.hs | 5 +++-- src/Data/Binary/Generic.hs | 3 ++- src/Data/Binary/Get.hs | 2 -- src/Data/Binary/Put.hs | 3 ++- 6 files changed, 9 insertions(+), 7 deletions(-) From git at git.haskell.org Wed Dec 16 09:42:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:42:33 +0000 (UTC) Subject: [commit: packages/binary] master: Add changelog.md to 'cabal sdist' (fb98a5b) Message-ID: <20151216094233.20C443A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/fb98a5b15880aca220caeca3f5c404adb6a35eaf >--------------------------------------------------------------- commit fb98a5b15880aca220caeca3f5c404adb6a35eaf Author: Lennart Kolmodin Date: Wed Jul 8 16:10:13 2015 +0200 Add changelog.md to 'cabal sdist' Should fix issue #80. >--------------------------------------------------------------- fb98a5b15880aca220caeca3f5c404adb6a35eaf binary.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/binary.cabal b/binary.cabal index f8ccb69..a8a65a8 100644 --- a/binary.cabal +++ b/binary.cabal @@ -20,7 +20,7 @@ build-type: Simple cabal-version: >= 1.8 tested-with: GHC == 7.4.2, GHC == 7.6.3, GHC == 7.8.2, GHC == 7.10.1 extra-source-files: - README.md docs/hcar/binary-Lb.tex tools/derive/*.hs + README.md changelog.md docs/hcar/binary-Lb.tex tools/derive/*.hs -- from the benchmark 'bench' extra-source-files: From git at git.haskell.org Wed Dec 16 09:42:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:42:35 +0000 (UTC) Subject: [commit: packages/binary] master: Bump version to 0.7.6.0. (23b5911) Message-ID: <20151216094235.2720A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/23b59113a757e05446f236fb76e965f1c18f1b7e >--------------------------------------------------------------- commit 23b59113a757e05446f236fb76e965f1c18f1b7e Author: Lennart Kolmodin Date: Mon Jul 27 13:59:19 2015 +0200 Bump version to 0.7.6.0. >--------------------------------------------------------------- 23b59113a757e05446f236fb76e965f1c18f1b7e binary.cabal | 2 +- changelog.md | 5 +++++ 2 files changed, 6 insertions(+), 1 deletion(-) diff --git a/binary.cabal b/binary.cabal index a8a65a8..8109975 100644 --- a/binary.cabal +++ b/binary.cabal @@ -1,5 +1,5 @@ name: binary -version: 0.7.5.0 +version: 0.7.6.0 license: BSD3 license-file: LICENSE author: Lennart Kolmodin diff --git a/changelog.md b/changelog.md index 6763f96..1bf50de 100644 --- a/changelog.md +++ b/changelog.md @@ -1,6 +1,11 @@ binary ====== +binary-0.7.6.0 +-------------- + +- Added binary instance for GHC.Fingerprint (from GHC >= 7.4). + binary-0.7.5.0 -------------- From git at git.haskell.org Wed Dec 16 09:42:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:42:37 +0000 (UTC) Subject: [commit: packages/binary] master: Update Travis CI to use GHC 7.8.3 -> 7.8.4. (cd7030e) Message-ID: <20151216094237.2D58A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/cd7030ebfdc58867018e35eb56fa7ffef1eeced9 >--------------------------------------------------------------- commit cd7030ebfdc58867018e35eb56fa7ffef1eeced9 Author: Lennart Kolmodin Date: Tue Jul 28 13:25:48 2015 +0200 Update Travis CI to use GHC 7.8.3 -> 7.8.4. >--------------------------------------------------------------- cd7030ebfdc58867018e35eb56fa7ffef1eeced9 .travis.yml | 2 +- binary.cabal | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index eb66f2c..a405342 100644 --- a/.travis.yml +++ b/.travis.yml @@ -4,7 +4,7 @@ env: - CABALVER=1.18 GHCVER=7.4.2 - CABALVER=1.18 GHCVER=7.6.3 - - CABALVER=1.18 GHCVER=7.8.3 + - CABALVER=1.18 GHCVER=7.8.4 - CABALVER=1.22 GHCVER=7.10.1 before_install: diff --git a/binary.cabal b/binary.cabal index 8109975..78dc074 100644 --- a/binary.cabal +++ b/binary.cabal @@ -18,7 +18,7 @@ category: Data, Parsing stability: provisional build-type: Simple cabal-version: >= 1.8 -tested-with: GHC == 7.4.2, GHC == 7.6.3, GHC == 7.8.2, GHC == 7.10.1 +tested-with: GHC == 7.4.2, GHC == 7.6.3, GHC == 7.8.4, GHC == 7.10.1 extra-source-files: README.md changelog.md docs/hcar/binary-Lb.tex tools/derive/*.hs From git at git.haskell.org Wed Dec 16 09:42:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:42:39 +0000 (UTC) Subject: [commit: packages/binary] master: Don't mark modules using bytestring as safe on GHC 7.2 to fix compilation (fb381cc) Message-ID: <20151216094239.356433A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/fb381cc6b8bbe23a87cb48c8a5681990bf522d2a >--------------------------------------------------------------- commit fb381cc6b8bbe23a87cb48c8a5681990bf522d2a Author: Adam Bergmark Date: Wed Jul 29 17:13:50 2015 +0200 Don't mark modules using bytestring as safe on GHC 7.2 to fix compilation >--------------------------------------------------------------- fb381cc6b8bbe23a87cb48c8a5681990bf522d2a src/Data/Binary/Class.hs | 2 +- src/Data/Binary/Generic.hs | 5 ++++- src/Data/Binary/Put.hs | 2 +- 3 files changed, 6 insertions(+), 3 deletions(-) diff --git a/src/Data/Binary/Class.hs b/src/Data/Binary/Class.hs index 0807c5f..37117f7 100644 --- a/src/Data/Binary/Class.hs +++ b/src/Data/Binary/Class.hs @@ -1,5 +1,5 @@ {-# LANGUAGE CPP, FlexibleContexts #-} -#if __GLASGOW_HASKELL__ >= 701 +#if __GLASGOW_HASKELL__ >= 701 && __GLASGOW_HASKELL__ != 702 {-# LANGUAGE Safe #-} #endif #ifdef GENERICS diff --git a/src/Data/Binary/Generic.hs b/src/Data/Binary/Generic.hs index 2077772..3f8edb3 100644 --- a/src/Data/Binary/Generic.hs +++ b/src/Data/Binary/Generic.hs @@ -1,5 +1,8 @@ {-# LANGUAGE BangPatterns, CPP, FlexibleInstances, KindSignatures, - ScopedTypeVariables, Safe, TypeOperators, TypeSynonymInstances #-} + ScopedTypeVariables, TypeOperators, TypeSynonymInstances #-} +#if __GLASGOW_HASKELL__ >= 701 && __GLASGOW_HASKELL__ != 702 +{-# LANGUAGE Safe #-} +#endif {-# OPTIONS_GHC -fno-warn-orphans #-} ----------------------------------------------------------------------------- diff --git a/src/Data/Binary/Put.hs b/src/Data/Binary/Put.hs index 112d145..5ada9b2 100644 --- a/src/Data/Binary/Put.hs +++ b/src/Data/Binary/Put.hs @@ -1,5 +1,5 @@ {-# LANGUAGE CPP #-} -#if __GLASGOW_HASKELL__ >= 701 +#if __GLASGOW_HASKELL__ >= 701 && __GLASGOW_HASKELL__ != 702 {-# LANGUAGE Safe #-} #endif From git at git.haskell.org Wed Dec 16 09:42:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:42:41 +0000 (UTC) Subject: [commit: packages/binary] master: Merge pull request #83 from bergmark/ghc72 (6e636f4) Message-ID: <20151216094241.3B1C73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/6e636f468701ed82b3e79eda9129215fc0f4ef68 >--------------------------------------------------------------- commit 6e636f468701ed82b3e79eda9129215fc0f4ef68 Merge: cd7030e fb381cc Author: Lennart Kolmodin Date: Wed Jul 29 19:31:45 2015 +0200 Merge pull request #83 from bergmark/ghc72 Don't mark modules using bytestring as safe on GHC 7.2 to fix compilation >--------------------------------------------------------------- 6e636f468701ed82b3e79eda9129215fc0f4ef68 src/Data/Binary/Class.hs | 2 +- src/Data/Binary/Generic.hs | 5 ++++- src/Data/Binary/Put.hs | 2 +- 3 files changed, 6 insertions(+), 3 deletions(-) From git at git.haskell.org Wed Dec 16 09:42:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:42:43 +0000 (UTC) Subject: [commit: packages/binary] master: Bump version to 0.7.6.1. (cfd4680) Message-ID: <20151216094243.40F1B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/cfd4680104d44982605d9c985bb2ebc4c0abe304 >--------------------------------------------------------------- commit cfd4680104d44982605d9c985bb2ebc4c0abe304 Author: Lennart Kolmodin Date: Wed Jul 29 19:36:28 2015 +0200 Bump version to 0.7.6.1. >--------------------------------------------------------------- cfd4680104d44982605d9c985bb2ebc4c0abe304 binary.cabal | 2 +- changelog.md | 5 +++++ 2 files changed, 6 insertions(+), 1 deletion(-) diff --git a/binary.cabal b/binary.cabal index 78dc074..59b55b6 100644 --- a/binary.cabal +++ b/binary.cabal @@ -1,5 +1,5 @@ name: binary -version: 0.7.6.0 +version: 0.7.6.1 license: BSD3 license-file: LICENSE author: Lennart Kolmodin diff --git a/changelog.md b/changelog.md index 1bf50de..493a50a 100644 --- a/changelog.md +++ b/changelog.md @@ -1,6 +1,11 @@ binary ====== +binary-0.7.6.1 +-------------- + +- Fix compilation for GHC == 7.2.*. + binary-0.7.6.0 -------------- From git at git.haskell.org Wed Dec 16 09:42:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:42:45 +0000 (UTC) Subject: [commit: packages/binary] master: Use GHC 7.10.2 on Travis CI instead of GHC 7.10.1. (cd675bb) Message-ID: <20151216094245.4745E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/cd675bb30acd66b1301e7f4ac721e1440e1858df >--------------------------------------------------------------- commit cd675bb30acd66b1301e7f4ac721e1440e1858df Author: Lennart Kolmodin Date: Thu Jul 30 10:17:25 2015 +0200 Use GHC 7.10.2 on Travis CI instead of GHC 7.10.1. >--------------------------------------------------------------- cd675bb30acd66b1301e7f4ac721e1440e1858df .travis.yml | 2 +- binary.cabal | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/.travis.yml b/.travis.yml index a405342..d77d543 100644 --- a/.travis.yml +++ b/.travis.yml @@ -5,7 +5,7 @@ env: - CABALVER=1.18 GHCVER=7.4.2 - CABALVER=1.18 GHCVER=7.6.3 - CABALVER=1.18 GHCVER=7.8.4 - - CABALVER=1.22 GHCVER=7.10.1 + - CABALVER=1.22 GHCVER=7.10.2 before_install: - sudo add-apt-repository -y ppa:hvr/ghc diff --git a/binary.cabal b/binary.cabal index 59b55b6..c88993b 100644 --- a/binary.cabal +++ b/binary.cabal @@ -18,7 +18,7 @@ category: Data, Parsing stability: provisional build-type: Simple cabal-version: >= 1.8 -tested-with: GHC == 7.4.2, GHC == 7.6.3, GHC == 7.8.4, GHC == 7.10.1 +tested-with: GHC == 7.4.2, GHC == 7.6.3, GHC == 7.8.4, GHC == 7.10.2 extra-source-files: README.md changelog.md docs/hcar/binary-Lb.tex tools/derive/*.hs From git at git.haskell.org Wed Dec 16 09:42:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:42:47 +0000 (UTC) Subject: [commit: packages/binary] master: Inline flush late to give the RULES a chanse to act (bbebc9a) Message-ID: <20151216094247.4E38A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/bbebc9a58906a98cf8a734fc8c270ffc941ed654 >--------------------------------------------------------------- commit bbebc9a58906a98cf8a734fc8c270ffc941ed654 Author: Lennart Kolmodin Date: Thu Jul 30 18:55:21 2015 +0200 Inline flush late to give the RULES a chanse to act RULE: append flush flush = flush >--------------------------------------------------------------- bbebc9a58906a98cf8a734fc8c270ffc941ed654 src/Data/Binary/Builder/Base.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Data/Binary/Builder/Base.hs b/src/Data/Binary/Builder/Base.hs index c4f0790..a1f46b5 100644 --- a/src/Data/Binary/Builder/Base.hs +++ b/src/Data/Binary/Builder/Base.hs @@ -191,6 +191,7 @@ flush = Builder $ \ k buf@(Buffer p o u l) -> else let !b = Buffer p (o+u) 0 l !bs = S.PS p o u in return $! L.Chunk bs (inlinePerformIO (k b)) +{-# INLINE [0] flush #-} ------------------------------------------------------------------------ From git at git.haskell.org Wed Dec 16 09:42:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:42:49 +0000 (UTC) Subject: [commit: packages/binary] master: Mark INLINEs with a phase to remove warning. (112a1a5) Message-ID: <20151216094249.5438D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/112a1a5d6d8069cd227d51d99a142da64f0a61aa >--------------------------------------------------------------- commit 112a1a5d6d8069cd227d51d99a142da64f0a61aa Author: Lennart Kolmodin Date: Thu Jul 30 18:56:51 2015 +0200 Mark INLINEs with a phase to remove warning. The warnings are like this; Rule "getWord16le/readN" may never fire because ?getWord16le? might inline first The RULES do the same thing as the inlining, so either one is fine. Specifying a phase removes the warning. >--------------------------------------------------------------- 112a1a5d6d8069cd227d51d99a142da64f0a61aa src/Data/Binary/Get.hs | 14 +++++++------- 1 file changed, 7 insertions(+), 7 deletions(-) diff --git a/src/Data/Binary/Get.hs b/src/Data/Binary/Get.hs index 0541efb..091a14c 100644 --- a/src/Data/Binary/Get.hs +++ b/src/Data/Binary/Get.hs @@ -409,7 +409,7 @@ getPtr n = readNWith n peek -- | Read a Word8 from the monad state getWord8 :: Get Word8 getWord8 = readN 1 B.unsafeHead -{-# INLINE getWord8 #-} +{-# INLINE[2] getWord8 #-} -- force GHC to inline getWordXX {-# RULES @@ -429,7 +429,7 @@ word16be :: B.ByteString -> Word16 word16be = \s -> (fromIntegral (s `B.unsafeIndex` 0) `shiftl_w16` 8) .|. (fromIntegral (s `B.unsafeIndex` 1)) -{-# INLINE getWord16be #-} +{-# INLINE[2] getWord16be #-} {-# INLINE word16be #-} -- | Read a Word16 in little endian format @@ -440,7 +440,7 @@ word16le :: B.ByteString -> Word16 word16le = \s -> (fromIntegral (s `B.unsafeIndex` 1) `shiftl_w16` 8) .|. (fromIntegral (s `B.unsafeIndex` 0) ) -{-# INLINE getWord16le #-} +{-# INLINE[2] getWord16le #-} {-# INLINE word16le #-} -- | Read a Word32 in big endian format @@ -453,7 +453,7 @@ word32be = \s -> (fromIntegral (s `B.unsafeIndex` 1) `shiftl_w32` 16) .|. (fromIntegral (s `B.unsafeIndex` 2) `shiftl_w32` 8) .|. (fromIntegral (s `B.unsafeIndex` 3) ) -{-# INLINE getWord32be #-} +{-# INLINE[2] getWord32be #-} {-# INLINE word32be #-} -- | Read a Word32 in little endian format @@ -466,7 +466,7 @@ word32le = \s -> (fromIntegral (s `B.unsafeIndex` 2) `shiftl_w32` 16) .|. (fromIntegral (s `B.unsafeIndex` 1) `shiftl_w32` 8) .|. (fromIntegral (s `B.unsafeIndex` 0) ) -{-# INLINE getWord32le #-} +{-# INLINE[2] getWord32le #-} {-# INLINE word32le #-} -- | Read a Word64 in big endian format @@ -483,7 +483,7 @@ word64be = \s -> (fromIntegral (s `B.unsafeIndex` 5) `shiftl_w64` 16) .|. (fromIntegral (s `B.unsafeIndex` 6) `shiftl_w64` 8) .|. (fromIntegral (s `B.unsafeIndex` 7) ) -{-# INLINE getWord64be #-} +{-# INLINE[2] getWord64be #-} {-# INLINE word64be #-} -- | Read a Word64 in little endian format @@ -500,7 +500,7 @@ word64le = \s -> (fromIntegral (s `B.unsafeIndex` 2) `shiftl_w64` 16) .|. (fromIntegral (s `B.unsafeIndex` 1) `shiftl_w64` 8) .|. (fromIntegral (s `B.unsafeIndex` 0) ) -{-# INLINE getWord64le #-} +{-# INLINE[2] getWord64le #-} {-# INLINE word64le #-} ------------------------------------------------------------------------ From git at git.haskell.org Wed Dec 16 09:42:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:42:51 +0000 (UTC) Subject: [commit: packages/binary] master: Silence some warnings in benchmarks/Get.hs (76d2475) Message-ID: <20151216094251.599693A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/76d2475f47dbbecc6aced2a4799db5ade11c392b >--------------------------------------------------------------- commit 76d2475f47dbbecc6aced2a4799db5ade11c392b Author: Lennart Kolmodin Date: Sun Aug 9 17:49:26 2015 +0200 Silence some warnings in benchmarks/Get.hs >--------------------------------------------------------------- 76d2475f47dbbecc6aced2a4799db5ade11c392b benchmarks/Get.hs | 23 ++++++++++++++++------- 1 file changed, 16 insertions(+), 7 deletions(-) diff --git a/benchmarks/Get.hs b/benchmarks/Get.hs index fd18acf..7a51492 100644 --- a/benchmarks/Get.hs +++ b/benchmarks/Get.hs @@ -8,21 +8,17 @@ module Main where import Control.DeepSeq import Control.Exception (evaluate) -import Control.Monad.Trans (liftIO) import Criterion.Main import qualified Data.ByteString as S import qualified Data.ByteString.Char8 as C8 import qualified Data.ByteString.Lazy as L import Data.Char (ord) -import Data.Monoid (Monoid(mappend, mempty)) -import Data.Word (Word8, Word16, Word32) +import Data.Word (Word8) import Control.Applicative import Data.Binary.Get -import Data.Binary ( get ) import qualified Data.Serialize.Get as Cereal -import qualified Data.Serialize as Cereal import qualified Data.Attoparsec.ByteString as A import qualified Data.Attoparsec.ByteString.Lazy as AL @@ -86,16 +82,24 @@ main = do whnf (runTest (getWord8N16A mega)) oneMegabyteLBS ] +checkBracket :: Int -> Int checkBracket x | x == bracketCount = x | otherwise = error "argh!" +runTest :: Get a -> L.ByteString -> a runTest decoder inp = runGet decoder inp + +runCereal :: Cereal.Get a -> C8.ByteString -> a runCereal decoder inp = case Cereal.runGet decoder inp of Right a -> a Left err -> error err + +runAtto :: AL.Parser a -> C8.ByteString -> a runAtto decoder inp = case A.parseOnly decoder inp of Right a -> a Left err -> error err + +runAttoL :: Show a => AL.Parser a -> L.ByteString -> a runAttoL decoder inp = case AL.parse decoder inp of AL.Done _ r -> r a -> error (show a) @@ -108,15 +112,20 @@ oneMegabyte = S.replicate mega $ fromIntegral $ ord 'a' oneMegabyteLBS :: L.ByteString oneMegabyteLBS = L.fromChunks [oneMegabyte] +mega :: Int mega = 1024 * 1024 -- 100k of brackets +bracketTest :: L.ByteString -> Int bracketTest inp = runTest bracketParser inp bracketCount :: Int bracketCount = fromIntegral $ L.length brackets `div` 2 +brackets :: L.ByteString brackets = L.fromChunks [C8.concat (L.toChunks bracketsInChunks)] + +bracketsInChunks :: L.ByteString bracketsInChunks = L.fromChunks (replicate chunksOfBrackets oneChunk) where oneChunk = "((()((()()))((()(()()()()()()()(((()()()()(()()(()(()())))))()((())())))()())(((())())(()))))()(()))" @@ -143,9 +152,9 @@ bracketParser_cereal = cont <|> return 0 bracketParser_atto :: A.Parser Int bracketParser_atto = cont <|> return 0 where - cont = do v <- some ( do A.word8 40 + cont = do v <- some ( do _ <- A.word8 40 n <- bracketParser_atto - A.word8 41 + _ <- A.word8 41 return $! n + 1) return $! sum v From git at git.haskell.org Wed Dec 16 09:42:53 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:42:53 +0000 (UTC) Subject: [commit: packages/binary] master: Change the non-allocating benchmarks to allocating. (848a000) Message-ID: <20151216094253.608283A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/848a000cee0e01fcf685f52b93aa77c8d68b7f0b >--------------------------------------------------------------- commit 848a000cee0e01fcf685f52b93aa77c8d68b7f0b Author: Lennart Kolmodin Date: Sun Aug 9 18:11:02 2015 +0200 Change the non-allocating benchmarks to allocating. Previously we had several non-allocating benchmarks. They were not representative to the most common use case where we want to save all the decoded input, not just a fraction. This patch updates the benchmark to save the decoded input in lists. >--------------------------------------------------------------- 848a000cee0e01fcf685f52b93aa77c8d68b7f0b benchmarks/Get.hs | 128 ++++++++++++++++++++++++++++++------------------------ 1 file changed, 71 insertions(+), 57 deletions(-) diff --git a/benchmarks/Get.hs b/benchmarks/Get.hs index 7a51492..de0a19f 100644 --- a/benchmarks/Get.hs +++ b/benchmarks/Get.hs @@ -159,12 +159,16 @@ bracketParser_atto = cont <|> return 0 return $! sum v -- Strict struct of 4 Word8s -data Struct4 = Struct4 {-# UNPACK #-} !Word8 - {-# UNPACK #-} !Word8 - {-# UNPACK #-} !Word8 - {-# UNPACK #-} !Word8 - deriving Show - +data S2 = S2 {-# UNPACK #-} !Word8 {-# UNPACK #-} !Word8 +data S4 = S4 {-# UNPACK #-} !Word8 {-# UNPACK #-} !Word8 {-# UNPACK #-} !Word8 {-# UNPACK #-} !Word8 +data S8 = S8 {-# UNPACK #-} !Word8 {-# UNPACK #-} !Word8 {-# UNPACK #-} !Word8 {-# UNPACK #-} !Word8 + {-# UNPACK #-} !Word8 {-# UNPACK #-} !Word8 {-# UNPACK #-} !Word8 {-# UNPACK #-} !Word8 +data S16 = S16 {-# UNPACK #-} !Word8 {-# UNPACK #-} !Word8 {-# UNPACK #-} !Word8 {-# UNPACK #-} !Word8 + {-# UNPACK #-} !Word8 {-# UNPACK #-} !Word8 {-# UNPACK #-} !Word8 {-# UNPACK #-} !Word8 + {-# UNPACK #-} !Word8 {-# UNPACK #-} !Word8 {-# UNPACK #-} !Word8 {-# UNPACK #-} !Word8 + {-# UNPACK #-} !Word8 {-# UNPACK #-} !Word8 {-# UNPACK #-} !Word8 {-# UNPACK #-} !Word8 + +getStruct4 :: Int -> Get [S4] getStruct4 = loop [] where loop acc 0 = return acc loop acc n = do @@ -172,9 +176,10 @@ getStruct4 = loop [] !w1 <- getWord8 !w2 <- getWord8 !w3 <- getWord8 - let !s = Struct4 w0 w1 w2 w3 + let !s = S4 w0 w1 w2 w3 loop (s : acc) (n - 4) +getStruct4_cereal :: Int -> Cereal.Get [S4] getStruct4_cereal = loop [] where loop acc 0 = return acc loop acc n = do @@ -182,9 +187,10 @@ getStruct4_cereal = loop [] !w1 <- Cereal.getWord8 !w2 <- Cereal.getWord8 !w3 <- Cereal.getWord8 - let !s = Struct4 w0 w1 w2 w3 + let !s = S4 w0 w1 w2 w3 loop (s : acc) (n - 4) +getStruct4_atto :: Int -> A.Parser [S4] getStruct4_atto = loop [] where loop acc 0 = return acc loop acc n = do @@ -192,48 +198,53 @@ getStruct4_atto = loop [] !w1 <- A.anyWord8 !w2 <- A.anyWord8 !w3 <- A.anyWord8 - let !s = Struct4 w0 w1 w2 w3 + let !s = S4 w0 w1 w2 w3 loop (s : acc) (n - 4) --- No-allocation loops. - -getWord8N1 = loop 0 +getWord8N1 :: Int -> Get [Word8] +getWord8N1 = loop [] where loop s n | s `seq` n `seq` False = undefined loop s 0 = return s loop s n = do s0 <- getWord8 - loop (s0+s) (n-1) + loop (s0:s) (n-1) -getWord8N1_cereal = loop 0 +getWord8N1_cereal :: Int -> Cereal.Get [Word8] +getWord8N1_cereal = loop [] where loop s n | s `seq` n `seq` False = undefined loop s 0 = return s loop s n = do s0 <- Cereal.getWord8 - loop (s0+s) (n-1) + loop (s0:s) (n-1) -getWord8N1_atto = loop 0 +getWord8N1_atto :: Int -> A.Parser [Word8] +getWord8N1_atto = loop [] where loop s n | s `seq` n `seq` False = undefined loop s 0 = return s loop s n = do s0 <- A.anyWord8 - loop (s0+s) (n-1) + loop (s0:s) (n-1) -getWord8N2 = loop 0 +getWord8N2 :: Int -> Get [S2] +getWord8N2 = loop [] where loop s n | s `seq` n `seq` False = undefined loop s 0 = return s loop s n = do s0 <- getWord8 s1 <- getWord8 - loop (s0+s1+s) (n-2) + let !v = S2 s0 s1 + loop (v:s) (n-2) -getWord8N2A = loop 0 +getWord8N2A :: Int -> Get [S2] +getWord8N2A = loop [] where loop s n | s `seq` n `seq` False = undefined loop s 0 = return s loop s n = do - v <- (+) <$> getWord8 <*> getWord8 - loop (s+v) (n-2) + !v <- S2 <$> getWord8 <*> getWord8 + loop (v:s) (n-2) -getWord8N4 = loop 0 +getWord8N4 :: Int -> Get [S4] +getWord8N4 = loop [] where loop s n | s `seq` n `seq` False = undefined loop s 0 = return s loop s n = do @@ -241,17 +252,19 @@ getWord8N4 = loop 0 s1 <- getWord8 s2 <- getWord8 s3 <- getWord8 - loop (s+s0+s1+s2+s3) (n-4) + let !v = S4 s0 s1 s2 s3 + loop (v:s) (n-4) -getWord8N4A = loop 0 +getWord8N4A :: Int -> Get [S4] +getWord8N4A = loop [] where loop s n | s `seq` n `seq` False = undefined loop s 0 = return s loop s n = do - let p !s0 !s1 !s2 !s3 = s0 + s1 + s2 + s3 - v <- p <$> getWord8 <*> getWord8 <*> getWord8 <*> getWord8 - loop (s+v) (n-4) + !v <- S4 <$> getWord8 <*> getWord8 <*> getWord8 <*> getWord8 + loop (v:s) (n-4) -getWord8N8 = loop 0 +getWord8N8 :: Int -> Get [S8] +getWord8N8 = loop [] where loop s n | s `seq` n `seq` False = undefined loop s 0 = return s loop s n = do @@ -263,15 +276,15 @@ getWord8N8 = loop 0 s5 <- getWord8 s6 <- getWord8 s7 <- getWord8 - loop (s+s0+s1+s2+s3+s4+s5+s6+s7) (n-8) + let !v = S8 s0 s1 s2 s3 s4 s5 s6 s7 + loop (v:s) (n-8) -getWord8N8A = loop 0 +getWord8N8A :: Int -> Get [S8] +getWord8N8A = loop [] where loop s n | s `seq` n `seq` False = undefined loop s 0 = return s loop s n = do - let p !s0 !s1 !s2 !s3 !s4 !s5 !s6 !s7 = - s0 + s1 + s2 + s3 + s4 + s5 + s6 + s7 - v <- p <$> getWord8 + !v <- S8 <$> getWord8 <*> getWord8 <*> getWord8 <*> getWord8 @@ -279,9 +292,10 @@ getWord8N8A = loop 0 <*> getWord8 <*> getWord8 <*> getWord8 - loop (s+v) (n-8) + loop (v:s) (n-8) -getWord8N16 = loop 0 +getWord8N16 :: Int -> Get [S16] +getWord8N16 = loop [] where loop s n | s `seq` n `seq` False = undefined loop s 0 = return s loop s n = do @@ -301,28 +315,28 @@ getWord8N16 = loop 0 s13 <- getWord8 s14 <- getWord8 s15 <- getWord8 - loop (s+s0+s1+s2+s3+s4+s5+s6+s7+s8+s9+s10+s11+s12+s13+s14+s15) (n-16) + let !v = S16 s0 s1 s2 s3 s4 s5 s6 s7 s8 s9 s10 s11 s12 s13 s14 s15 + loop (v:s) (n-16) -getWord8N16A = loop 0 +getWord8N16A :: Int -> Get [S16] +getWord8N16A = loop [] where loop s n | s `seq` n `seq` False = undefined loop s 0 = return s loop s n = do - let p !s0 !s1 !s2 !s3 !s4 !s5 !s6 !s7 !s8 !s9 !s10 !s11 !s12 !s13 !s14 !s15 = - s0 + s1 + s2 + s3 + s4 + s5 + s6 + s7 + s8 + s9 + s10 + s11 + s12 + s13 + s14 + s15 - !v <- p <$> getWord8 - <*> getWord8 - <*> getWord8 - <*> getWord8 - <*> getWord8 - <*> getWord8 - <*> getWord8 - <*> getWord8 - <*> getWord8 - <*> getWord8 - <*> getWord8 - <*> getWord8 - <*> getWord8 - <*> getWord8 - <*> getWord8 - <*> getWord8 - loop (s+v) (n-16) + !v <- S16 <$> getWord8 + <*> getWord8 + <*> getWord8 + <*> getWord8 + <*> getWord8 + <*> getWord8 + <*> getWord8 + <*> getWord8 + <*> getWord8 + <*> getWord8 + <*> getWord8 + <*> getWord8 + <*> getWord8 + <*> getWord8 + <*> getWord8 + <*> getWord8 + loop (v:s) (n-16) From git at git.haskell.org Wed Dec 16 09:42:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:42:55 +0000 (UTC) Subject: [commit: packages/binary] master: Structure the benchmarks in the the "get" bench in groups. (8c530d7) Message-ID: <20151216094255.6606E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/8c530d7a31c04e54231fad68e89c6cec13233dad >--------------------------------------------------------------- commit 8c530d7a31c04e54231fad68e89c6cec13233dad Author: Lennart Kolmodin Date: Sun Aug 9 18:14:28 2015 +0200 Structure the benchmarks in the the "get" bench in groups. >--------------------------------------------------------------- 8c530d7a31c04e54231fad68e89c6cec13233dad benchmarks/Get.hs | 91 ++++++++++++++++++++++++++++++------------------------- 1 file changed, 50 insertions(+), 41 deletions(-) diff --git a/benchmarks/Get.hs b/benchmarks/Get.hs index de0a19f..26c2f98 100644 --- a/benchmarks/Get.hs +++ b/benchmarks/Get.hs @@ -39,47 +39,56 @@ main = do rnf oneMegabyteLBS ] defaultMain - [ - bench "brackets 100kb one chunk input" $ - whnf (checkBracket . runTest bracketParser) brackets - , bench "brackets 100kb in 100 byte chunks" $ - whnf (checkBracket . runTest bracketParser) bracketsInChunks - , bench "Attoparsec lazy-bs brackets 100kb one chunk" $ - whnf (checkBracket . runAttoL bracketParser_atto) brackets - , bench "Attoparsec lazy-bs brackets 100kb in 100 byte chunks" $ - whnf (checkBracket . runAttoL bracketParser_atto) bracketsInChunks - , bench "Attoparsec strict-bs brackets 100kb" $ - whnf (checkBracket . runAtto bracketParser_atto) $ S.concat (L.toChunks brackets) - , bench "Cereal strict-bs brackets 100kb" $ - whnf (checkBracket . runCereal bracketParser_cereal) $ S.concat (L.toChunks brackets) - , bench "Binary getStruct4 1MB struct of 4 word8" $ - whnf (runTest (getStruct4 mega)) oneMegabyteLBS - , bench "Cereal getStruct4 1MB struct of 4 word8" $ - whnf (runCereal (getStruct4_cereal mega)) oneMegabyte - , bench "Attoparsec getStruct4 1MB struct of 4 word8" $ - whnf (runAtto (getStruct4_atto mega)) oneMegabyte - , bench "Binary getWord8 1MB chunk size 1 byte" $ - whnf (runTest (getWord8N1 mega)) oneMegabyteLBS - , bench "Cereal getWord8 1MB chunk size 1 byte" $ - whnf (runCereal (getWord8N1_cereal mega)) oneMegabyte - , bench "Attoparsec getWord8 1MB chunk size 1 byte" $ - whnf (runAtto (getWord8N1_atto mega)) oneMegabyte - , bench "getWord8 1MB chunk size 2 bytes" $ - whnf (runTest (getWord8N2 mega)) oneMegabyteLBS - , bench "getWord8 1MB chunk size 4 bytes" $ - whnf (runTest (getWord8N4 mega)) oneMegabyteLBS - , bench "getWord8 1MB chunk size 8 bytes" $ - whnf (runTest (getWord8N8 mega)) oneMegabyteLBS - , bench "getWord8 1MB chunk size 16 bytes" $ - whnf (runTest (getWord8N16 mega)) oneMegabyteLBS - , bench "getWord8 1MB chunk size 2 bytes Applicative" $ - whnf (runTest (getWord8N2A mega)) oneMegabyteLBS - , bench "getWord8 1MB chunk size 4 bytes Applicative" $ - whnf (runTest (getWord8N4A mega)) oneMegabyteLBS - , bench "getWord8 1MB chunk size 8 bytes Applicative" $ - whnf (runTest (getWord8N8A mega)) oneMegabyteLBS - , bench "getWord8 1MB chunk size 16 bytes Applicative" $ - whnf (runTest (getWord8N16A mega)) oneMegabyteLBS + [ bgroup "brackets" + [ bench "Binary 100kb, one chunk" $ + whnf (checkBracket . runTest bracketParser) brackets + , bench "Binary 100kb, 100 byte chunks" $ + whnf (checkBracket . runTest bracketParser) bracketsInChunks + , bench "Attoparsec lazy-bs 100kb, one chunk" $ + whnf (checkBracket . runAttoL bracketParser_atto) brackets + , bench "Attoparsec lazy-bs 100kb, 100 byte chunks" $ + whnf (checkBracket . runAttoL bracketParser_atto) bracketsInChunks + , bench "Attoparsec strict-bs 100kb" $ + whnf (checkBracket . runAtto bracketParser_atto) $ S.concat (L.toChunks brackets) + , bench "Cereal strict-bs 100kb" $ + whnf (checkBracket . runCereal bracketParser_cereal) $ S.concat (L.toChunks brackets) + ] + , bgroup "comparison getStruct4, 1MB of struct of 4 Word8s" + [ bench "Attoparsec" $ + whnf (runAtto (getStruct4_atto mega)) oneMegabyte + , bench "Binary" $ + whnf (runTest (getStruct4 mega)) oneMegabyteLBS + , bench "Cereal" $ + whnf (runCereal (getStruct4_cereal mega)) oneMegabyte + ] + , bgroup "comparison getWord8, 1MB" + [ bench "Attoparsec" $ + whnf (runAtto (getWord8N1_atto mega)) oneMegabyte + , bench "Binary" $ + whnf (runTest (getWord8N1 mega)) oneMegabyteLBS + , bench "Cereal" $ + whnf (runCereal (getWord8N1_cereal mega)) oneMegabyte + ] + , bgroup "getWord8 1MB" + [ bench "chunk size 2 bytes" $ + whnf (runTest (getWord8N2 mega)) oneMegabyteLBS + , bench "chunk size 4 bytes" $ + whnf (runTest (getWord8N4 mega)) oneMegabyteLBS + , bench "chunk size 8 bytes" $ + whnf (runTest (getWord8N8 mega)) oneMegabyteLBS + , bench "chunk size 16 bytes" $ + whnf (runTest (getWord8N16 mega)) oneMegabyteLBS + ] + , bgroup "getWord8 1MB Applicative" + [ bench "chunk size 2 bytes" $ + whnf (runTest (getWord8N2A mega)) oneMegabyteLBS + , bench "chunk size 4 bytes" $ + whnf (runTest (getWord8N4A mega)) oneMegabyteLBS + , bench "chunk size 8 bytes" $ + whnf (runTest (getWord8N8A mega)) oneMegabyteLBS + , bench "chunk size 16 bytes" $ + whnf (runTest (getWord8N16A mega)) oneMegabyteLBS + ] ] checkBracket :: Int -> Int From git at git.haskell.org Wed Dec 16 09:42:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:42:57 +0000 (UTC) Subject: [commit: packages/binary] master: Compile benchmark get with -Wall. (b72bd25) Message-ID: <20151216094257.6D0143A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/b72bd25c690fcb073c71664df2e3e0d238096a54 >--------------------------------------------------------------- commit b72bd25c690fcb073c71664df2e3e0d238096a54 Author: Lennart Kolmodin Date: Thu Aug 13 22:12:11 2015 +0200 Compile benchmark get with -Wall. >--------------------------------------------------------------- b72bd25c690fcb073c71664df2e3e0d238096a54 binary.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/binary.cabal b/binary.cabal index c88993b..cf9955e 100644 --- a/binary.cabal +++ b/binary.cabal @@ -120,7 +120,7 @@ benchmark get mtl -- build dependencies from using binary source rather than depending on the library build-depends: array, containers - ghc-options: -O2 + ghc-options: -O2 -Wall benchmark builder type: exitcode-stdio-1.0 From git at git.haskell.org Wed Dec 16 09:42:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:42:59 +0000 (UTC) Subject: [commit: packages/binary] master: Add benchmark for Generic generated Binary instances. (6ab893a) Message-ID: <20151216094259.76A233A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/6ab893a8decbabacb3a7c076d9d2f427ed07902c >--------------------------------------------------------------- commit 6ab893a8decbabacb3a7c076d9d2f427ed07902c Author: Lennart Kolmodin Date: Thu Aug 13 22:25:19 2015 +0200 Add benchmark for Generic generated Binary instances. We use Cabal's PackageDescription as the type to serialize. It is large, has many levels of data types, and also uses enums and strings. It's a good stress test. GenericsBench defines criterion benchmarks for serialization and deserialization. In GenericsBenchTypes we derive the Binary instances. PackageDescription already defines Binary instances for the system installed Binary, but naturally this won't work for the benchmark - we need our own instances that are derived from the code in this library. The data to serialize we get from your .cabal/package/hackage.haskell.org/ directory, it's data from hackage, not autogenerated. GenericsBenchCache makes sure that if we rerun the benchmark we will use the same PackageDescriptions, even if the user has executed 'cabal update' since the last benchmark run. >--------------------------------------------------------------- 6ab893a8decbabacb3a7c076d9d2f427ed07902c benchmarks/GenericsBench.hs | 52 ++++++++++++++++++++++++ benchmarks/GenericsBenchCache.hs | 86 ++++++++++++++++++++++++++++++++++++++++ benchmarks/GenericsBenchTypes.hs | 47 ++++++++++++++++++++++ binary.cabal | 27 +++++++++++++ 4 files changed, 212 insertions(+) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 6ab893a8decbabacb3a7c076d9d2f427ed07902c From git at git.haskell.org Wed Dec 16 09:43:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:43:01 +0000 (UTC) Subject: [commit: packages/binary] master: Add new deps to .travis.yml file. (160246b) Message-ID: <20151216094301.7BDD43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/160246b8967de544d39d6218ffe41f7f4d21d28a >--------------------------------------------------------------- commit 160246b8967de544d39d6218ffe41f7f4d21d28a Author: Lennart Kolmodin Date: Thu Aug 13 22:39:01 2015 +0200 Add new deps to .travis.yml file. Due to the dependency cycle we need to manually preinstall all deps before we attempt to configure/build binary. >--------------------------------------------------------------- 160246b8967de544d39d6218ffe41f7f4d21d28a .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index d77d543..bec9245 100644 --- a/.travis.yml +++ b/.travis.yml @@ -17,7 +17,7 @@ install: - cabal update - cabal sandbox init # can't use "cabal install --only-dependencies --enable-tests --enable-benchmarks" due to dep-cycle - - cabal install criterion deepseq mtl "QuickCheck >= 2.8" HUnit "test-framework-quickcheck2 >= 0.3" "random >= 1.0.1.0" attoparsec cereal -j + - cabal install criterion deepseq mtl "QuickCheck >= 2.8" HUnit "test-framework-quickcheck2 >= 0.3" "random >= 1.0.1.0" attoparsec cereal 'Cabal == 1.22.*' tar zlib -j script: - cabal configure --enable-tests --enable-benchmarks -v2 --ghc-options=-fno-spec-constr From git at git.haskell.org Wed Dec 16 09:43:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:43:03 +0000 (UTC) Subject: [commit: packages/binary] master: Conditionally include <$> for older GHC versions. (5a91e0d) Message-ID: <20151216094303.817233A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/5a91e0d8b7ef5150b268b52536751f44c4a9a052 >--------------------------------------------------------------- commit 5a91e0d8b7ef5150b268b52536751f44c4a9a052 Author: Lennart Kolmodin Date: Fri Aug 14 12:56:59 2015 +0200 Conditionally include <$> for older GHC versions. >--------------------------------------------------------------- 5a91e0d8b7ef5150b268b52536751f44c4a9a052 benchmarks/GenericsBenchCache.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/benchmarks/GenericsBenchCache.hs b/benchmarks/GenericsBenchCache.hs index 1b6f041..d65e731 100644 --- a/benchmarks/GenericsBenchCache.hs +++ b/benchmarks/GenericsBenchCache.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveGeneric, StandaloneDeriving, BangPatterns #-} +{-# LANGUAGE DeriveGeneric, StandaloneDeriving, BangPatterns, CPP #-} module GenericsBenchCache (readPackageDescriptionCache) where import qualified Text.ParserCombinators.ReadP as Read @@ -20,6 +20,9 @@ import System.Exit import GenericsBenchTypes () +#if ! MIN_VERSION_base(4,8,0) +import Control.Applicative ((<$>)) +#endif readTar :: String -> Int -> IO [PackageDescription] readTar tarPath limit = do From git at git.haskell.org Wed Dec 16 09:43:05 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:43:05 +0000 (UTC) Subject: [commit: packages/binary] master: Conditionally include Control.Applicative for older GHC versions. (e07fccb) Message-ID: <20151216094305.884FF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/e07fccbe9935b0e7a0c1487bdae40cb0c1706656 >--------------------------------------------------------------- commit e07fccbe9935b0e7a0c1487bdae40cb0c1706656 Author: Lennart Kolmodin Date: Fri Aug 14 22:22:42 2015 +0200 Conditionally include Control.Applicative for older GHC versions. >--------------------------------------------------------------- e07fccbe9935b0e7a0c1487bdae40cb0c1706656 tests/File.hs | 18 +++++++++++------- 1 file changed, 11 insertions(+), 7 deletions(-) diff --git a/tests/File.hs b/tests/File.hs index 1998bc6..1ec631b 100644 --- a/tests/File.hs +++ b/tests/File.hs @@ -1,14 +1,18 @@ +{-# LANGUAGE CPP #-} module Main where -import Control.Applicative -import Test.HUnit -import System.Directory ( getTemporaryDirectory ) -import System.FilePath ( () ) +#if ! MIN_VERSION_base(4,8,0) +import Control.Applicative +#endif -import Distribution.Simple.Utils ( withTempDirectory ) -import Distribution.Verbosity ( silent ) +import System.Directory (getTemporaryDirectory) +import System.FilePath (()) +import Test.HUnit -import Data.Binary +import Distribution.Simple.Utils (withTempDirectory) +import Distribution.Verbosity (silent) + +import Data.Binary data Foo = Bar !Word32 !Word32 !Word32 deriving (Eq, Show) From git at git.haskell.org Wed Dec 16 09:43:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:43:07 +0000 (UTC) Subject: [commit: packages/binary] master: Conditionally include Data.Monoid for older GHC versions. (f9ff5c3) Message-ID: <20151216094307.8EFC03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/f9ff5c36f46f4f6d12baf5ab2fce7d553dba712f >--------------------------------------------------------------- commit f9ff5c36f46f4f6d12baf5ab2fce7d553dba712f Author: Lennart Kolmodin Date: Fri Aug 14 22:30:16 2015 +0200 Conditionally include Data.Monoid for older GHC versions. >--------------------------------------------------------------- f9ff5c36f46f4f6d12baf5ab2fce7d553dba712f benchmarks/Builder.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/benchmarks/Builder.hs b/benchmarks/Builder.hs index 042b371..71a202f 100644 --- a/benchmarks/Builder.hs +++ b/benchmarks/Builder.hs @@ -6,6 +6,10 @@ module Main (main) where +#if ! MIN_VERSION_base(4,8,0) +import Data.Monoid (Monoid(mappend, mempty)) +#endif + import Control.DeepSeq import Control.Exception (evaluate) import Control.Monad.Trans (liftIO) @@ -14,7 +18,6 @@ import qualified Data.ByteString as S import qualified Data.ByteString.Char8 as C import qualified Data.ByteString.Lazy as L import Data.Char (ord) -import Data.Monoid (Monoid(mappend, mempty)) import Data.Word (Word8) import Data.Binary.Builder From git at git.haskell.org Wed Dec 16 09:43:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:43:09 +0000 (UTC) Subject: [commit: packages/binary] master: Remove unused import. (9f74d40) Message-ID: <20151216094309.967DA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/9f74d402ce304f58644ee0f56f98d87653a39500 >--------------------------------------------------------------- commit 9f74d402ce304f58644ee0f56f98d87653a39500 Author: Lennart Kolmodin Date: Fri Aug 14 22:31:00 2015 +0200 Remove unused import. >--------------------------------------------------------------- 9f74d402ce304f58644ee0f56f98d87653a39500 benchmarks/Builder.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/benchmarks/Builder.hs b/benchmarks/Builder.hs index 71a202f..ad08e16 100644 --- a/benchmarks/Builder.hs +++ b/benchmarks/Builder.hs @@ -12,7 +12,6 @@ import Data.Monoid (Monoid(mappend, mempty)) import Control.DeepSeq import Control.Exception (evaluate) -import Control.Monad.Trans (liftIO) import Criterion.Main import qualified Data.ByteString as S import qualified Data.ByteString.Char8 as C From git at git.haskell.org Wed Dec 16 09:43:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:43:11 +0000 (UTC) Subject: [commit: packages/binary] master: benchmark builder: Specify Int as we otherwise default to Integer. (0388304) Message-ID: <20151216094311.9C2B93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/038830410c1880e337cbfd85343ca78d07b11180 >--------------------------------------------------------------- commit 038830410c1880e337cbfd85343ca78d07b11180 Author: Lennart Kolmodin Date: Fri Aug 14 22:31:12 2015 +0200 benchmark builder: Specify Int as we otherwise default to Integer. The benchmark executes 25% faster, time which could not be attribute to the speed of binary itself. >--------------------------------------------------------------- 038830410c1880e337cbfd85343ca78d07b11180 benchmarks/Builder.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/benchmarks/Builder.hs b/benchmarks/Builder.hs index ad08e16..3c48e7b 100644 --- a/benchmarks/Builder.hs +++ b/benchmarks/Builder.hs @@ -86,7 +86,7 @@ from4Word8s (x:xs) = singleton x <> singleton x <> singleton x <> singleton x <> -- Write 100 short, length-prefixed ByteStrings. lengthPrefixedBS :: S.ByteString -> Builder -lengthPrefixedBS bs = loop 100 +lengthPrefixedBS bs = loop (100 :: Int) where loop n | n `seq` False = undefined loop 0 = mempty loop n = From git at git.haskell.org Wed Dec 16 09:43:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:43:13 +0000 (UTC) Subject: [commit: packages/binary] master: Optimize roll by using foldl' instead of foldr (1f643cb) Message-ID: <20151216094313.A271F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/1f643cbc973751605ec6a3ed0d93a6dab0bd0774 >--------------------------------------------------------------- commit 1f643cbc973751605ec6a3ed0d93a6dab0bd0774 Author: Bas van Dijk Date: Mon Sep 28 22:39:28 2015 +0200 Optimize roll by using foldl' instead of foldr The "roll" benchmarks in the get executable show the difference: get roll benchmarking roll/foldr time 547.4 ms (537.8 ms .. 553.5 ms) 1.000 R? (1.000 R? .. 1.000 R?) mean 549.4 ms (547.2 ms .. 550.4 ms) std dev 1.857 ms (0.0 s .. 1.896 ms) variance introduced by outliers: 19% (moderately inflated) benchmarking roll/foldl' time 434.7 ms (426.4 ms .. 443.1 ms) 1.000 R? (1.000 R? .. 1.000 R?) mean 433.7 ms (432.3 ms .. 434.7 ms) std dev 1.472 ms (0.0 s .. 1.696 ms) variance introduced by outliers: 19% (moderately inflated) The "Integer/decode" benchmark shows the actual decoding speed. First the old implementation based on foldr: get Integer/decode benchmarking Integer/decode time 552.9 ms (540.2 ms .. 569.3 ms) 1.000 R? (1.000 R? .. 1.000 R?) mean 558.2 ms (556.1 ms .. 559.3 ms) std dev 1.824 ms (0.0 s .. 1.906 ms) variance introduced by outliers: 19% (moderately inflated) The new implementation based on foldl': get Integer/decode benchmarking Integer/decode time 457.5 ms (406.2 ms .. 505.6 ms) 0.998 R? (0.994 R? .. 1.000 R?) mean 455.9 ms (448.3 ms .. 462.3 ms) std dev 10.11 ms (0.0 s .. 11.02 ms) variance introduced by outliers: 19% (moderately inflated) >--------------------------------------------------------------- 1f643cbc973751605ec6a3ed0d93a6dab0bd0774 benchmarks/Get.hs | 34 ++++++++++++++++++++++++++++++++-- src/Data/Binary/Class.hs | 6 +++--- 2 files changed, 35 insertions(+), 5 deletions(-) diff --git a/benchmarks/Get.hs b/benchmarks/Get.hs index 26c2f98..191f585 100644 --- a/benchmarks/Get.hs +++ b/benchmarks/Get.hs @@ -12,10 +12,12 @@ import Criterion.Main import qualified Data.ByteString as S import qualified Data.ByteString.Char8 as C8 import qualified Data.ByteString.Lazy as L +import Data.Bits import Data.Char (ord) -import Data.Word (Word8) +import Data.List (foldl') import Control.Applicative +import Data.Binary import Data.Binary.Get import qualified Data.Serialize.Get as Cereal @@ -36,7 +38,9 @@ main = do rnf bracketsInChunks, rnf bracketCount, rnf oneMegabyte, - rnf oneMegabyteLBS + rnf oneMegabyteLBS, + rnf manyBytes, + rnf encodedBigInteger ] defaultMain [ bgroup "brackets" @@ -89,6 +93,13 @@ main = do , bench "chunk size 16 bytes" $ whnf (runTest (getWord8N16A mega)) oneMegabyteLBS ] + , bgroup "roll" + [ bench "foldr" $ nf (roll_foldr :: [Word8] -> Integer) manyBytes + , bench "foldl'" $ nf (roll_foldl' :: [Word8] -> Integer) manyBytes + ] + , bgroup "Integer" + [ bench "decode" $ nf (decode :: L.ByteString -> Integer) encodedBigInteger + ] ] checkBracket :: Int -> Int @@ -349,3 +360,22 @@ getWord8N16A = loop [] <*> getWord8 <*> getWord8 loop (v:s) (n-16) + +manyBytes :: [Word8] +manyBytes = concat $ replicate 256 [0..255] + +bigInteger :: Integer +bigInteger = roll_foldl' manyBytes + +encodedBigInteger :: L.ByteString +encodedBigInteger = encode bigInteger + +roll_foldr :: (Integral a, Num a, Bits a) => [Word8] -> a +roll_foldr = foldr unstep 0 + where + unstep b a = a `shiftL` 8 .|. fromIntegral b + +roll_foldl' :: (Integral a, Num a, Bits a) => [Word8] -> a +roll_foldl' = foldl' unstep 0 . reverse + where + unstep a b = a `shiftL` 8 .|. fromIntegral b diff --git a/src/Data/Binary/Class.hs b/src/Data/Binary/Class.hs index 37117f7..b0f7529 100644 --- a/src/Data/Binary/Class.hs +++ b/src/Data/Binary/Class.hs @@ -53,7 +53,7 @@ import Data.ByteString.Lazy (ByteString) import qualified Data.ByteString.Lazy as L import Data.Char (ord) -import Data.List (unfoldr) +import Data.List (unfoldr, foldl') -- And needed for the instances: import qualified Data.ByteString as B @@ -249,9 +249,9 @@ unroll = unfoldr step step i = Just (fromIntegral i, i `shiftR` 8) roll :: (Integral a, Num a, Bits a) => [Word8] -> a -roll = foldr unstep 0 +roll = foldl' unstep 0 . reverse where - unstep b a = a `shiftL` 8 .|. fromIntegral b + unstep a b = a `shiftL` 8 .|. fromIntegral b #ifdef HAS_NATURAL -- Fixed-size type for a subset of Natural From git at git.haskell.org Wed Dec 16 09:43:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:43:15 +0000 (UTC) Subject: [commit: packages/binary] master: Add Binary Version instance (48c1250) Message-ID: <20151216094315.A9C173A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/48c12500ae34ad6e0d8e23edf81a8d3564bfdb48 >--------------------------------------------------------------- commit 48c12500ae34ad6e0d8e23edf81a8d3564bfdb48 Author: Oleg Grenrus Date: Fri Oct 2 13:10:49 2015 +0300 Add Binary Version instance >--------------------------------------------------------------- 48c12500ae34ad6e0d8e23edf81a8d3564bfdb48 src/Data/Binary/Class.hs | 13 +++++++++++++ 1 file changed, 13 insertions(+) diff --git a/src/Data/Binary/Class.hs b/src/Data/Binary/Class.hs index 37117f7..5aacb5f 100644 --- a/src/Data/Binary/Class.hs +++ b/src/Data/Binary/Class.hs @@ -86,6 +86,8 @@ import qualified Data.Foldable as Fold import GHC.Fingerprint #endif +import Data.Version (Version(..)) + ------------------------------------------------------------------------ #ifdef GENERICS @@ -606,3 +608,14 @@ instance Binary Fingerprint where x2 <- get return $! Fingerprint x1 x2 #endif + +------------------------------------------------------------------------ +-- Version + +-- | /Since: binary-0.8/ +instance Binary Version where + get = do + br <- get + tags <- get + return $ Version br tags + put (Version br tags) = put br >> put tags From git at git.haskell.org Wed Dec 16 09:43:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:43:17 +0000 (UTC) Subject: [commit: packages/binary] master: Merge pull request #86 from basvandijk/optimize-roll (63d7834) Message-ID: <20151216094317.B13B93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/63d7834f171624113094a4cff6613c9b869699af >--------------------------------------------------------------- commit 63d7834f171624113094a4cff6613c9b869699af Merge: 0388304 1f643cb Author: Lennart Kolmodin Date: Tue Oct 6 15:40:17 2015 +0200 Merge pull request #86 from basvandijk/optimize-roll Optimize roll by using foldl' instead of foldr >--------------------------------------------------------------- 63d7834f171624113094a4cff6613c9b869699af benchmarks/Get.hs | 34 ++++++++++++++++++++++++++++++++-- src/Data/Binary/Class.hs | 6 +++--- 2 files changed, 35 insertions(+), 5 deletions(-) From git at git.haskell.org Wed Dec 16 09:43:19 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:43:19 +0000 (UTC) Subject: [commit: packages/binary] master: Add Binary Void instance (57cf1f0) Message-ID: <20151216094319.B84F13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/57cf1f0460fdc27b8f5783749c90201503a7a87a >--------------------------------------------------------------- commit 57cf1f0460fdc27b8f5783749c90201503a7a87a Author: Brian McKenna Date: Fri Oct 23 14:44:31 2015 +1100 Add Binary Void instance This is so that we can write and read things like [Void], or (Expr Void) - something I'm actually doing in Morte. https://github.com/Gabriel439/Haskell-Morte-Library/pull/26 The reader always fails if you actually try to get an instance of it. Trying to access a void value should not happen for well-formed instances, for example: *Data.Binary Data.Void> decode $ encode ([] :: [Void]) :: [Void] [] >--------------------------------------------------------------- 57cf1f0460fdc27b8f5783749c90201503a7a87a binary.cabal | 4 ++++ src/Data/Binary/Class.hs | 7 +++++++ 2 files changed, 11 insertions(+) diff --git a/binary.cabal b/binary.cabal index 37ed51c..503e588 100644 --- a/binary.cabal +++ b/binary.cabal @@ -50,6 +50,10 @@ library -- prior to ghc-7.4 generics lived in ghc-prim build-depends: ghc-prim + if impl(ghc <= 7.8) + -- Data.Void was moved to base for 7.10 + build-depends: void + ghc-options: -O2 -Wall -fliberate-case-threshold=1000 -- Due to circular dependency, we cannot make any of the test-suites or diff --git a/src/Data/Binary/Class.hs b/src/Data/Binary/Class.hs index b0f7529..9984a93 100644 --- a/src/Data/Binary/Class.hs +++ b/src/Data/Binary/Class.hs @@ -43,6 +43,7 @@ module Data.Binary.Class ( import Data.Word import Data.Bits import Data.Int +import Data.Void import Data.Binary.Put import Data.Binary.Get @@ -128,6 +129,12 @@ class Binary t where ------------------------------------------------------------------------ -- Simple instances +-- Void never gets written nor reconstructed since it's impossible to have a +-- value of that type +instance Binary Void where + put = absurd + get = mzero + -- The () type need never be written to disk: values of singleton type -- can be reconstructed from the type alone instance Binary () where From git at git.haskell.org Wed Dec 16 09:43:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:43:21 +0000 (UTC) Subject: [commit: packages/binary] master: Use Travis CI containers. (bf75741) Message-ID: <20151216094321.BE1713A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/bf757416875b1683345e6d55f2dcad3a9b0ae00e >--------------------------------------------------------------- commit bf757416875b1683345e6d55f2dcad3a9b0ae00e Author: Lennart Kolmodin Date: Thu Oct 29 17:20:56 2015 +0100 Use Travis CI containers. >--------------------------------------------------------------- bf757416875b1683345e6d55f2dcad3a9b0ae00e .travis.yml | 31 +++++++++++++++++++++---------- 1 file changed, 21 insertions(+), 10 deletions(-) diff --git a/.travis.yml b/.travis.yml index bec9245..56097f2 100644 --- a/.travis.yml +++ b/.travis.yml @@ -1,20 +1,31 @@ -# NB: don't set `language: haskell` here # See https://github.com/hvr/multi-ghc-travis for more information -env: - - CABALVER=1.18 GHCVER=7.4.2 - - CABALVER=1.18 GHCVER=7.6.3 - - CABALVER=1.18 GHCVER=7.8.4 - - CABALVER=1.22 GHCVER=7.10.2 +language: c + +sudo: false + +matrix: + include: + - env: CABALVER=1.18 GHCVER=7.4.2 + addons: {apt: {packages: [cabal-install-1.18,ghc-7.4.2], sources: [hvr-ghc]}} + - env: CABALVER=1.18 GHCVER=7.6.3 + addons: {apt: {packages: [cabal-install-1.18,ghc-7.6.3], sources: [hvr-ghc]}} + - env: CABALVER=1.18 GHCVER=7.8.4 + addons: {apt: {packages: [cabal-install-1.18,ghc-7.8.4], sources: [hvr-ghc]}} + - env: CABALVER=1.22 GHCVER=7.10.2 + addons: {apt: {packages: [cabal-install-1.22,ghc-7.10.2], sources: [hvr-ghc]}} + - env: CABALVER=head GHCVER=head + addons: {apt: {packages: [cabal-install-head,ghc-head], sources: [hvr-ghc]}} + + allow_failures: + - env: CABALVER=head GHCVER=head before_install: - - sudo add-apt-repository -y ppa:hvr/ghc - - sudo apt-get update - - sudo apt-get install cabal-install-$CABALVER ghc-$GHCVER - export PATH=/opt/ghc/$GHCVER/bin:/opt/cabal/$CABALVER/bin:$PATH install: - - cabal update + - cabal --version + - travis_retry cabal update - cabal sandbox init # can't use "cabal install --only-dependencies --enable-tests --enable-benchmarks" due to dep-cycle - cabal install criterion deepseq mtl "QuickCheck >= 2.8" HUnit "test-framework-quickcheck2 >= 0.3" "random >= 1.0.1.0" attoparsec cereal 'Cabal == 1.22.*' tar zlib -j From git at git.haskell.org Wed Dec 16 09:43:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:43:23 +0000 (UTC) Subject: [commit: packages/binary] master: Attempt to reduce compile time on Travis CI. (0b7abd9) Message-ID: <20151216094323.C385E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/0b7abd9f8e168382babc43e57621ea25daaa8c4e >--------------------------------------------------------------- commit 0b7abd9f8e168382babc43e57621ea25daaa8c4e Author: Lennart Kolmodin Date: Thu Oct 29 18:14:00 2015 +0100 Attempt to reduce compile time on Travis CI. As suggested at https://github.com/hvr/multi-ghc-travis, reduce the effect of bug https://ghc.haskell.org/trac/ghc/ticket/9221. >--------------------------------------------------------------- 0b7abd9f8e168382babc43e57621ea25daaa8c4e .travis.yml | 2 ++ 1 file changed, 2 insertions(+) diff --git a/.travis.yml b/.travis.yml index 56097f2..cf16df1 100644 --- a/.travis.yml +++ b/.travis.yml @@ -26,6 +26,8 @@ before_install: install: - cabal --version - travis_retry cabal update +# workaround for https://ghc.haskell.org/trac/ghc/ticket/9221 + - sed -i 's/^jobs:/-- jobs:/' ${HOME}/.cabal/config - cabal sandbox init # can't use "cabal install --only-dependencies --enable-tests --enable-benchmarks" due to dep-cycle - cabal install criterion deepseq mtl "QuickCheck >= 2.8" HUnit "test-framework-quickcheck2 >= 0.3" "random >= 1.0.1.0" attoparsec cereal 'Cabal == 1.22.*' tar zlib -j From git at git.haskell.org Wed Dec 16 09:43:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:43:25 +0000 (UTC) Subject: [commit: packages/binary] master: Only support Void for >= GHC 7.10. (0adaed9) Message-ID: <20151216094325.CB32A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/0adaed92127dde38d5fd9ad584b0e2215f0eb09a >--------------------------------------------------------------- commit 0adaed92127dde38d5fd9ad584b0e2215f0eb09a Author: Lennart Kolmodin Date: Wed Nov 11 11:12:14 2015 +0100 Only support Void for >= GHC 7.10. >--------------------------------------------------------------- 0adaed92127dde38d5fd9ad584b0e2215f0eb09a binary.cabal | 4 ---- src/Data/Binary/Class.hs | 5 +++++ 2 files changed, 5 insertions(+), 4 deletions(-) diff --git a/binary.cabal b/binary.cabal index 503e588..37ed51c 100644 --- a/binary.cabal +++ b/binary.cabal @@ -50,10 +50,6 @@ library -- prior to ghc-7.4 generics lived in ghc-prim build-depends: ghc-prim - if impl(ghc <= 7.8) - -- Data.Void was moved to base for 7.10 - build-depends: void - ghc-options: -O2 -Wall -fliberate-case-threshold=1000 -- Due to circular dependency, we cannot make any of the test-suites or diff --git a/src/Data/Binary/Class.hs b/src/Data/Binary/Class.hs index 9984a93..a022a42 100644 --- a/src/Data/Binary/Class.hs +++ b/src/Data/Binary/Class.hs @@ -8,6 +8,7 @@ #if MIN_VERSION_base(4,8,0) #define HAS_NATURAL +#define HAS_VOID #endif #if __GLASGOW_HASKELL__ >= 704 @@ -43,7 +44,9 @@ module Data.Binary.Class ( import Data.Word import Data.Bits import Data.Int +#ifdef HAS_VOID import Data.Void +#endif import Data.Binary.Put import Data.Binary.Get @@ -129,11 +132,13 @@ class Binary t where ------------------------------------------------------------------------ -- Simple instances +#ifdef HAS_VOID -- Void never gets written nor reconstructed since it's impossible to have a -- value of that type instance Binary Void where put = absurd get = mzero +#endif -- The () type need never be written to disk: values of singleton type -- can be reconstructed from the type alone From git at git.haskell.org Wed Dec 16 09:43:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:43:27 +0000 (UTC) Subject: [commit: packages/binary] master: Merge branch 'feature/void-binary-instance' (db20135) Message-ID: <20151216094327.D17093A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/db201353ed55c9392670a927a9caaed66035b6c7 >--------------------------------------------------------------- commit db201353ed55c9392670a927a9caaed66035b6c7 Merge: 0b7abd9 0adaed9 Author: Lennart Kolmodin Date: Wed Nov 11 11:51:36 2015 +0100 Merge branch 'feature/void-binary-instance' >--------------------------------------------------------------- db201353ed55c9392670a927a9caaed66035b6c7 src/Data/Binary/Class.hs | 12 ++++++++++++ 1 file changed, 12 insertions(+) From git at git.haskell.org Wed Dec 16 09:43:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:43:29 +0000 (UTC) Subject: [commit: packages/binary] master: Use applicative form in 'get' for Version. (67ccd53) Message-ID: <20151216094329.D7F2F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/67ccd5398f199f3e92cc7c34dcf0fa47d41c3011 >--------------------------------------------------------------- commit 67ccd5398f199f3e92cc7c34dcf0fa47d41c3011 Author: Lennart Kolmodin Date: Wed Nov 11 16:05:39 2015 +0100 Use applicative form in 'get' for Version. >--------------------------------------------------------------- 67ccd5398f199f3e92cc7c34dcf0fa47d41c3011 src/Data/Binary/Class.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/src/Data/Binary/Class.hs b/src/Data/Binary/Class.hs index 5aacb5f..eb11cb4 100644 --- a/src/Data/Binary/Class.hs +++ b/src/Data/Binary/Class.hs @@ -47,6 +47,9 @@ import Data.Int import Data.Binary.Put import Data.Binary.Get +#if ! MIN_VERSION_base(4,8,0) +import Control.Applicative +#endif import Control.Monad import Data.ByteString.Lazy (ByteString) @@ -614,8 +617,5 @@ instance Binary Fingerprint where -- | /Since: binary-0.8/ instance Binary Version where - get = do - br <- get - tags <- get - return $ Version br tags + get = Version <$> get <*> get put (Version br tags) = put br >> put tags From git at git.haskell.org Wed Dec 16 09:43:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:43:31 +0000 (UTC) Subject: [commit: packages/binary] master: Merge branch 'phadej/version' (6c5d126) Message-ID: <20151216094331.E01693A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/6c5d12623fabee47d044ca3532574c13c7c26c9c >--------------------------------------------------------------- commit 6c5d12623fabee47d044ca3532574c13c7c26c9c Merge: db20135 67ccd53 Author: Lennart Kolmodin Date: Wed Nov 11 16:06:23 2015 +0100 Merge branch 'phadej/version' >--------------------------------------------------------------- 6c5d12623fabee47d044ca3532574c13c7c26c9c src/Data/Binary/Class.hs | 13 +++++++++++++ 1 file changed, 13 insertions(+) From git at git.haskell.org Wed Dec 16 09:43:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:43:33 +0000 (UTC) Subject: [commit: packages/binary] master: Remove duplicate Binary instance of Version. (abc306b) Message-ID: <20151216094333.E57A53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/abc306b5f7bdd8fff2fa95781c458d23491ee66f >--------------------------------------------------------------- commit abc306b5f7bdd8fff2fa95781c458d23491ee66f Author: Lennart Kolmodin Date: Wed Nov 11 17:26:52 2015 +0100 Remove duplicate Binary instance of Version. >--------------------------------------------------------------- abc306b5f7bdd8fff2fa95781c458d23491ee66f benchmarks/GenericsBenchTypes.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/benchmarks/GenericsBenchTypes.hs b/benchmarks/GenericsBenchTypes.hs index 4aeb7ba..65f1efa 100644 --- a/benchmarks/GenericsBenchTypes.hs +++ b/benchmarks/GenericsBenchTypes.hs @@ -43,5 +43,4 @@ instance Binary SourceRepo instance Binary TestSuite instance Binary TestSuiteInterface instance Binary TestType -instance Binary Version instance Binary VersionRange From git at git.haskell.org Wed Dec 16 09:43:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:43:35 +0000 (UTC) Subject: [commit: packages/binary] master: Bump version to 0.8.0.0 (43ee092) Message-ID: <20151216094335.EB1923A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/43ee092f022517222e1573f9c9468aa0b6a2cc00 >--------------------------------------------------------------- commit 43ee092f022517222e1573f9c9468aa0b6a2cc00 Author: Oleg Grenrus Date: Thu Nov 12 06:34:22 2015 +0200 Bump version to 0.8.0.0 >--------------------------------------------------------------- 43ee092f022517222e1573f9c9468aa0b6a2cc00 binary.cabal | 2 +- changelog.md | 6 ++++++ 2 files changed, 7 insertions(+), 1 deletion(-) diff --git a/binary.cabal b/binary.cabal index 37ed51c..25c7c7c 100644 --- a/binary.cabal +++ b/binary.cabal @@ -1,5 +1,5 @@ name: binary -version: 0.7.6.1 +version: 0.8.0.0 license: BSD3 license-file: LICENSE author: Lennart Kolmodin diff --git a/changelog.md b/changelog.md index 493a50a..d9aaa3f 100644 --- a/changelog.md +++ b/changelog.md @@ -1,6 +1,12 @@ binary ====== +binary-0.8.0.0 +-------------- + +- Added binary instance for `Version` from `Data.Version`. +- Added binary instance for `Void` (from `base >= 4.8`). + binary-0.7.6.1 -------------- From git at git.haskell.org Wed Dec 16 09:43:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:43:37 +0000 (UTC) Subject: [commit: packages/binary] master: Merge pull request #89 from phadej/bump-0.8 (8d643d1) Message-ID: <20151216094337.F190F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/8d643d14025d0b6bef0fc410bf085565ad5540f6 >--------------------------------------------------------------- commit 8d643d14025d0b6bef0fc410bf085565ad5540f6 Merge: abc306b 43ee092 Author: Lennart Kolmodin Date: Thu Nov 12 17:44:39 2015 +0100 Merge pull request #89 from phadej/bump-0.8 Bump version to 0.8.0.0 >--------------------------------------------------------------- 8d643d14025d0b6bef0fc410bf085565ad5540f6 binary.cabal | 2 +- changelog.md | 6 ++++++ 2 files changed, 7 insertions(+), 1 deletion(-) From git at git.haskell.org Wed Dec 16 09:43:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:43:40 +0000 (UTC) Subject: [commit: packages/binary] master: Add since annotations (53ea7cb) Message-ID: <20151216094340.047E63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/53ea7cb290d69a85b07dedfd51022c0684b2db48 >--------------------------------------------------------------- commit 53ea7cb290d69a85b07dedfd51022c0684b2db48 Author: Oleg Grenrus Date: Fri Nov 13 07:35:25 2015 +0200 Add since annotations >--------------------------------------------------------------- 53ea7cb290d69a85b07dedfd51022c0684b2db48 src/Data/Binary.hs | 4 ++++ src/Data/Binary/Class.hs | 6 +++++- src/Data/Binary/Get.hs | 2 ++ src/Data/Binary/Get/Internal.hs | 14 +++++++++++++- 4 files changed, 24 insertions(+), 2 deletions(-) diff --git a/src/Data/Binary.hs b/src/Data/Binary.hs index d5a1858..bb25ee5 100644 --- a/src/Data/Binary.hs +++ b/src/Data/Binary.hs @@ -180,6 +180,8 @@ decode = runGet get -- 'Right' on success. In both cases the unconsumed input and the number of -- consumed bytes is returned. In case of failure, a human-readable error -- message will be returned as well. +-- +-- /Since: 0.7.0.0/ decodeOrFail :: Binary a => L.ByteString -> Either (L.ByteString, ByteOffset, String) (L.ByteString, ByteOffset, a) @@ -204,6 +206,8 @@ encodeFile f v = L.writeFile f (encode v) -- | Decode a value from a file. In case of errors, 'error' will -- be called with the error message. +-- +-- /Since: 0.7.0.0/ decodeFile :: Binary a => FilePath -> IO a decodeFile f = do result <- decodeFileOrFail f diff --git a/src/Data/Binary/Class.hs b/src/Data/Binary/Class.hs index 6247daf..ffb9734 100644 --- a/src/Data/Binary/Class.hs +++ b/src/Data/Binary/Class.hs @@ -140,6 +140,8 @@ class Binary t where #ifdef HAS_VOID -- Void never gets written nor reconstructed since it's impossible to have a -- value of that type + +-- | /Since: 0.8.0.0/ instance Binary Void where put = absurd get = mzero @@ -274,6 +276,7 @@ roll = foldl' unstep 0 . reverse -- Fixed-size type for a subset of Natural type NaturalWord = Word64 +-- | /Since: 0.7.3.0/ instance Binary Natural where {-# INLINE put #-} put n | n <= hi = do @@ -614,6 +617,7 @@ instance (Binary i, Ix i, Binary e, IArray UArray e) => Binary (UArray i e) wher -- Fingerprints #ifdef HAS_GHC_FINGERPRINT +-- | /Since: 0.7.6.0/ instance Binary Fingerprint where put (Fingerprint x1 x2) = do put x1 @@ -627,7 +631,7 @@ instance Binary Fingerprint where ------------------------------------------------------------------------ -- Version --- | /Since: binary-0.8/ +-- | /Since: 0.8.0.0/ instance Binary Version where get = Version <$> get <*> get put (Version br tags) = put br >> put tags diff --git a/src/Data/Binary/Get.hs b/src/Data/Binary/Get.hs index 091a14c..de1a326 100644 --- a/src/Data/Binary/Get.hs +++ b/src/Data/Binary/Get.hs @@ -299,6 +299,8 @@ dropHeadChunk lbs = -- success. In both cases any unconsumed input and the number of bytes -- consumed is returned. In the case of failure, a human-readable -- error message is included as well. +-- +-- /Since: 0.6.4.0/ runGetOrFail :: Get a -> L.ByteString -> Either (L.ByteString, ByteOffset, String) (L.ByteString, ByteOffset, a) runGetOrFail g lbs0 = feedAll (runGetIncremental g) lbs0 diff --git a/src/Data/Binary/Get/Internal.hs b/src/Data/Binary/Get/Internal.hs index 804fde1..3669242 100644 --- a/src/Data/Binary/Get/Internal.hs +++ b/src/Data/Binary/Get/Internal.hs @@ -123,6 +123,7 @@ instance Applicative Get where (<*>) = apG {-# INLINE (<*>) #-} +-- | /Since: 0.7.1.0/ instance MonadPlus Get where mzero = empty mplus = (<|>) @@ -192,6 +193,8 @@ bytesRead = C $ \inp k -> BytesRead (fromIntegral $ B.length inp) (k inp) -- If the given decoder fails, 'isolate' will also fail. -- Offset from 'bytesRead' will be relative to the start of 'isolate', not the -- absolute of the input. +-- +-- /Since: 0.7.2.0/ isolate :: Int -- ^ The number of bytes that must be consumed -> Get a -- ^ The decoder to isolate -> Get a @@ -254,6 +257,7 @@ getBytes :: Int -> Get B.ByteString getBytes = getByteString {-# INLINE getBytes #-} +-- | /Since: 0.7.0.0/ instance Alternative Get where empty = C $ \inp _ks -> Fail inp "Data.Binary.Get(Alternative).empty" (<|>) f g = do @@ -298,6 +302,8 @@ pushFront bs = C $ \ inp ks -> ks (B.append bs inp) () -- | Run the given decoder, but without consuming its input. If the given -- decoder fails, then so will this function. +-- +-- /Since: 0.7.0.0/ lookAhead :: Get a -> Get a lookAhead g = do (decoder, bs) <- runAndKeepTrack g @@ -309,6 +315,8 @@ lookAhead g = do -- | Run the given decoder, and only consume its input if it returns 'Just'. -- If 'Nothing' is returned, the input will be unconsumed. -- If the given decoder fails, then so will this function. +-- +-- /Since: 0.7.0.0/ lookAheadM :: Get (Maybe a) -> Get (Maybe a) lookAheadM g = do let g' = maybe (Left ()) Right <$> g @@ -317,6 +325,8 @@ lookAheadM g = do -- | Run the given decoder, and only consume its input if it returns 'Right'. -- If 'Left' is returned, the input will be unconsumed. -- If the given decoder fails, then so will this function. +-- +-- /Since: 0.7.1.0/ lookAheadE :: Get (Either a b) -> Get (Either a b) lookAheadE g = do (decoder, bs) <- runAndKeepTrack g @@ -326,8 +336,10 @@ lookAheadE g = do Fail inp s -> C $ \_ _ -> Fail inp s _ -> error "Binary: impossible" --- Label a decoder. If the decoder fails, the label will be appended on +-- | Label a decoder. If the decoder fails, the label will be appended on -- a new line to the error message string. +-- +-- /Since: 0.7.2.0/ label :: String -> Get a -> Get a label msg decoder = C $ \inp ks -> let r0 = runCont decoder inp (\inp' a -> Done inp' a) From git at git.haskell.org Wed Dec 16 09:43:42 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 09:43:42 +0000 (UTC) Subject: [commit: packages/binary] master: Merge pull request #90 from phadej/since-0.8 (8429d6b) Message-ID: <20151216094342.0AFCF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/8429d6b4a04970b8a0a151109a8299675ad5d190 >--------------------------------------------------------------- commit 8429d6b4a04970b8a0a151109a8299675ad5d190 Merge: 8d643d1 53ea7cb Author: Lennart Kolmodin Date: Fri Nov 13 11:17:29 2015 +0100 Merge pull request #90 from phadej/since-0.8 Add since annotations >--------------------------------------------------------------- 8429d6b4a04970b8a0a151109a8299675ad5d190 src/Data/Binary.hs | 4 ++++ src/Data/Binary/Class.hs | 6 +++++- src/Data/Binary/Get.hs | 2 ++ src/Data/Binary/Get/Internal.hs | 14 +++++++++++++- 4 files changed, 24 insertions(+), 2 deletions(-) From git at git.haskell.org Wed Dec 16 10:38:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 10:38:31 +0000 (UTC) Subject: [commit: ghc] master: Update binary submodule to binary-0.8 snapshot (3a48e6e) Message-ID: <20151216103831.93DB43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3a48e6ef80e4bf3d84814316cace259147f67df2/ghc >--------------------------------------------------------------- commit 3a48e6ef80e4bf3d84814316cace259147f67df2 Author: Herbert Valerio Riedel Date: Wed Dec 16 11:37:20 2015 +0100 Update binary submodule to binary-0.8 snapshot This requires tweaking version constraints to allow this new major version of `binary`. Starting with binary-0.8, `Binary Version` is de-orphaned into `binary`. This requires some minor adaptations to remove/hide orphan instances. /cc @kolmodin Differential Revision: https://phabricator.haskell.org/D1635 >--------------------------------------------------------------- 3a48e6ef80e4bf3d84814316cace259147f67df2 compiler/ghc.cabal.in | 2 +- libraries/Cabal | 2 +- libraries/binary | 2 +- libraries/ghc-boot/GHC/PackageDb.hs | 13 +------------ libraries/ghc-boot/ghc-boot.cabal | 2 +- utils/ghc-cabal/ghc.mk | 1 + 6 files changed, 6 insertions(+), 16 deletions(-) diff --git a/compiler/ghc.cabal.in b/compiler/ghc.cabal.in index f053f79..8dc4e23 100644 --- a/compiler/ghc.cabal.in +++ b/compiler/ghc.cabal.in @@ -48,7 +48,7 @@ Library directory >= 1 && < 1.3, process >= 1 && < 1.5, bytestring >= 0.9 && < 0.11, - binary >= 0.7 && < 0.8, + binary == 0.8.*, time < 1.6, containers >= 0.5 && < 0.6, array >= 0.1 && < 0.6, diff --git a/libraries/Cabal b/libraries/Cabal index d602f63..35f50ba 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit d602f63e7daf426514e38492bfdeeb4f33bd361d +Subproject commit 35f50ba6946fbfbff8aa5a9ff548f0d1f481dbdb diff --git a/libraries/binary b/libraries/binary index 86e4c9a..8429d6b 160000 --- a/libraries/binary +++ b/libraries/binary @@ -1 +1 @@ -Subproject commit 86e4c9a6125cdddb0592a653f48c699a574ccf7b +Subproject commit 8429d6b4a04970b8a0a151109a8299675ad5d190 diff --git a/libraries/ghc-boot/GHC/PackageDb.hs b/libraries/ghc-boot/GHC/PackageDb.hs index fcb24d8..2be20b2 100644 --- a/libraries/ghc-boot/GHC/PackageDb.hs +++ b/libraries/ghc-boot/GHC/PackageDb.hs @@ -1,6 +1,4 @@ -{-# LANGUAGE CPP #-} --- This module deliberately defines orphan instances for now (Binary Version). -{-# OPTIONS_GHC -fno-warn-orphans -fno-warn-name-shadowing #-} +{-# OPTIONS_GHC -fno-warn-name-shadowing #-} ----------------------------------------------------------------------------- -- | -- Module : GHC.PackageDb @@ -381,15 +379,6 @@ instance (BinaryStringRep a, BinaryStringRep b, BinaryStringRep c, (map (\(k,v) -> (fromStringRep k, v)) instantiatedWith) exposed trusted) -instance Binary Version where - put (Version a b) = do - put a - put b - get = do - a <- get - b <- get - return (Version a b) - instance (BinaryStringRep a, BinaryStringRep b) => Binary (OriginalModule a b) where put (OriginalModule originalPackageId originalModuleName) = do diff --git a/libraries/ghc-boot/ghc-boot.cabal b/libraries/ghc-boot/ghc-boot.cabal index 7f0f14f..883bbaf 100644 --- a/libraries/ghc-boot/ghc-boot.cabal +++ b/libraries/ghc-boot/ghc-boot.cabal @@ -39,7 +39,7 @@ Library GHC.LanguageExtensions build-depends: base >= 4 && < 5, - binary >= 0.7 && < 0.8, + binary == 0.8.*, bytestring >= 0.9 && < 1, directory >= 1 && < 1.3, filepath diff --git a/utils/ghc-cabal/ghc.mk b/utils/ghc-cabal/ghc.mk index 3ac864f..49a2ba3 100644 --- a/utils/ghc-cabal/ghc.mk +++ b/utils/ghc-cabal/ghc.mk @@ -38,6 +38,7 @@ $(ghc-cabal_DIST_BINARY): utils/ghc-cabal/Main.hs $(TOUCH_DEP) | $$(dir $$@)/. b -no-user-$(GHC_PACKAGE_DB_FLAG) \ -Wall -fno-warn-unused-imports -fno-warn-warnings-deprecations \ -DCABAL_VERSION=$(CABAL_VERSION) \ + -DMIN_VERSION_binary_0_8_0 \ -DBOOTSTRAPPING \ -optP-include -optPutils/ghc-cabal/cabal_macros_boot.h \ -odir bootstrapping \ From git at git.haskell.org Wed Dec 16 11:31:22 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 11:31:22 +0000 (UTC) Subject: [commit: ghc] master: Add `-W(no-)xxx` aliases for `-f(no-)warn-xxx` flags (2206fa8) Message-ID: <20151216113122.F2DB73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2206fa8cdb1209320f3690690b610320b4810de6/ghc >--------------------------------------------------------------- commit 2206fa8cdb1209320f3690690b610320b4810de6 Author: David Luposchainsky Date: Wed Dec 16 11:42:00 2015 +0100 Add `-W(no-)xxx` aliases for `-f(no-)warn-xxx` flags This also updates the user's guide to refer to the `-W`-based warning flags by default. Quoting the release note entry: | Warnings can now be controlled with `-W(no-)...` flags in addition to | the old `-f(no-)warn...` ones. This was done as the first part of a | rewrite of the warning system to provide better control over warnings, | better warning messages, and more common syntax compared to other | compilers. The old `-fwarn...`-based warning flags will remain | functional for the forseeable future. This is part of https://ghc.haskell.org/wiki/Design/Warnings and addresses #11218 Reviewed By: hvr, bgamari Differential Revision: https://phabricator.haskell.org/D1613 >--------------------------------------------------------------- 2206fa8cdb1209320f3690690b610320b4810de6 compiler/main/DynFlags.hs | 176 +++++++++-------- compiler/main/HscMain.hs | 4 +- compiler/main/InteractiveEval.hs | 2 +- compiler/rename/RnPat.hs | 2 +- compiler/typecheck/TcClassDcl.hs | 2 +- compiler/typecheck/TcDeriv.hs | 2 +- compiler/typecheck/TcErrors.hs | 4 +- compiler/typecheck/TcSimplify.hs | 4 +- docs/users_guide/7.12.1-notes.rst | 19 +- docs/users_guide/ghci.rst | 8 +- docs/users_guide/glasgow_exts.rst | 18 +- docs/users_guide/runghc.rst | 2 +- docs/users_guide/safe_haskell.rst | 6 +- docs/users_guide/separate_compilation.rst | 4 +- docs/users_guide/sooner.rst | 2 +- docs/users_guide/using-warnings.rst | 288 ++++++++++++++-------------- docs/users_guide/using.rst | 4 +- ghc/InteractiveUI.hs | 15 +- testsuite/tests/ghci/scripts/Makefile | 2 +- testsuite/tests/ghci/scripts/ghci024.stdout | 4 +- utils/mkUserGuidePart/Options/Warnings.hs | 196 +++++++++---------- 21 files changed, 391 insertions(+), 373 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 2206fa8cdb1209320f3690690b610320b4810de6 From git at git.haskell.org Wed Dec 16 13:51:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 13:51:31 +0000 (UTC) Subject: [commit: ghc] master: Start using `-W` instead of `-f(no-)warn` in some places (437ebdd) Message-ID: <20151216135131.94C483A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/437ebdda48e7a32fe1bea49cb503f456a0152a36/ghc >--------------------------------------------------------------- commit 437ebdda48e7a32fe1bea49cb503f456a0152a36 Author: Herbert Valerio Riedel Date: Wed Dec 16 13:32:32 2015 +0100 Start using `-W` instead of `-f(no-)warn` in some places This replaces some occurences of `-f(no-)warn` with the new `-W`-aliases introduced via 2206fa8cdb120932 / #11218, in cases which are guaranteed to be invoked with recent enough GHC (i.e. the stage1+ GHC). After this commit, mostly the compiler and the testsuite remain using `-f(wo-)warn...` because the compiler needs to be bootstrappable with older GHCs, while for the testsuite it's convenient to be able to quickly compare the behavior to older GHCs (which may not support the new flags yet). The compiler-part can be updated to use the new flags once GHC 8.3 development starts. Reviewed By: quchen Differential Revision: https://phabricator.haskell.org/D1637 >--------------------------------------------------------------- 437ebdda48e7a32fe1bea49cb503f456a0152a36 libraries/base/Control/Arrow.hs | 2 +- libraries/base/Control/Category.hs | 2 +- libraries/base/Control/Concurrent.hs | 2 +- libraries/base/Foreign/C/Types.hs | 4 +- libraries/base/GHC/Base.hs | 4 +- libraries/base/GHC/Conc.hs | 2 +- libraries/base/GHC/Conc/IO.hs | 2 +- libraries/base/GHC/Conc/Sync.hs | 2 +- libraries/base/GHC/Conc/Windows.hs | 2 +- libraries/base/GHC/Event/IntTable.hs | 2 +- libraries/base/GHC/Float.hs | 2 +- libraries/base/GHC/IO/Encoding/CodePage/API.hs | 2 +- libraries/base/GHC/IO/FD.hs | 2 +- libraries/base/GHC/IO/Handle.hs | 2 +- libraries/base/GHC/IO/Handle/Internals.hs | 4 +- libraries/base/GHC/IO/Handle/Text.hs | 4 +- libraries/base/GHC/Real.hs | 2 +- libraries/base/Text/Show/Functions.hs | 2 +- libraries/ghc-prim/GHC/Classes.hs | 8 ++-- mk/warnings.mk | 57 ++++++++++++++------------ 20 files changed, 57 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 437ebdda48e7a32fe1bea49cb503f456a0152a36 From git at git.haskell.org Wed Dec 16 15:56:50 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 15:56:50 +0000 (UTC) Subject: [commit: ghc] master: GHC.Stack: Fix Haddock markup (d36e9e1) Message-ID: <20151216155650.4B5103A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d36e9e12b2f308e0d23db68889c18d01b6512bcc/ghc >--------------------------------------------------------------- commit d36e9e12b2f308e0d23db68889c18d01b6512bcc Author: Ben Gamari Date: Wed Dec 16 12:27:34 2015 +0100 GHC.Stack: Fix Haddock markup >--------------------------------------------------------------- d36e9e12b2f308e0d23db68889c18d01b6512bcc libraries/base/GHC/Stack/CCS.hsc | 3 +-- libraries/base/GHC/Stack/Types.hs | 9 ++++++++- 2 files changed, 9 insertions(+), 3 deletions(-) diff --git a/libraries/base/GHC/Stack/CCS.hsc b/libraries/base/GHC/Stack/CCS.hsc index 6d62a1e..b62c80a 100644 --- a/libraries/base/GHC/Stack/CCS.hsc +++ b/libraries/base/GHC/Stack/CCS.hsc @@ -75,7 +75,7 @@ ccModule p = (# peek CostCentre, module) p ccSrcSpan :: Ptr CostCentre -> IO CString ccSrcSpan p = (# peek CostCentre, srcloc) p --- | returns a '[String]' representing the current call stack. This +-- | Returns a @[String]@ representing the current call stack. This -- can be useful for debugging. -- -- The implementation uses the call-stack simulation maintined by the @@ -85,7 +85,6 @@ ccSrcSpan p = (# peek CostCentre, srcloc) p -- uninformative. -- -- @since 4.5.0.0 - currentCallStack :: IO [String] currentCallStack = ccsToStrings =<< getCurrentCCS () diff --git a/libraries/base/GHC/Stack/Types.hs b/libraries/base/GHC/Stack/Types.hs index f877f7e..ebe4591 100644 --- a/libraries/base/GHC/Stack/Types.hs +++ b/libraries/base/GHC/Stack/Types.hs @@ -65,10 +65,14 @@ import GHC.Integer () -- myerror msg = error (msg ++ "\n" ++ prettyCallStack ?callStack) -- @ -- +-- Will produce the following when evaluated, +-- +-- @ -- ghci> myerror "die" -- *** Exception: die -- CallStack (from ImplicitParams): -- myerror, called at :2:1 in interactive:Ghci1 +-- @ -- -- @CallStack at s do not interact with the RTS and do not require compilation with -- @-prof at . On the other hand, as they are built up explicitly using @@ -80,7 +84,10 @@ import GHC.Integer () -- ordered with the most recently called function at the head. -- -- @since 4.8.1.0 -data CallStack = CallStack { getCallStack :: [([Char], SrcLoc)] } +data CallStack = CallStack { getCallStack :: [([Char], SrcLoc)] + -- ^ Get a list of stack frames with the most + -- recently called function at the head. + } -- See Note [Overview of implicit CallStacks] From git at git.haskell.org Wed Dec 16 15:56:53 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 15:56:53 +0000 (UTC) Subject: [commit: ghc] master: Update haddock submodule (4c7da9c) Message-ID: <20151216155653.3C6E73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4c7da9c557ac5990fb4ccdd6145e0d2487a57219/ghc >--------------------------------------------------------------- commit 4c7da9c557ac5990fb4ccdd6145e0d2487a57219 Author: Ben Gamari Date: Wed Dec 16 07:47:51 2015 -0500 Update haddock submodule Also rename and move the horribly named isVanillaLSig to Haddock as isUserLSig, reflecting the fact that it returns whether the signature was provided by the user or generated. >--------------------------------------------------------------- 4c7da9c557ac5990fb4ccdd6145e0d2487a57219 compiler/hsSyn/HsBinds.hs | 6 ------ utils/haddock | 2 +- 2 files changed, 1 insertion(+), 7 deletions(-) diff --git a/compiler/hsSyn/HsBinds.hs b/compiler/hsSyn/HsBinds.hs index 267627d..3641642 100644 --- a/compiler/hsSyn/HsBinds.hs +++ b/compiler/hsSyn/HsBinds.hs @@ -819,12 +819,6 @@ isFixityLSig :: LSig name -> Bool isFixityLSig (L _ (FixSig {})) = True isFixityLSig _ = False -isVanillaLSig :: LSig name -> Bool -- User type signatures --- A badly-named function, but it's part of the GHCi (used --- by Haddock) so I don't want to change it gratuitously. -isVanillaLSig (L _(TypeSig {})) = True -isVanillaLSig _ = False - isTypeLSig :: LSig name -> Bool -- Type signatures isTypeLSig (L _(TypeSig {})) = True isTypeLSig (L _(ClassOpSig {})) = True diff --git a/utils/haddock b/utils/haddock index d4657f0..66cf3d2 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit d4657f07912416a1b14ddb517696f8ef3ffb85a7 +Subproject commit 66cf3d2714ef1cf851782fbe4378f8c2b1af3335 From git at git.haskell.org Wed Dec 16 16:16:24 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 16:16:24 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T11224' created Message-ID: <20151216161624.DBBD03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T11224 Referencing: a729ac8c091cbcc8c3b456836dbcdea5c20b0af5 From git at git.haskell.org Wed Dec 16 16:16:28 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 16:16:28 +0000 (UTC) Subject: [commit: ghc] wip/T11224: WIP for Trac #11224 (a729ac8) Message-ID: <20151216161628.8C9883A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T11224 Link : http://ghc.haskell.org/trac/ghc/changeset/a729ac8c091cbcc8c3b456836dbcdea5c20b0af5/ghc >--------------------------------------------------------------- commit a729ac8c091cbcc8c3b456836dbcdea5c20b0af5 Author: Simon Peyton Jones Date: Wed Dec 16 12:00:58 2015 +0000 WIP for Trac #11224 Not right yet. But the fix in Match.hs is solid; could be cherry-picked. >--------------------------------------------------------------- a729ac8c091cbcc8c3b456836dbcdea5c20b0af5 compiler/basicTypes/PatSyn.hs | 2 +- compiler/deSugar/Match.hs | 86 +++++---- compiler/typecheck/TcBinds.hs | 25 +-- compiler/typecheck/TcHsType.hs | 2 +- compiler/typecheck/TcPatSyn.hs | 209 +++++++++++---------- compiler/typecheck/TcRnTypes.hs | 7 +- testsuite/tests/patsyn/should_compile/T11224b.hs | 16 ++ testsuite/tests/patsyn/should_compile/all.T | 1 + .../tests/patsyn/should_fail/as-pattern.stderr | 7 +- testsuite/tests/patsyn/should_run/T11224.hs | 28 +++ testsuite/tests/patsyn/should_run/T11224.stdout | 6 + testsuite/tests/patsyn/should_run/all.T | 1 + 12 files changed, 231 insertions(+), 159 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a729ac8c091cbcc8c3b456836dbcdea5c20b0af5 From git at git.haskell.org Wed Dec 16 16:40:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 16:40:47 +0000 (UTC) Subject: [commit: ghc] master: Improve detection of `fdatasync(2)` (re #11137) (ab79ed7) Message-ID: <20151216164047.83CE53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ab79ed763cfbaa1b0d1f39ba5ed1cde7dffd4b87/ghc >--------------------------------------------------------------- commit ab79ed763cfbaa1b0d1f39ba5ed1cde7dffd4b87 Author: Herbert Valerio Riedel Date: Wed Dec 16 17:40:48 2015 +0100 Improve detection of `fdatasync(2)` (re #11137) This updates the `unix` submodule to pull in an improved Autoconf test for `fdatasync(2)` in cases where `` lacks a declaration, but linking against `fdatasync` works which led to a false positive previously. >--------------------------------------------------------------- ab79ed763cfbaa1b0d1f39ba5ed1cde7dffd4b87 libraries/unix | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/unix b/libraries/unix index 59edb0a..5d5b747 160000 --- a/libraries/unix +++ b/libraries/unix @@ -1 +1 @@ -Subproject commit 59edb0a0a0d91ecfe938029b3b00a0c99dcb8481 +Subproject commit 5d5b74716b696b0f22c37a88ccc5c114b13f0398 From git at git.haskell.org Wed Dec 16 16:57:53 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 16:57:53 +0000 (UTC) Subject: [commit: ghc] master: Synchronize Haddock submodule with master branch (11b9ada) Message-ID: <20151216165753.25F6F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/11b9ada1310fda8f5ac2e53ad87b7309e02f1df3/ghc >--------------------------------------------------------------- commit 11b9ada1310fda8f5ac2e53ad87b7309e02f1df3 Author: Ben Gamari Date: Wed Dec 16 17:24:40 2015 +0100 Synchronize Haddock submodule with master branch Thanks for Matthew Pickering for managing this rebase. >--------------------------------------------------------------- 11b9ada1310fda8f5ac2e53ad87b7309e02f1df3 utils/haddock | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/haddock b/utils/haddock index 66cf3d2..6f46d59 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit 66cf3d2714ef1cf851782fbe4378f8c2b1af3335 +Subproject commit 6f46d59d7def2afc0b0aa59ad96aa5f06482c799 From git at git.haskell.org Wed Dec 16 17:13:58 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 17:13:58 +0000 (UTC) Subject: [commit: ghc] master: Look through type synonyms in GADT kind signatures (efaa51d) Message-ID: <20151216171358.E693B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/efaa51de15017b92618634898fc2c2aee2c5fd5b/ghc >--------------------------------------------------------------- commit efaa51de15017b92618634898fc2c2aee2c5fd5b Author: Jan Stolarek Date: Wed Dec 16 12:57:45 2015 +0100 Look through type synonyms in GADT kind signatures Summary: Fixes #11237 Test Plan: ./validate Reviewers: goldfire, austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1636 GHC Trac Issues: #11237 >--------------------------------------------------------------- efaa51de15017b92618634898fc2c2aee2c5fd5b compiler/types/TyCoRep.hs | 6 +++--- compiler/types/Type.hs-boot | 2 ++ testsuite/tests/typecheck/should_compile/T11237.hs | 13 +++++++++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 4 files changed, 19 insertions(+), 3 deletions(-) diff --git a/compiler/types/TyCoRep.hs b/compiler/types/TyCoRep.hs index c25bd11..d409c7d 100644 --- a/compiler/types/TyCoRep.hs +++ b/compiler/types/TyCoRep.hs @@ -114,7 +114,7 @@ module TyCoRep ( import {-# SOURCE #-} DataCon( dataConTyCon, dataConFullSig , DataCon, eqSpecTyVar ) import {-# SOURCE #-} Type( isPredTy, isCoercionTy, mkAppTy - , partitionInvisibles ) + , partitionInvisibles, coreView ) -- Transitively pulls in a LOT of stuff, better to break the loop import {-# SOURCE #-} Coercion @@ -412,13 +412,13 @@ Some basic functions, put here to break loops eg with the pretty printer -} isLiftedTypeKind :: Kind -> Bool -isLiftedTypeKind (TyConApp tc []) = isLiftedTypeKindTyConName (tyConName tc) +isLiftedTypeKind ki | Just ki' <- coreView ki = isLiftedTypeKind ki' isLiftedTypeKind (TyConApp tc [TyConApp lev []]) = tc `hasKey` tYPETyConKey && lev `hasKey` liftedDataConKey isLiftedTypeKind _ = False isUnliftedTypeKind :: Kind -> Bool -isUnliftedTypeKind (TyConApp tc []) = tc `hasKey` unliftedTypeKindTyConKey +isUnliftedTypeKind ki | Just ki' <- coreView ki = isUnliftedTypeKind ki' isUnliftedTypeKind (TyConApp tc [TyConApp lev []]) = tc `hasKey` tYPETyConKey && lev `hasKey` unliftedDataConKey isUnliftedTypeKind _ = False diff --git a/compiler/types/Type.hs-boot b/compiler/types/Type.hs-boot index aa12398..abddc24 100644 --- a/compiler/types/Type.hs-boot +++ b/compiler/types/Type.hs-boot @@ -14,3 +14,5 @@ eqType :: Type -> Type -> Bool coreViewOneStarKind :: Type -> Maybe Type partitionInvisibles :: TyCon -> (a -> Type) -> [a] -> ([a], [a]) + +coreView :: Type -> Maybe Type diff --git a/testsuite/tests/typecheck/should_compile/T11237.hs b/testsuite/tests/typecheck/should_compile/T11237.hs new file mode 100644 index 0000000..422aefd --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T11237.hs @@ -0,0 +1,13 @@ +{-# LANGUAGE TypeInType #-} +{-# LANGUAGE GADTs #-} +module TypeInTypeBug where + +import qualified Data.Kind + +data Works :: Data.Kind.Type where + WorksConstr :: Works + +type Set = Data.Kind.Type + +data ShouldWork :: Set where + ShouldWorkConstr :: ShouldWork diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index 8acb9a3..6bd0b03 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -479,3 +479,4 @@ test('T10770a', expect_broken(10770), compile, ['']) test('T10770b', expect_broken(10770), compile, ['']) test('T10935', normal, compile, ['']) test('T10971a', normal, compile, ['']) +test('T11237', normal, compile, ['']) From git at git.haskell.org Wed Dec 16 18:05:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 18:05:13 +0000 (UTC) Subject: [commit: ghc] master: Note [The equality types story] in TysPrim (046b47a) Message-ID: <20151216180513.4AF183A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/046b47ab5a077e76abd9610946428419cfe82ca9/ghc >--------------------------------------------------------------- commit 046b47ab5a077e76abd9610946428419cfe82ca9 Author: Richard Eisenberg Date: Wed Dec 16 13:04:09 2015 -0500 Note [The equality types story] in TysPrim This supercedes the Note recently written in TysWiredIn. >--------------------------------------------------------------- 046b47ab5a077e76abd9610946428419cfe82ca9 compiler/prelude/PrelNames.hs | 2 +- compiler/prelude/TysPrim.hs | 150 ++++++++++++++++++++++++++++++++--- compiler/prelude/TysWiredIn.hs | 31 +------- compiler/typecheck/TcInteract.hs | 2 + compiler/typecheck/TcRnTypes.hs | 2 + compiler/typecheck/TcUnify.hs | 3 +- compiler/types/Class.hs | 1 + libraries/base/Data/Type/Equality.hs | 13 ++- libraries/ghc-prim/GHC/Types.hs | 6 +- 9 files changed, 158 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 046b47ab5a077e76abd9610946428419cfe82ca9 From git at git.haskell.org Wed Dec 16 22:25:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 22:25:40 +0000 (UTC) Subject: [commit: ghc] master: Update Cabal submodule to latest snapshot (b35cc1f) Message-ID: <20151216222540.96E203A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b35cc1fb649173c2aea59b98640c026f30960219/ghc >--------------------------------------------------------------- commit b35cc1fb649173c2aea59b98640c026f30960219 Author: Herbert Valerio Riedel Date: Wed Dec 16 23:22:42 2015 +0100 Update Cabal submodule to latest snapshot This needs minor adaptations to ghc-cabal due to http://git.haskell.org/packages/Cabal.git/commitdiff/b39b906d05c409e4960ae15dbaca89664826a85f >--------------------------------------------------------------- b35cc1fb649173c2aea59b98640c026f30960219 libraries/Cabal | 2 +- utils/ghc-cabal/Main.hs | 6 +++--- 2 files changed, 4 insertions(+), 4 deletions(-) diff --git a/libraries/Cabal b/libraries/Cabal index 35f50ba..4e33454 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit 35f50ba6946fbfbff8aa5a9ff548f0d1f481dbdb +Subproject commit 4e33454f5566c1ad3339c4bdf7444dff6c8fc21f diff --git a/utils/ghc-cabal/Main.hs b/utils/ghc-cabal/Main.hs index 6da7733..ad18f2e 100644 --- a/utils/ghc-cabal/Main.hs +++ b/utils/ghc-cabal/Main.hs @@ -167,7 +167,7 @@ doCopy directory distDir (installDirTemplates lbi) progs = withPrograms lbi stripProgram' = stripProgram { - programFindLocation = \_ _ -> return (Just strip) } + programFindLocation = \_ _ -> return (Just (strip,[])) } progs' <- configureProgram verbosity stripProgram' progs let lbi' = lbi { @@ -216,12 +216,12 @@ doRegister directory distDir ghc ghcpkg topdir ghcpkgconf = topdir "package.conf.d" ghcProgram' = ghcProgram { programPostConf = \_ cp -> return cp { programDefaultArgs = ["-B" ++ topdir] }, - programFindLocation = \_ _ -> return (Just ghc) } + programFindLocation = \_ _ -> return (Just (ghc,[])) } ghcPkgProgram' = ghcPkgProgram { programPostConf = \_ cp -> return cp { programDefaultArgs = ["--global-package-db", ghcpkgconf] ++ ["--force" | not (null myDestDir) ] }, - programFindLocation = \_ _ -> return (Just ghcpkg) } + programFindLocation = \_ _ -> return (Just (ghcpkg,[])) } configurePrograms ps conf = foldM (flip (configureProgram verbosity)) conf ps progs' <- configurePrograms [ghcProgram', ghcPkgProgram'] progs From git at git.haskell.org Wed Dec 16 22:37:02 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 22:37:02 +0000 (UTC) Subject: [commit: packages/haskeline] master: Relax upper bound to allow upcoming `transformers-0.5` (285f032) Message-ID: <20151216223702.608673A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/285f0325dce25f08f51318b6806bb21a045e3c9e >--------------------------------------------------------------- commit 285f0325dce25f08f51318b6806bb21a045e3c9e Author: Herbert Valerio Riedel Date: Wed Dec 16 17:09:30 2015 +0100 Relax upper bound to allow upcoming `transformers-0.5` GHC 8.0 will ship with the not yet released `transformers-0.5.0.0` release. >--------------------------------------------------------------- 285f0325dce25f08f51318b6806bb21a045e3c9e haskeline.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/haskeline.cabal b/haskeline.cabal index b1e41ae..508312b 100644 --- a/haskeline.cabal +++ b/haskeline.cabal @@ -52,7 +52,7 @@ flag legacy-encoding Library Build-depends: base >=4.3 && < 4.10, containers>=0.4 && < 0.6, directory>=1.1 && < 1.3, bytestring>=0.9 && < 0.11, - filepath >= 1.2 && < 1.5, transformers >= 0.2 && < 0.5 + filepath >= 1.2 && < 1.5, transformers >= 0.2 && < 0.6 Default-Language: Haskell98 Default-Extensions: ForeignFunctionInterface, Rank2Types, FlexibleInstances, From git at git.haskell.org Wed Dec 16 22:37:04 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 22:37:04 +0000 (UTC) Subject: [commit: packages/haskeline] master: Merge pull request #33 from hvr/pr/transformers-0.5 (56a17bd) Message-ID: <20151216223704.65B0D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/56a17bd9b917ace9045991cddb882636c1508002 >--------------------------------------------------------------- commit 56a17bd9b917ace9045991cddb882636c1508002 Merge: 06349b7 285f032 Author: Judah Jacobson Date: Wed Dec 16 13:04:32 2015 -0800 Merge pull request #33 from hvr/pr/transformers-0.5 Relax upper bound to allow upcoming `transformers-0.5` >--------------------------------------------------------------- 56a17bd9b917ace9045991cddb882636c1508002 haskeline.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Wed Dec 16 22:37:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 22:37:38 +0000 (UTC) Subject: [commit: ghc] master: Update transformers submodule to latest v0.5.0.0 (1687f99) Message-ID: <20151216223738.1A5053A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1687f999dfa09e975e679f1fdec807fc87de40e8/ghc >--------------------------------------------------------------- commit 1687f999dfa09e975e679f1fdec807fc87de40e8 Author: Herbert Valerio Riedel Date: Wed Dec 16 23:31:34 2015 +0100 Update transformers submodule to latest v0.5.0.0 `transformers-0.5.0.0` will be the next version of `transformers` and this is the designated version to be used for GHC 8.0.1 This needs to update the haskeline submodule in order to relax the upper bound for the major version bump to 0.5 >--------------------------------------------------------------- 1687f999dfa09e975e679f1fdec807fc87de40e8 libraries/haskeline | 2 +- libraries/transformers | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/libraries/haskeline b/libraries/haskeline index 06349b7..56a17bd 160000 --- a/libraries/haskeline +++ b/libraries/haskeline @@ -1 +1 @@ -Subproject commit 06349b7ffc503ba0c8bdf0293d1adc6026da97bd +Subproject commit 56a17bd9b917ace9045991cddb882636c1508002 diff --git a/libraries/transformers b/libraries/transformers index 34fba39..4c66312 160000 --- a/libraries/transformers +++ b/libraries/transformers @@ -1 +1 @@ -Subproject commit 34fba39b1279936a739ca8857e9592cc9a44c34e +Subproject commit 4c66312b8d72d463dd293d50cc81a885ec588af2 From git at git.haskell.org Wed Dec 16 23:16:52 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 16 Dec 2015 23:16:52 +0000 (UTC) Subject: [commit: ghc] master: Add test for #10897 (6c9258d) Message-ID: <20151216231652.56A3E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6c9258def53008f050e91e6d3e08c4c297392c00/ghc >--------------------------------------------------------------- commit 6c9258def53008f050e91e6d3e08c4c297392c00 Author: Matthew Pickering Date: Wed Dec 16 23:16:15 2015 +0000 Add test for #10897 >--------------------------------------------------------------- 6c9258def53008f050e91e6d3e08c4c297392c00 testsuite/tests/patsyn/should_compile/T10897a.hs | 4 ++++ testsuite/tests/patsyn/should_compile/T10897b.hs | 4 ++++ testsuite/tests/patsyn/should_compile/all.T | 3 +++ 3 files changed, 11 insertions(+) diff --git a/testsuite/tests/patsyn/should_compile/T10897a.hs b/testsuite/tests/patsyn/should_compile/T10897a.hs new file mode 100644 index 0000000..2bad0d9 --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/T10897a.hs @@ -0,0 +1,4 @@ +{-# LANGUAGE PatternSynonyms #-} +module T10897a where +pattern Single :: a -> a +pattern Single x = x diff --git a/testsuite/tests/patsyn/should_compile/T10897b.hs b/testsuite/tests/patsyn/should_compile/T10897b.hs new file mode 100644 index 0000000..6b506b8 --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/T10897b.hs @@ -0,0 +1,4 @@ +module B where +import T10897a + +Single y = True diff --git a/testsuite/tests/patsyn/should_compile/all.T b/testsuite/tests/patsyn/should_compile/all.T index d89cab6..4452711 100644 --- a/testsuite/tests/patsyn/should_compile/all.T +++ b/testsuite/tests/patsyn/should_compile/all.T @@ -42,3 +42,6 @@ test('poly-export3', normal, compile, ['']) test('multi-export', normal, compile, ['']) test('export-super-class', normal, compile, ['']) test('export-record-selector', normal, compile, ['']) +test('T10897', expect_broken(10897), multi_compile, ['T10897', [ + ('T10897a.hs','-c') + ,('T10897b.hs', '-c')], '']) From git at git.haskell.org Thu Dec 17 00:41:10 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 17 Dec 2015 00:41:10 +0000 (UTC) Subject: [commit: ghc] master: GHC doesn't have a way to ask for user-package-db, so Cabal reimplemented it. (7221ad7) Message-ID: <20151217004110.29FE23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7221ad70daa363d77f60d96c3f6e1baa1d9bec81/ghc >--------------------------------------------------------------- commit 7221ad70daa363d77f60d96c3f6e1baa1d9bec81 Author: Edward Z. Yang Date: Wed Dec 16 10:39:12 2015 -0800 GHC doesn't have a way to ask for user-package-db, so Cabal reimplemented it. Signed-off-by: Edward Z. Yang Test Plan: docs only Reviewers: austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1644 >--------------------------------------------------------------- 7221ad70daa363d77f60d96c3f6e1baa1d9bec81 compiler/main/DynFlags.hs | 2 ++ compiler/main/Packages.hs | 3 +++ 2 files changed, 5 insertions(+) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 5b16bd6..e443926 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -973,6 +973,8 @@ versionedAppDir :: DynFlags -> IO FilePath versionedAppDir dflags = do appdir <- getAppUserDataDirectory (programName dflags) return $ appdir (TARGET_ARCH ++ '-':TARGET_OS ++ '-':projectVersion dflags) + -- NB: This functionality is reimplemented in Cabal, so if you + -- change it, be sure to update Cabal. -- | The target code type of the compilation (if any). -- diff --git a/compiler/main/Packages.hs b/compiler/main/Packages.hs index 8d0f2a6..a26b275 100644 --- a/compiler/main/Packages.hs +++ b/compiler/main/Packages.hs @@ -378,6 +378,9 @@ getPackageConfRefs dflags = do resolvePackageConfig :: DynFlags -> PkgConfRef -> IO (Maybe FilePath) resolvePackageConfig dflags GlobalPkgConf = return $ Just (systemPackageConfig dflags) +-- NB: This logic is reimplemented in Cabal, so if you change it, +-- make sure you update Cabal. (Or, better yet, dump it in the +-- compiler info so Cabal can use the info.) resolvePackageConfig dflags UserPkgConf = handleIO (\_ -> return Nothing) $ do dir <- versionedAppDir dflags let pkgconf = dir "package.conf.d" From git at git.haskell.org Thu Dec 17 09:39:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 17 Dec 2015 09:39:51 +0000 (UTC) Subject: [commit: ghc] master: Fix tests when run in parallel (dd3837a) Message-ID: <20151217093951.0E9F83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/dd3837aba04ff1549217dcf5db8adc3625f175ae/ghc >--------------------------------------------------------------- commit dd3837aba04ff1549217dcf5db8adc3625f175ae Author: Simon Marlow Date: Thu Dec 17 01:37:23 2015 -0800 Fix tests when run in parallel >--------------------------------------------------------------- dd3837aba04ff1549217dcf5db8adc3625f175ae testsuite/tests/ghc-api/annotations-literals/Makefile | 4 ++-- testsuite/tests/ghc-api/annotations-literals/all.T | 6 ++++-- testsuite/tests/ghc-api/annotations-literals/parsed.hs | 2 +- 3 files changed, 7 insertions(+), 5 deletions(-) diff --git a/testsuite/tests/ghc-api/annotations-literals/Makefile b/testsuite/tests/ghc-api/annotations-literals/Makefile index 5b06030..58b50e8 100644 --- a/testsuite/tests/ghc-api/annotations-literals/Makefile +++ b/testsuite/tests/ghc-api/annotations-literals/Makefile @@ -6,12 +6,12 @@ clean: rm -f *.o *.hi literals: - rm -f literals.o literals.hi + rm -f literals.o literals.hi LiteralsTest.o LiteralsTest.hi '$(TEST_HC)' $(TEST_HC_OPTS) --make -v0 -package ghc literals ./literals "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`" parsed: - rm -f parsed.o parsed.hi + rm -f parsed.o parsed.hi LiteralsTest2.o LiteralsTest2.hi '$(TEST_HC)' $(TEST_HC_OPTS) --make -v0 -package ghc parsed ./parsed "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`" diff --git a/testsuite/tests/ghc-api/annotations-literals/all.T b/testsuite/tests/ghc-api/annotations-literals/all.T index 999c5a4..bef7049 100644 --- a/testsuite/tests/ghc-api/annotations-literals/all.T +++ b/testsuite/tests/ghc-api/annotations-literals/all.T @@ -1,2 +1,4 @@ -test('literals', normal, run_command, ['$MAKE -s --no-print-directory literals']) -test('parsed', normal, run_command, ['$MAKE -s --no-print-directory parsed']) \ No newline at end of file +test('literals', extra_clean(['LiteralsTest.o', 'LiteralsTest.hi']), + run_command, ['$MAKE -s --no-print-directory literals']) +test('parsed', extra_clean(['LiteralsTest2.o', 'LiteralsTest2.hi']), + run_command, ['$MAKE -s --no-print-directory parsed']) diff --git a/testsuite/tests/ghc-api/annotations-literals/parsed.hs b/testsuite/tests/ghc-api/annotations-literals/parsed.hs index 063e6bc..8664fdc 100644 --- a/testsuite/tests/ghc-api/annotations-literals/parsed.hs +++ b/testsuite/tests/ghc-api/annotations-literals/parsed.hs @@ -20,7 +20,7 @@ import Data.Dynamic ( fromDynamic,Dynamic ) main::IO() main = do [libdir] <- getArgs - testOneFile libdir "LiteralsTest" + testOneFile libdir "LiteralsTest2" testOneFile libdir fileName = do p <- runGhc (Just libdir) $ do From git at git.haskell.org Thu Dec 17 09:39:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 17 Dec 2015 09:39:54 +0000 (UTC) Subject: [commit: ghc] master: Remote GHCi, -fexternal-interpreter (4905b83) Message-ID: <20151217093954.04FE63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4905b83a2d448c65ccced385343d4e8124548a3b/ghc >--------------------------------------------------------------- commit 4905b83a2d448c65ccced385343d4e8124548a3b Author: Simon Marlow Date: Wed Nov 18 16:42:24 2015 +0000 Remote GHCi, -fexternal-interpreter Summary: (Apologies for the size of this patch, I couldn't make a smaller one that was validate-clean and also made sense independently) (Some of this code is derived from GHCJS.) This commit adds support for running interpreted code (for GHCi and TemplateHaskell) in a separate process. The functionality is experimental, so for now it is off by default and enabled by the flag -fexternal-interpreter. Reaosns we want this: * compiling Template Haskell code with -prof does not require building the code without -prof first * when GHC itself is profiled, it can interpret unprofiled code, and the same applies to dynamic linking. We would no longer need to force -dynamic-too with TemplateHaskell, and we can load ordinary objects into a dynamically-linked GHCi (and vice versa). * An unprofiled GHCi can load and run profiled code, which means it can use the stack-trace functionality provided by profiling without taking the performance hit on the compiler that profiling would entail. Amongst other things; see https://ghc.haskell.org/trac/ghc/wiki/RemoteGHCi for more details. Notes on the implementation are in Note [Remote GHCi] in the new module compiler/ghci/GHCi.hs. It probably needs more documenting, feel free to suggest things I could elaborate on. Things that are not currently implemented for -fexternal-interpreter: * The GHCi debugger * :set prog, :set args in GHCi * `recover` in Template Haskell * Redirecting stdin/stdout for the external process These are all doable, I just wanted to get to a working validate-clean patch first. I also haven't done any benchmarking yet. I expect there to be slight hit to link times for byte code and some penalty due to having to serialize/deserialize TH syntax, but I don't expect it to be a serious problem. There's also lots of low-hanging fruit in the byte code generator/linker that we could exploit to speed things up. Test Plan: * validate * I've run parts of the test suite with EXTRA_HC_OPTS=-fexternal-interpreter, notably tests/ghci and tests/th. There are a few failures due to the things not currently implemented (see above). Reviewers: simonpj, goldfire, ezyang, austin, alanz, hvr, niteria, bgamari, gibiansky, luite Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1562 >--------------------------------------------------------------- 4905b83a2d448c65ccced385343d4e8124548a3b .gitignore | 1 + aclocal.m4 | 2 +- compiler/basicTypes/BasicTypes.hs | 5 - compiler/basicTypes/Literal.hs | 14 +- compiler/coreSyn/MkCore.hs | 7 +- compiler/deSugar/Coverage.hs | 4 +- compiler/ghc.cabal.in | 7 +- compiler/ghc.mk | 47 +- compiler/ghci/ByteCodeAsm.hs | 93 +--- compiler/ghci/ByteCodeGen.hs | 175 ++++--- compiler/ghci/ByteCodeInstr.hs | 55 +-- compiler/ghci/ByteCodeItbls.hs | 437 ++--------------- compiler/ghci/ByteCodeLink.hs | 284 ++++------- compiler/ghci/ByteCodeTypes.hs | 90 ++++ compiler/ghci/Debugger.hs | 8 +- compiler/ghci/DebuggerUtils.hs | 2 +- compiler/ghci/GHCi.hs | 499 +++++++++++++++++++ compiler/ghci/Linker.hs | 544 ++++++++++++--------- compiler/ghci/RtClosureInspect.hs | 14 +- compiler/main/Annotations.hs | 14 +- compiler/main/DriverPipeline.hs | 9 +- compiler/main/DynFlags.hs | 77 +-- compiler/main/DynamicLoading.hs | 5 +- compiler/main/GHC.hs | 51 +- compiler/main/GhcMake.hs | 2 +- compiler/main/GhcPlugins.hs | 4 +- compiler/main/Hooks.hs | 33 +- compiler/main/HscMain.hs | 55 ++- compiler/main/HscTypes.hs | 29 +- compiler/main/InteractiveEval.hs | 332 ++++--------- compiler/main/InteractiveEvalTypes.hs | 26 +- compiler/main/SysTools.hs | 10 +- compiler/specialise/SpecConstr.hs | 2 +- compiler/typecheck/TcRnDriver.hs | 8 +- compiler/typecheck/TcRnMonad.hs | 2 + compiler/typecheck/TcRnTypes.hs | 2 + compiler/typecheck/TcSplice.hs | 200 +++++++- compiler/typecheck/TcSplice.hs-boot | 1 + compiler/utils/Binary.hs | 10 + compiler/utils/Outputable.hs | 4 + compiler/utils/Panic.hs | 43 +- ghc.mk | 12 +- ghc/GhciMonad.hs | 127 +++-- ghc/InteractiveUI.hs | 65 ++- ghc/Main.hs | 46 +- ghc/ghc-bin.cabal.in | 3 +- iserv/Main.hs | 94 ++++ iserv/Makefile | 15 + iserv/ghc.mk | 67 +++ iserv/iserv-bin.cabal | 26 + iserv/iservmain.c | 16 + libraries/ghc-boot/GHC/LanguageExtensions.hs | 8 +- .../utils => libraries/ghc-boot/GHC}/Serialized.hs | 30 +- libraries/ghc-boot/ghc-boot.cabal | 1 + libraries/ghci/GHCi/CreateBCO.hs | 147 ++++++ libraries/ghci/GHCi/FFI.hsc | 149 ++++++ libraries/ghci/GHCi/InfoTable.hsc | 348 +++++++++++++ libraries/ghci/GHCi/Message.hs | 386 +++++++++++++++ {compiler/ghci => libraries/ghci/GHCi}/ObjLink.hs | 88 ++-- libraries/ghci/GHCi/RemoteTypes.hs | 91 ++++ libraries/ghci/GHCi/ResolvedBCO.hs | 62 +++ libraries/ghci/GHCi/Run.hs | 308 ++++++++++++ libraries/ghci/GHCi/Signals.hs | 46 ++ libraries/ghci/GHCi/TH.hs | 175 +++++++ libraries/ghci/GHCi/TH/Binary.hs | 73 +++ libraries/ghci/GNUmakefile | 4 + libraries/ghci/LICENSE | 31 ++ libraries/ghci/SizedSeq.hs | 37 ++ libraries/ghci/ghc.mk | 5 + libraries/ghci/ghci.cabal | 41 ++ rts/Interpreter.c | 7 +- rules/build-prog.mk | 18 +- rules/shell-wrapper.mk | 2 +- testsuite/config/ghc | 5 +- testsuite/driver/testlib.py | 17 +- testsuite/tests/annotations/should_run/annrun01.hs | 2 +- testsuite/tests/cabal/cabal04/Makefile | 3 +- testsuite/tests/cabal/cabal04/all.T | 0 testsuite/tests/ghc-api/T4891/T4891.hs | 19 +- .../tests/ghci.debugger/scripts/break006.stderr | 4 +- .../tests/ghci.debugger/scripts/break011.script | 3 + .../tests/ghci.debugger/scripts/break011.stdout | 12 + .../tests/ghci.debugger/scripts/break013.stdout | 2 +- .../tests/ghci.debugger/scripts/break024.stdout | 4 +- .../tests/ghci.debugger/scripts/print019.stderr | 2 +- .../prog001/{prog001.stdout => prog001-ext.stdout} | 0 testsuite/tests/ghci/prog001/prog001.T | 4 +- testsuite/tests/ghci/scripts/T10110A.hs | 1 + testsuite/tests/ghci/scripts/all.T | 12 +- .../tests/profiling/should_run/scc003.prof.sample | 48 +- testsuite/tests/rts/LinkerUnload.hs | 4 +- testsuite/tests/rts/T2615.hs | 2 +- testsuite/tests/th/Makefile | 7 + testsuite/tests/th/TH_Roles2.stderr | 5 +- testsuite/tests/th/TH_finalizer.hs | 11 + testsuite/tests/th/TH_finalizer.stderr | 2 + testsuite/tests/th/TH_spliceE5_prof_ext.hs | 14 + ...spliceE5.stdout => TH_spliceE5_prof_ext.stdout} | 0 testsuite/tests/th/TH_spliceE5_prof_ext_Lib.hs | 8 + testsuite/tests/th/all.T | 10 + utils/ghctags/Main.hs | 6 +- 101 files changed, 4163 insertions(+), 1779 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 4905b83a2d448c65ccced385343d4e8124548a3b From git at git.haskell.org Thu Dec 17 09:39:56 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 17 Dec 2015 09:39:56 +0000 (UTC) Subject: [commit: ghc] master: accept output (a6d664c) Message-ID: <20151217093956.989493A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a6d664cf8afc5ad86240d83052772e4dc14df9cb/ghc >--------------------------------------------------------------- commit a6d664cf8afc5ad86240d83052772e4dc14df9cb Author: Simon Marlow Date: Thu Dec 17 01:32:20 2015 -0800 accept output >--------------------------------------------------------------- a6d664cf8afc5ad86240d83052772e4dc14df9cb testsuite/tests/th/TH_Roles2.stderr | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/th/TH_Roles2.stderr b/testsuite/tests/th/TH_Roles2.stderr index c44e5b9..a8a4ed1 100644 --- a/testsuite/tests/th/TH_Roles2.stderr +++ b/testsuite/tests/th/TH_Roles2.stderr @@ -5,7 +5,7 @@ TYPE CONSTRUCTORS Kind: forall k1. k1 -> * COERCION AXIOMS Dependent modules: [] -Dependent packages: [array-0.5.1.0, base-4.9.0.0, binary-0.7.5.0, +Dependent packages: [array-0.5.1.0, base-4.9.0.0, binary-0.8.0.0, bytestring-0.10.7.0, containers-0.5.6.3, deepseq-1.4.2.0, ghc-boot-0.0.0.0, ghc-prim-0.5.0.0, integer-gmp-1.0.0.0, pretty-1.1.3.2, template-haskell-2.11.0.0] From git at git.haskell.org Thu Dec 17 11:11:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 17 Dec 2015 11:11:13 +0000 (UTC) Subject: [commit: ghc] master: Bump haddock expected performance numbers (acd447e) Message-ID: <20151217111113.5B94C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/acd447e671e90c2f964069f268943db0f2a57a7c/ghc >--------------------------------------------------------------- commit acd447e671e90c2f964069f268943db0f2a57a7c Author: Ben Gamari Date: Thu Dec 17 10:40:57 2015 +0100 Bump haddock expected performance numbers This was a pretty brutal upgrade, with >100% increase in allocations while processing `base`. Ugh. >--------------------------------------------------------------- acd447e671e90c2f964069f268943db0f2a57a7c testsuite/tests/perf/haddock/all.T | 15 +++++++++------ 1 file changed, 9 insertions(+), 6 deletions(-) diff --git a/testsuite/tests/perf/haddock/all.T b/testsuite/tests/perf/haddock/all.T index 49a126b..296dc1e 100644 --- a/testsuite/tests/perf/haddock/all.T +++ b/testsuite/tests/perf/haddock/all.T @@ -5,7 +5,7 @@ test('haddock.base', [unless(in_tree_compiler(), skip), req_haddock ,stats_num_field('bytes allocated', - [(wordsize(64), 11119767632, 5) + [(wordsize(64), 26282821104, 5) # 2012-08-14: 5920822352 (amd64/Linux) # 2012-09-20: 5829972376 (amd64/Linux) # 2012-10-08: 5902601224 (amd64/Linux) @@ -25,7 +25,8 @@ test('haddock.base', # 2014-01-08: 9014511528 (x86_64/Linux) - Eliminate so-called "silent superclass parameters" (and others) # 2015-07-22: 9418857192 (x86_64/Linux) - Just slowly creeping up. # 2015-10-03: 9894189856 (x86_64/Linux) - Still creeping - # 2015-12-11: 11119767632 (amd64/Linux) TypeInType (see #11196) + # 2015-12-11: 11119767632 (amd64/Linux) - TypeInType (see #11196) + # 2015-12-17: 26282821104 (x86_64/Linux) - Update Haddock to master ,(platform('i386-unknown-mingw32'), 4434804940, 5) # 2013-02-10: 3358693084 (x86/Windows) @@ -48,7 +49,7 @@ test('haddock.base', test('haddock.Cabal', [unless(in_tree_compiler(), skip), req_haddock ,stats_num_field('bytes allocated', - [(wordsize(64), 8114833312, 5) + [(wordsize(64), 9982130512, 5) # 2012-08-14: 3255435248 (amd64/Linux) # 2012-08-29: 3324606664 (amd64/Linux, new codegen) # 2012-10-08: 3373401360 (amd64/Linux) @@ -68,8 +69,9 @@ test('haddock.Cabal', # 2014-10-04: 6019839624 (x86_64/Linux - Burning Bridges, Cabal update) # 2014-12-14: 6387320816 (x86_64/Linux) - Update to Haddock 2.16 # 2015-01-22: 6710234312 (x86_64/Linux) - Cabal updated - # 2015-06-29: 7413958344 (x86_64/Linux) due to #10482, not yet investigated - # 2015-12-11: 8114833312 (amd64/Linux) TypeInType (See #11196) + # 2015-06-29: 7413958344 (x86_64/Linux) - due to #10482, not yet investigated + # 2015-12-11: 8114833312 (amd64/Linux) - TypeInType (See #11196) + # 2015-12-17: 9982130512 (amd64/Linux) - Update Haddock to master ,(platform('i386-unknown-mingw32'), 3293415576, 5) # 2012-10-30: 1733638168 (x86/Windows) @@ -91,7 +93,7 @@ test('haddock.Cabal', test('haddock.compiler', [unless(in_tree_compiler(), skip), req_haddock ,stats_num_field('bytes allocated', - [(wordsize(64), 49395782136, 10) + [(wordsize(64), 58017214568, 10) # 2012P-08-14: 26070600504 (amd64/Linux) # 2012-08-29: 26353100288 (amd64/Linux, new CG) # 2012-09-18: 26882813032 (amd64/Linux) @@ -104,6 +106,7 @@ test('haddock.compiler', # 2015-06-29: 40624322224 (amd64/Linux) due to #10482, not yet investigated # 2015-12-03: 44721228752 (amd64/Linux) slow creep upwards # 2015-12-15: 49395782136 (amd64/Linux) more creep, following kind-equalities + # 2015-12-17: 58017214568 (amd64/Linux) update Haddock to master ,(platform('i386-unknown-mingw32'), 902576468, 10) # 2012-10-30: 13773051312 (x86/Windows) From git at git.haskell.org Thu Dec 17 11:11:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 17 Dec 2015 11:11:16 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Add missing LiteralsTest2.hs (b20a65d) Message-ID: <20151217111116.723EF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b20a65d5bf0ebf656c67f57e9b2c1094b459b827/ghc >--------------------------------------------------------------- commit b20a65d5bf0ebf656c67f57e9b2c1094b459b827 Author: Ben Gamari Date: Thu Dec 17 06:08:02 2015 -0500 testsuite: Add missing LiteralsTest2.hs >--------------------------------------------------------------- b20a65d5bf0ebf656c67f57e9b2c1094b459b827 .../ghc-api/annotations-literals/{LiteralsTest.hs => LiteralsTest2.hs} | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/ghc-api/annotations-literals/LiteralsTest.hs b/testsuite/tests/ghc-api/annotations-literals/LiteralsTest2.hs similarity index 90% copy from testsuite/tests/ghc-api/annotations-literals/LiteralsTest.hs copy to testsuite/tests/ghc-api/annotations-literals/LiteralsTest2.hs index 9081adf..e85eb17 100644 --- a/testsuite/tests/ghc-api/annotations-literals/LiteralsTest.hs +++ b/testsuite/tests/ghc-api/annotations-literals/LiteralsTest2.hs @@ -1,5 +1,5 @@ {-# LANGUAGE MagicHash #-} -module LiteralsTest where +module LiteralsTest2 where x,y :: Int x = 0003 From git at git.haskell.org Thu Dec 17 11:11:19 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 17 Dec 2015 11:11:19 +0000 (UTC) Subject: [commit: ghc] master: Fix haddock hyperlinker (62e60bb) Message-ID: <20151217111119.146A13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/62e60bb914980dff1b29eecbe1270deb0b265d9d/ghc >--------------------------------------------------------------- commit 62e60bb914980dff1b29eecbe1270deb0b265d9d Author: Ben Gamari Date: Wed Dec 16 23:33:08 2015 +0100 Fix haddock hyperlinker Updates haddock submodule >--------------------------------------------------------------- 62e60bb914980dff1b29eecbe1270deb0b265d9d utils/haddock | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/haddock b/utils/haddock index 6f46d59..fa03f80 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit 6f46d59d7def2afc0b0aa59ad96aa5f06482c799 +Subproject commit fa03f80d76f1511a811a0209ea7a6a8b6c58704f From git at git.haskell.org Thu Dec 17 11:11:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 17 Dec 2015 11:11:21 +0000 (UTC) Subject: [commit: ghc] master: TcTypeable: Don't use bogus fingerprints when suppress-uniques is enabled (786d528) Message-ID: <20151217111121.B330E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/786d528e8f949daeb62d34e0daa5e35f642065fc/ghc >--------------------------------------------------------------- commit 786d528e8f949daeb62d34e0daa5e35f642065fc Author: Ben Gamari Date: Wed Dec 16 21:09:54 2015 +0100 TcTypeable: Don't use bogus fingerprints when suppress-uniques is enabled Previously the Typeable implementation would intentionally create TyCon representations with bogus fingerprints to avoid fingerprints (which may change often) from leaking into test output. As pointed out by Richard in #10376 this is very bad as simply enabling a debug flag, `-dsuppress-uniques`, completely breaks the soundness of `Typeable`! This patch removes this behavior and replaces it with logic in the testsuite driver to filter out spurious changes due to Typeable representations. Test Plan: Validate Reviewers: austin, simonpj, goldfire Reviewed By: goldfire Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1629 GHC Trac Issues: #10376 >--------------------------------------------------------------- 786d528e8f949daeb62d34e0daa5e35f642065fc compiler/typecheck/TcTypeable.hs | 4 +--- testsuite/driver/testlib.py | 9 +++++++++ testsuite/tests/simplCore/should_compile/Makefile | 3 ++- testsuite/tests/simplCore/should_compile/T8274.stdout | 8 ++++---- 4 files changed, 16 insertions(+), 8 deletions(-) diff --git a/compiler/typecheck/TcTypeable.hs b/compiler/typecheck/TcTypeable.hs index c951387..032ff79 100644 --- a/compiler/typecheck/TcTypeable.hs +++ b/compiler/typecheck/TcTypeable.hs @@ -194,9 +194,7 @@ mkTyConRepBinds (dflags, mod_expr, pkg_str, mod_str, tr_datacon, trn_datacon) ty hashThis :: String hashThis = unwords [pkg_str, mod_str, tycon_str] - Fingerprint high low - | gopt Opt_SuppressUniques dflags = Fingerprint 0 0 - | otherwise = fingerprintString hashThis + Fingerprint high low = fingerprintString hashThis word64 :: Word64 -> HsLit word64 | wORD_SIZE dflags == 4 = \n -> HsWord64Prim (show n) (toInteger n) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index c41bb8c..4e9a1fb 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -1691,12 +1691,20 @@ def normalise_callstacks(str): # Ignore line number differences in call stacks (#10834). return re.sub(', called at (.+):[\\d]+:[\\d]+ in [\\w\-\.]+:', repl, str) +def normalise_type_reps(str): + """ Normalise out fingerprints from Typeable TyCon representations """ + return re.sub(r'TyCon\s*\d+\#\#\s*\d+\#\#\s*', + 'TyCon FINGERPRINT FINGERPRINT ', + str, + flags=re.MULTILINE) + def normalise_errmsg( str ): # remove " error:" and lower-case " Warning:" to make patch for # trac issue #10021 smaller str = modify_lines(str, lambda l: re.sub(' error:', '', l)) str = modify_lines(str, lambda l: re.sub(' Warning:', ' warning:', l)) str = normalise_callstacks(str) + str = normalise_type_reps(str) # If somefile ends in ".exe" or ".exe:", zap ".exe" (for Windows) # the colon is there because it appears in error messages; this @@ -1766,6 +1774,7 @@ def normalise_output( str ): # This can occur in error messages generated by the program. str = re.sub('([^\\s])\\.exe', '\\1', str) str = normalise_callstacks(str) + str = normalise_type_reps(str) return str def normalise_asm( str ): diff --git a/testsuite/tests/simplCore/should_compile/Makefile b/testsuite/tests/simplCore/should_compile/Makefile index a804768..87b1d95 100644 --- a/testsuite/tests/simplCore/should_compile/Makefile +++ b/testsuite/tests/simplCore/should_compile/Makefile @@ -14,7 +14,8 @@ T11155: T8274: $(RM) -f T8274.o T8274.hi - '$(TEST_HC)' $(TEST_HC_OPTS) -O -c -ddump-simpl -dsuppress-uniques T8274.hs | grep '#' + # Set -dppr-cols to ensure things don't wrap + '$(TEST_HC)' $(TEST_HC_OPTS) -O -c -ddump-simpl -dsuppress-uniques -dppr-cols=200 T8274.hs | grep '#' T7865: $(RM) -f T7865.o T7865.hi diff --git a/testsuite/tests/simplCore/should_compile/T8274.stdout b/testsuite/tests/simplCore/should_compile/T8274.stdout index 269f4e7..05a0069 100644 --- a/testsuite/tests/simplCore/should_compile/T8274.stdout +++ b/testsuite/tests/simplCore/should_compile/T8274.stdout @@ -1,12 +1,12 @@ T8274.$trModule2 = GHC.Types.TrNameS "main"# T8274.$trModule1 = GHC.Types.TrNameS "T8274"# T8274.$tc'Positives1 = GHC.Types.TrNameS "'Positives"# - GHC.Types.TyCon 0## 0## T8274.$trModule T8274.$tc'Positives1 +T8274.$tc'Positives = GHC.Types.TyCon 14732531009298850569## 4925356269917933860## T8274.$trModule T8274.$tc'Positives1 T8274.$tcP1 = GHC.Types.TrNameS "P"# -T8274.$tcP = GHC.Types.TyCon 0## 0## T8274.$trModule T8274.$tcP1 +T8274.$tcP = GHC.Types.TyCon 11095028091707994303## 9476557054198009608## T8274.$trModule T8274.$tcP1 T8274.$tc'Negatives1 = GHC.Types.TrNameS "'Negatives"# - GHC.Types.TyCon 0## 0## T8274.$trModule T8274.$tc'Negatives1 +T8274.$tc'Negatives = GHC.Types.TyCon 15950179315687996644## 11481167534507418130## T8274.$trModule T8274.$tc'Negatives1 T8274.$tcN1 = GHC.Types.TrNameS "N"# -T8274.$tcN = GHC.Types.TyCon 0## 0## T8274.$trModule T8274.$tcN1 +T8274.$tcN = GHC.Types.TyCon 7479687563082171902## 17616649989360543185## T8274.$trModule T8274.$tcN1 p = T8274.Positives 42# 4.23# 4.23## '4'# 4## n = T8274.Negatives -4# -4.0# -4.0## From git at git.haskell.org Thu Dec 17 11:48:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 17 Dec 2015 11:48:40 +0000 (UTC) Subject: [commit: ghc] master: Fix libffi dependency, and remove redundant LibFFI.hsc (27f47cd) Message-ID: <20151217114840.14CAA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/27f47cda4a2d91bbeaeeb5efa8d0e3a908798120/ghc >--------------------------------------------------------------- commit 27f47cda4a2d91bbeaeeb5efa8d0e3a908798120 Author: Simon Marlow Date: Thu Dec 17 03:03:29 2015 -0800 Fix libffi dependency, and remove redundant LibFFI.hsc LibFFI.hsc was moved to libraries/ghci/GHCi/FFI.hsc, I just forgot to remove the old one. We also need an explicit dependency on libffi, which moves from compiler/ghc.mk to the top-level ghc.mk (because libraries/ghci/ghc.mk is auto-generated). >--------------------------------------------------------------- 27f47cda4a2d91bbeaeeb5efa8d0e3a908798120 compiler/ghc.cabal.in | 1 - compiler/ghc.mk | 5 -- compiler/ghci/LibFFI.hsc | 138 ----------------------------------------------- ghc.mk | 6 +++ 4 files changed, 6 insertions(+), 144 deletions(-) diff --git a/compiler/ghc.cabal.in b/compiler/ghc.cabal.in index ae702ef..fc81942 100644 --- a/compiler/ghc.cabal.in +++ b/compiler/ghc.cabal.in @@ -587,7 +587,6 @@ Library ByteCodeItbls ByteCodeLink Debugger - LibFFI Linker RtClosureInspect DebuggerUtils diff --git a/compiler/ghc.mk b/compiler/ghc.mk index d93b879..f5c53d4 100644 --- a/compiler/ghc.mk +++ b/compiler/ghc.mk @@ -704,11 +704,6 @@ ifeq "$(DYNAMIC_GHC_PROGRAMS)" "YES" compiler/utils/Util_HC_OPTS += -DDYNAMIC_GHC_PROGRAMS endif -# LibFFI.hs #includes ffi.h -ifneq "$(UseSystemLibFFI)" "YES" -compiler/stage2/build/LibFFI.hs : $(libffi_HEADERS) -endif - # Note [munge-stage1-package-config] # Strip the date/patchlevel from the version of stage1. See Note # [fiddle-stage1-version] above. diff --git a/compiler/ghci/LibFFI.hsc b/compiler/ghci/LibFFI.hsc deleted file mode 100644 index d3759f3..0000000 --- a/compiler/ghci/LibFFI.hsc +++ /dev/null @@ -1,138 +0,0 @@ ------------------------------------------------------------------------------ --- --- libffi bindings --- --- (c) The University of Glasgow 2008 --- ------------------------------------------------------------------------------ - -#include - -module LibFFI ( - ForeignCallToken, - prepForeignCall - ) where - -import TyCon -import ForeignCall -import Panic -import DynFlags - -import Control.Monad -import Foreign -import Foreign.C - ----------------------------------------------------------------------------- - -type ForeignCallToken = C_ffi_cif - -prepForeignCall - :: DynFlags - -> CCallConv - -> [PrimRep] -- arg types - -> PrimRep -- result type - -> IO (Ptr ForeignCallToken) -- token for making calls - -- (must be freed by caller) -prepForeignCall dflags cconv arg_types result_type - = do - let n_args = length arg_types - arg_arr <- mallocArray n_args - let init_arg ty n = pokeElemOff arg_arr n (primRepToFFIType dflags ty) - zipWithM_ init_arg arg_types [0..] - cif <- mallocBytes (#const sizeof(ffi_cif)) - let abi = convToABI cconv - let res_ty = primRepToFFIType dflags result_type - r <- ffi_prep_cif cif abi (fromIntegral n_args) res_ty arg_arr - if (r /= fFI_OK) - then throwGhcExceptionIO (InstallationError - ("prepForeignCallFailed: " ++ show r)) - else return cif - -convToABI :: CCallConv -> C_ffi_abi -convToABI CCallConv = fFI_DEFAULT_ABI -#if defined(mingw32_HOST_OS) && defined(i386_HOST_ARCH) -convToABI StdCallConv = fFI_STDCALL -#endif --- unknown conventions are mapped to the default, (#3336) -convToABI _ = fFI_DEFAULT_ABI - --- c.f. DsForeign.primTyDescChar -primRepToFFIType :: DynFlags -> PrimRep -> Ptr C_ffi_type -primRepToFFIType dflags r - = case r of - VoidRep -> ffi_type_void - IntRep -> signed_word - WordRep -> unsigned_word - Int64Rep -> ffi_type_sint64 - Word64Rep -> ffi_type_uint64 - AddrRep -> ffi_type_pointer - FloatRep -> ffi_type_float - DoubleRep -> ffi_type_double - _ -> panic "primRepToFFIType" - where - (signed_word, unsigned_word) - | wORD_SIZE dflags == 4 = (ffi_type_sint32, ffi_type_uint32) - | wORD_SIZE dflags == 8 = (ffi_type_sint64, ffi_type_uint64) - | otherwise = panic "primTyDescChar" - - -data C_ffi_type -data C_ffi_cif - -type C_ffi_status = (#type ffi_status) -type C_ffi_abi = (#type ffi_abi) - -foreign import ccall "&ffi_type_void" ffi_type_void :: Ptr C_ffi_type ---foreign import ccall "&ffi_type_uint8" ffi_type_uint8 :: Ptr C_ffi_type ---foreign import ccall "&ffi_type_sint8" ffi_type_sint8 :: Ptr C_ffi_type ---foreign import ccall "&ffi_type_uint16" ffi_type_uint16 :: Ptr C_ffi_type ---foreign import ccall "&ffi_type_sint16" ffi_type_sint16 :: Ptr C_ffi_type -foreign import ccall "&ffi_type_uint32" ffi_type_uint32 :: Ptr C_ffi_type -foreign import ccall "&ffi_type_sint32" ffi_type_sint32 :: Ptr C_ffi_type -foreign import ccall "&ffi_type_uint64" ffi_type_uint64 :: Ptr C_ffi_type -foreign import ccall "&ffi_type_sint64" ffi_type_sint64 :: Ptr C_ffi_type -foreign import ccall "&ffi_type_float" ffi_type_float :: Ptr C_ffi_type -foreign import ccall "&ffi_type_double" ffi_type_double :: Ptr C_ffi_type -foreign import ccall "&ffi_type_pointer"ffi_type_pointer :: Ptr C_ffi_type - -fFI_OK :: C_ffi_status -fFI_OK = (#const FFI_OK) ---fFI_BAD_ABI :: C_ffi_status ---fFI_BAD_ABI = (#const FFI_BAD_ABI) ---fFI_BAD_TYPEDEF :: C_ffi_status ---fFI_BAD_TYPEDEF = (#const FFI_BAD_TYPEDEF) - -fFI_DEFAULT_ABI :: C_ffi_abi -fFI_DEFAULT_ABI = (#const FFI_DEFAULT_ABI) -#if defined(mingw32_HOST_OS) && defined(i386_HOST_ARCH) -fFI_STDCALL :: C_ffi_abi -fFI_STDCALL = (#const FFI_STDCALL) -#endif - --- ffi_status ffi_prep_cif(ffi_cif *cif, --- ffi_abi abi, --- unsigned int nargs, --- ffi_type *rtype, --- ffi_type **atypes); - -foreign import ccall "ffi_prep_cif" - ffi_prep_cif :: Ptr C_ffi_cif -- cif - -> C_ffi_abi -- abi - -> CUInt -- nargs - -> Ptr C_ffi_type -- result type - -> Ptr (Ptr C_ffi_type) -- arg types - -> IO C_ffi_status - --- Currently unused: - --- void ffi_call(ffi_cif *cif, --- void (*fn)(), --- void *rvalue, --- void **avalue); - --- foreign import ccall "ffi_call" --- ffi_call :: Ptr C_ffi_cif -- cif --- -> FunPtr (IO ()) -- function to call --- -> Ptr () -- put result here --- -> Ptr (Ptr ()) -- arg values --- -> IO () diff --git a/ghc.mk b/ghc.mk index 883e0b3..64eb9bb 100644 --- a/ghc.mk +++ b/ghc.mk @@ -727,6 +727,12 @@ include $(patsubst %, %/ghc.mk, $(BUILD_DIRS)) .PHONY: stage1_libs stage1_libs : $(ALL_STAGE1_LIBS) +# We need this extra dependency when building our own libffi, because +# GHCi.FFI.hs #includes ffi.h +ifneq "$(UseSystemLibFFI)" "YES" +libraries/ghci/dist-install/build/GHCi/FFI.hs : $(libffi_HEADERS) +endif + # ---------------------------------------------- # Per-package compiler flags # From git at git.haskell.org Thu Dec 17 11:54:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 17 Dec 2015 11:54:18 +0000 (UTC) Subject: [commit: ghc] master: Add Shake configuration to configure.ac (86ad116) Message-ID: <20151217115418.EB1403A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/86ad116fd73824776a6addd7b068db4358093bee/ghc >--------------------------------------------------------------- commit 86ad116fd73824776a6addd7b068db4358093bee Author: Ben Gamari Date: Thu Dec 17 12:14:17 2015 +0100 Add Shake configuration to configure.ac The Shake build system requires that this file be generated by autoconf. Generate it if we find a shake tree. Reviewers: austin, hvr Reviewed By: hvr Subscribers: thomie, erikd Differential Revision: https://phabricator.haskell.org/D1638 >--------------------------------------------------------------- 86ad116fd73824776a6addd7b068db4358093bee configure.ac | 3 +++ 1 file changed, 3 insertions(+) diff --git a/configure.ac b/configure.ac index c8708ae..0f335a4 100644 --- a/configure.ac +++ b/configure.ac @@ -1098,6 +1098,9 @@ if grep ' ' compiler/ghc.cabal.in 2>&1 >/dev/null; then AC_MSG_ERROR([compiler/ghc.cabal.in contains tab characters; please remove them]) fi +if test -e shake/cfg/system.config.in; then + AC_CONFIG_FILES([shake/cfg/system.config]) +fi AC_CONFIG_FILES([mk/config.mk mk/install.mk mk/project.mk compiler/ghc.cabal ghc/ghc-bin.cabal utils/runghc/runghc.cabal settings docs/users_guide/ghc_config.py docs/index.html libraries/prologue.txt distrib/configure.ac]) AC_OUTPUT From git at git.haskell.org Thu Dec 17 11:54:22 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 17 Dec 2015 11:54:22 +0000 (UTC) Subject: [commit: ghc] master: Build system: Cabalize genapply (0cc4aad) Message-ID: <20151217115422.65F703A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0cc4aad36f91570b1b489e3d239256d1c781daac/ghc >--------------------------------------------------------------- commit 0cc4aad36f91570b1b489e3d239256d1c781daac Author: Ben Gamari Date: Thu Dec 17 12:13:17 2015 +0100 Build system: Cabalize genapply Test Plan: Validate Reviewers: thomie, austin Reviewed By: thomie, austin Differential Revision: https://phabricator.haskell.org/D1639 >--------------------------------------------------------------- 0cc4aad36f91570b1b489e3d239256d1c781daac utils/genapply/{GenApply.hs => Main.hs} | 1 - utils/{ghc-pwd/ghc-pwd.cabal => genapply/genapply.cabal} | 15 +++++++++++---- utils/genapply/ghc.mk | 14 +++++--------- 3 files changed, 16 insertions(+), 14 deletions(-) diff --git a/utils/genapply/GenApply.hs b/utils/genapply/Main.hs similarity index 97% rename from utils/genapply/GenApply.hs rename to utils/genapply/Main.hs index 26b5154..e58a496 100644 --- a/utils/genapply/GenApply.hs +++ b/utils/genapply/Main.hs @@ -1042,4 +1042,3 @@ genBitmapArray types = where bitmap_val = (fromIntegral (mkBitmap ty) `shiftL` BITMAP_BITS_SHIFT) .|. sum (map argSize ty) - diff --git a/utils/ghc-pwd/ghc-pwd.cabal b/utils/genapply/genapply.cabal similarity index 52% copy from utils/ghc-pwd/ghc-pwd.cabal copy to utils/genapply/genapply.cabal index dcd9529..dba3b6d 100644 --- a/utils/ghc-pwd/ghc-pwd.cabal +++ b/utils/genapply/genapply.cabal @@ -1,4 +1,4 @@ -Name: ghc-pwd +Name: genapply Version: 0.1 Copyright: XXX License: BSD3 @@ -7,13 +7,20 @@ License: BSD3 -- XXX Maintainer: Synopsis: XXX Description: - XXX + XXX build-type: Simple cabal-version: >=1.10 -Executable ghc-pwd +Flag unregisterised + description: Are we building an unregisterised compiler? + default: False + manual: True + +Executable genapply Default-Language: Haskell2010 Main-Is: Main.hs Build-Depends: base >= 3 && < 5, - directory >= 1 && < 1.3 + pretty + if flag(unregisterised) + Cpp-Options: -DNO_REGS diff --git a/utils/genapply/ghc.mk b/utils/genapply/ghc.mk index 2eea233..e0e5886 100644 --- a/utils/genapply/ghc.mk +++ b/utils/genapply/ghc.mk @@ -10,18 +10,14 @@ # # ----------------------------------------------------------------------------- -utils/genapply_dist_MODULES = GenApply -utils/genapply_dist_PROGNAME = genapply +utils/genapply_USES_CABAL = YES +utils/genapply_PACKAGE = genapply +utils/genapply_dist_PROGNAME = genapply +utils/genapply_dist_INSTALL = NO utils/genapply_dist_INSTALL_INPLACE = YES -utils/genapply_HC_OPTS += -package pretty - ifeq "$(GhcUnregisterised)" "YES" -utils/genapply_HC_OPTS += -DNO_REGS +utils/genapply_CONFIGURE_OPTS = --flag unregisterised endif -utils/genapply/GenApply.hs : includes/ghcconfig.h -utils/genapply/GenApply.hs : includes/MachRegs.h -utils/genapply/GenApply.hs : includes/Constants.h - $(eval $(call build-prog,utils/genapply,dist,0)) From git at git.haskell.org Thu Dec 17 11:54:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 17 Dec 2015 11:54:25 +0000 (UTC) Subject: [commit: ghc] master: Build system: Make cGhcRtsWithLibdw flag a proper Bool (109d847) Message-ID: <20151217115425.0C89E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/109d847971691a89dab6c80b37f46dc33197b8c2/ghc >--------------------------------------------------------------- commit 109d847971691a89dab6c80b37f46dc33197b8c2 Author: Ben Gamari Date: Thu Dec 17 12:14:53 2015 +0100 Build system: Make cGhcRtsWithLibdw flag a proper Bool Test Plan: validate Reviewers: austin Reviewed By: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1642 >--------------------------------------------------------------- 109d847971691a89dab6c80b37f46dc33197b8c2 compiler/ghc.mk | 8 ++++++-- compiler/main/DynFlags.hs | 15 +++++++-------- 2 files changed, 13 insertions(+), 10 deletions(-) diff --git a/compiler/ghc.mk b/compiler/ghc.mk index f5c53d4..9148c79 100644 --- a/compiler/ghc.mk +++ b/compiler/ghc.mk @@ -102,8 +102,12 @@ endif @echo 'cGhcWithSMP = "$(GhcWithSMP)"' >> $@ @echo 'cGhcRTSWays :: String' >> $@ @echo 'cGhcRTSWays = "$(GhcRTSWays)"' >> $@ - @echo 'cGhcRtsWithLibdw :: String' >> $@ - @echo 'cGhcRtsWithLibdw = "$(GhcRtsWithLibdw)"' >> $@ + @echo 'cGhcRtsWithLibdw :: Bool' >> $@ +ifeq "$(GhcRtsWithLibdw)" "YES" + @echo 'cGhcRtsWithLibdw = True' >> $@ +else + @echo 'cGhcRtsWithLibdw = False' >> $@ +endif @echo 'cGhcEnableTablesNextToCode :: String' >> $@ @echo 'cGhcEnableTablesNextToCode = "$(GhcEnableTablesNextToCode)"' >> $@ @echo 'cLeadingUnderscore :: String' >> $@ diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 03eb398..f6a551b 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -4117,25 +4117,24 @@ compilerInfo dflags ("Support SMP", cGhcWithSMP), ("Tables next to code", cGhcEnableTablesNextToCode), ("RTS ways", cGhcRTSWays), - ("RTS expects libdw", cGhcRtsWithLibdw), - ("Support dynamic-too", if isWindows then "NO" else "YES"), + ("RTS expects libdw", showBool cGhcRtsWithLibdw), + ("Support dynamic-too", showBool $ not isWindows), ("Support parallel --make", "YES"), ("Support reexported-modules", "YES"), ("Support thinning and renaming package flags", "YES"), ("Requires unified installed package IDs", "YES"), ("Uses package keys", "YES"), - ("Dynamic by default", if dYNAMIC_BY_DEFAULT dflags - then "YES" else "NO"), - ("GHC Dynamic", if dynamicGhc - then "YES" else "NO"), - ("GHC Profiled", if rtsIsProfiled - then "YES" else "NO"), + ("Dynamic by default", showBool $ dYNAMIC_BY_DEFAULT dflags), + ("GHC Dynamic", showBool dynamicGhc), + ("GHC Profiled", showBool rtsIsProfiled), ("Leading underscore", cLeadingUnderscore), ("Debug on", show debugIsOn), ("LibDir", topDir dflags), ("Global Package DB", systemPackageConfig dflags) ] where + showBool True = "YES" + showBool False = "NO" isWindows = platformOS (targetPlatform dflags) == OSMinGW32 #include "../includes/dist-derivedconstants/header/GHCConstantsHaskellWrappers.hs" From git at git.haskell.org Thu Dec 17 11:54:28 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 17 Dec 2015 11:54:28 +0000 (UTC) Subject: [commit: ghc] master: Conditionally show plural "s" in warnings (4f870f8) Message-ID: <20151217115428.5F3F73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4f870f8481b2611619adf66d61eff06f02e3741f/ghc >--------------------------------------------------------------- commit 4f870f8481b2611619adf66d61eff06f02e3741f Author: David Luposchainsky Date: Thu Dec 17 12:17:32 2015 +0100 Conditionally show plural "s" in warnings Redundant constraints and defaulting warnings had "constraint(s)" in their messages; the "s" is now conditional based on the number of things warned about. Reviewers: hvr, austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1647 >--------------------------------------------------------------- 4f870f8481b2611619adf66d61eff06f02e3741f compiler/typecheck/TcErrors.hs | 10 ++++-- compiler/typecheck/TcValidity.hs | 5 ++- .../tests/ghc-api/apirecomp001/apirecomp001.stderr | 40 +++++++++++----------- testsuite/tests/parser/should_compile/T2245.stderr | 38 ++++++++++---------- .../tests/typecheck/should_compile/T10971a.stderr | 34 +++++++++--------- .../tests/typecheck/should_fail/tcfail204.stderr | 20 +++++------ testsuite/tests/warnings/should_compile/PluralS.hs | 27 +++++++++++++++ .../tests/warnings/should_compile/PluralS.stderr | 26 ++++++++++++++ testsuite/tests/warnings/should_compile/all.T | 1 + 9 files changed, 131 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 4f870f8481b2611619adf66d61eff06f02e3741f From git at git.haskell.org Thu Dec 17 11:54:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 17 Dec 2015 11:54:31 +0000 (UTC) Subject: [commit: ghc] master: rules/haddock: Add EXTRA_HADDOCK_OPTS flag (e58a936) Message-ID: <20151217115431.0110A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e58a9361ac7e3699e298aa5c99398a21ac732500/ghc >--------------------------------------------------------------- commit e58a9361ac7e3699e298aa5c99398a21ac732500 Author: Ben Gamari Date: Thu Dec 17 12:15:27 2015 +0100 rules/haddock: Add EXTRA_HADDOCK_OPTS flag Allowing one to pass the new `--hyperlinked-source` option to generate pretty marked-up sources for the core libraries. Test Plan: Try it Reviewers: hvr, austin Reviewed By: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1643 >--------------------------------------------------------------- e58a9361ac7e3699e298aa5c99398a21ac732500 rules/haddock.mk | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/rules/haddock.mk b/rules/haddock.mk index f6978a7..3d3a83c 100644 --- a/rules/haddock.mk +++ b/rules/haddock.mk @@ -64,13 +64,14 @@ endif --hoogle \ --title="$$($1_PACKAGE)-$$($1_$2_VERSION)$$(if $$(strip $$($1_$2_SYNOPSIS)),: $$(strip $$($1_$2_SYNOPSIS)),)" \ --prologue="$1/$2/haddock-prologue.txt" \ - --optghc="-D__HADDOCK_VERSION__=$$(HADDOCK_VERSION_STRING)" \ + --optghc="-D__HADDOCK_VERSION__=$$(HADDOCK_VERSION_STRING)" \ $$(foreach mod,$$($1_$2_HIDDEN_MODULES),--hide=$$(mod)) \ $$(foreach pkg,$$($1_$2_DEPS),$$(if $$($$(pkg)_HADDOCK_FILE),--read-interface=../$$(pkg)$$(comma)../$$(pkg)/src/%{MODULE/./-}.html\#%{NAME}$$(comma)$$($$(pkg)_HADDOCK_FILE))) \ $$(foreach opt,$$($1_$2_$$(HADDOCK_WAY)_ALL_HC_OPTS),--optghc=$$(opt)) \ $$($1_$2_HADDOCK_FLAGS) $$($1_$2_HADDOCK_OPTS) \ $$($1_$2_HS_SRCS) \ $$($1_$2_EXTRA_HADDOCK_SRCS) \ + $$(EXTRA_HADDOCK_OPTS) \ +RTS -t"$1/$2/haddock.t" --machine-readable # --no-tmp-comp-dir above is important: it saves a few minutes in a From git at git.haskell.org Thu Dec 17 11:54:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 17 Dec 2015 11:54:34 +0000 (UTC) Subject: [commit: ghc] master: Reify DuplicateRecordFields by label, rather than by selector (4b161c9) Message-ID: <20151217115434.7D5A13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4b161c93dba774cc8051cf40a2024ad86f3259f2/ghc >--------------------------------------------------------------- commit 4b161c93dba774cc8051cf40a2024ad86f3259f2 Author: Adam Gundry Date: Thu Dec 17 12:19:23 2015 +0100 Reify DuplicateRecordFields by label, rather than by selector See `Note [Reifying field labels]` in `TcSplice`. This makes typical uses of TH work better with `DuplicateRecordFields`. If `reify` is called on the `Name` of a field label produced by the output of a previous `reify`, and there are multiple fields with that label defined in the same module, it may fail with an ambiguity error. Test Plan: Added tests, and manually tested that this makes Aeson's `deriveJSON` avoid the `$sel:` prefixes. Reviewers: simonpj, goldfire, austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1586 GHC Trac Issues: #11103 >--------------------------------------------------------------- 4b161c93dba774cc8051cf40a2024ad86f3259f2 compiler/typecheck/TcSplice.hs | 51 +++++++++++++++++++++- .../tests/overloadedrecflds/should_fail/T11103.hs | 20 +++++++++ .../overloadedrecflds/should_fail/T11103.stderr | 6 +++ .../tests/overloadedrecflds/should_fail/all.T | 1 + .../should_run/overloadedrecfldsrun04.hs | 15 ++++++- .../should_run/overloadedrecfldsrun04.stdout | 5 ++- 6 files changed, 95 insertions(+), 3 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 4b161c93dba774cc8051cf40a2024ad86f3259f2 From git at git.haskell.org Thu Dec 17 11:54:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 17 Dec 2015 11:54:38 +0000 (UTC) Subject: [commit: ghc] master: Add -fprint-typechecker-elaboration flag (fixes #10662) (d3dac4e) Message-ID: <20151217115438.09EF63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d3dac4e3c8c7032151a8b89040f799cc5a9575d8/ghc >--------------------------------------------------------------- commit d3dac4e3c8c7032151a8b89040f799cc5a9575d8 Author: Eugene Akentyev Date: Thu Dec 17 12:22:44 2015 +0100 Add -fprint-typechecker-elaboration flag (fixes #10662) Reviewers: thomie, austin, bgamari Reviewed By: thomie, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1625 GHC Trac Issues: #10662 >--------------------------------------------------------------- d3dac4e3c8c7032151a8b89040f799cc5a9575d8 compiler/hsSyn/HsBinds.hs | 22 ++++++++---- compiler/main/DynFlags.hs | 2 ++ docs/users_guide/using.rst | 41 ++++++++++++++++++++++ testsuite/tests/deSugar/should_compile/T10662.hs | 4 +++ .../tests/deSugar/should_compile/T10662.stderr | 6 ++++ testsuite/tests/deSugar/should_compile/all.T | 1 + testsuite/tests/roles/should_compile/T8958.stderr | 7 ++-- testsuite/tests/roles/should_compile/all.T | 2 +- utils/mkUserGuidePart/Options/Verbosity.hs | 6 ++++ 9 files changed, 80 insertions(+), 11 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d3dac4e3c8c7032151a8b89040f799cc5a9575d8 From git at git.haskell.org Thu Dec 17 11:54:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 17 Dec 2015 11:54:41 +0000 (UTC) Subject: [commit: ghc] master: Fix #11232. (cab1316) Message-ID: <20151217115441.1E3933A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cab131624ad0cdd54e2f3a70f93c1bd574ccf102/ghc >--------------------------------------------------------------- commit cab131624ad0cdd54e2f3a70f93c1bd574ccf102 Author: Richard Eisenberg Date: Thu Dec 17 12:18:47 2015 +0100 Fix #11232. I somehow forgot to propagate roles into UnivCos. Very simple fix, happily. Test Plan: simplCore/should_compile/T11232 Reviewers: bgamari, austin, simonpj Reviewed By: simonpj Subscribers: simonpj, thomie Differential Revision: https://phabricator.haskell.org/D1645 GHC Trac Issues: #11232 >--------------------------------------------------------------- cab131624ad0cdd54e2f3a70f93c1bd574ccf102 compiler/types/OptCoercion.hs | 37 ++++++++++++---------- testsuite/tests/simplCore/should_compile/T11232.hs | 15 +++++++++ testsuite/tests/simplCore/should_compile/all.T | 1 + 3 files changed, 36 insertions(+), 17 deletions(-) diff --git a/compiler/types/OptCoercion.hs b/compiler/types/OptCoercion.hs index f68bc8c..436b16a 100644 --- a/compiler/types/OptCoercion.hs +++ b/compiler/types/OptCoercion.hs @@ -87,21 +87,24 @@ optCoercion :: TCvSubst -> Coercion -> NormalCo -- *and* optimises it to reduce its size optCoercion env co | opt_NoOptCoercion = substCo env co - | debugIsOn = let out_co = opt_co1 lc False co - Pair in_ty1 in_ty2 = coercionKind co - Pair out_ty1 out_ty2 = coercionKind out_co - in - ASSERT2( substTy env in_ty1 `eqType` out_ty1 && - substTy env in_ty2 `eqType` out_ty2 - , text "optCoercion changed types!" - $$ hang (text "in_co:") 2 (ppr co) - $$ hang (text "in_ty1:") 2 (ppr in_ty1) - $$ hang (text "in_ty2:") 2 (ppr in_ty2) - $$ hang (text "out_co:") 2 (ppr out_co) - $$ hang (text "out_ty1:") 2 (ppr out_ty1) - $$ hang (text "out_ty2:") 2 (ppr out_ty2) - $$ hang (text "subst:") 2 (ppr env) ) - out_co + | debugIsOn + = let out_co = opt_co1 lc False co + (Pair in_ty1 in_ty2, in_role) = coercionKindRole co + (Pair out_ty1 out_ty2, out_role) = coercionKindRole out_co + in + ASSERT2( substTy env in_ty1 `eqType` out_ty1 && + substTy env in_ty2 `eqType` out_ty2 && + in_role == out_role + , text "optCoercion changed types!" + $$ hang (text "in_co:") 2 (ppr co) + $$ hang (text "in_ty1:") 2 (ppr in_ty1) + $$ hang (text "in_ty2:") 2 (ppr in_ty2) + $$ hang (text "out_co:") 2 (ppr out_co) + $$ hang (text "out_ty1:") 2 (ppr out_ty1) + $$ hang (text "out_ty2:") 2 (ppr out_ty2) + $$ hang (text "subst:") 2 (ppr env) ) + out_co + | otherwise = opt_co1 lc False co where lc = mkSubstLiftingContext env @@ -230,9 +233,9 @@ opt_co4 env sym rep r (AxiomInstCo con ind cos) cos) -- Note that the_co does *not* have sym pushed into it -opt_co4 env sym _ r (UnivCo prov _r t1 t2) +opt_co4 env sym rep r (UnivCo prov _r t1 t2) = ASSERT( r == _r ) - opt_univ env sym prov r t1 t2 + opt_univ env sym prov (chooseRole rep r) t1 t2 opt_co4 env sym rep r (TransCo co1 co2) -- sym (g `o` h) = sym h `o` sym g diff --git a/testsuite/tests/simplCore/should_compile/T11232.hs b/testsuite/tests/simplCore/should_compile/T11232.hs new file mode 100644 index 0000000..5b98d39 --- /dev/null +++ b/testsuite/tests/simplCore/should_compile/T11232.hs @@ -0,0 +1,15 @@ +module T11232 where + +import Control.Monad +import Data.Data + +mkMp :: ( MonadPlus m + , Typeable a + , Typeable b + ) + => (b -> m b) + -> a + -> m a +mkMp ext = unM (maybe (M (const mzero)) id (gcast (M ext))) + +newtype M m x = M { unM :: x -> m x } diff --git a/testsuite/tests/simplCore/should_compile/all.T b/testsuite/tests/simplCore/should_compile/all.T index f9388c9..2ea15f6 100644 --- a/testsuite/tests/simplCore/should_compile/all.T +++ b/testsuite/tests/simplCore/should_compile/all.T @@ -228,3 +228,4 @@ test('T11155', normal, run_command, ['$MAKE -s --no-print-directory T11155']) +test('T11232', normal, compile, ['-O2']) From git at git.haskell.org Thu Dec 17 11:54:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 17 Dec 2015 11:54:43 +0000 (UTC) Subject: [commit: ghc] master: users_guide: Remove extraneous vertical whitespace (575f0ad) Message-ID: <20151217115443.B33013A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/575f0ad67c2b036b686bf0b1b4d4c47d7d436b95/ghc >--------------------------------------------------------------- commit 575f0ad67c2b036b686bf0b1b4d4c47d7d436b95 Author: Ben Gamari Date: Thu Dec 17 12:26:43 2015 +0100 users_guide: Remove extraneous vertical whitespace >--------------------------------------------------------------- 575f0ad67c2b036b686bf0b1b4d4c47d7d436b95 docs/users_guide/using.rst | 96 ++++++++++++---------------------------------- 1 file changed, 24 insertions(+), 72 deletions(-) diff --git a/docs/users_guide/using.rst b/docs/users_guide/using.rst index 1253355..b936ea4 100644 --- a/docs/users_guide/using.rst +++ b/docs/users_guide/using.rst @@ -18,15 +18,11 @@ quick introduction to the basic usage of GHC for compiling a Haskell program, before the following sections dive into the full syntax. Let's create a Hello World program, and compile and run it. First, -create a file ``hello.hs`` containing the Haskell code: - -:: +create a file ``hello.hs`` containing the Haskell code: :: main = putStrLn "Hello, World!" -To compile the program, use GHC like this: - -:: +To compile the program, use GHC like this: :: $ ghc hello.hs @@ -40,9 +36,7 @@ By default GHC will be very quiet about what it is doing, only printing error messages. If you want to see in more detail what's going on behind the scenes, add ``-v`` to the command line. -Then we can run the program like this: - -:: +Then we can run the program like this: :: $ ./hello Hello World! @@ -72,9 +66,7 @@ Command-line arguments single: command-line; arguments single: arguments; command-line -An invocation of GHC takes the following form: - -:: +An invocation of GHC takes the following form: :: ghc [argument...] @@ -101,9 +93,7 @@ Haskell source file deliberately uses name shadowing, it should be compiled with the ``-Wno-name-shadowing`` option. Rather than maintaining the list of per-file options in a ``Makefile``, it is possible to do this directly in the source file using the -``OPTIONS_GHC`` :ref:`pragma `. - -:: +``OPTIONS_GHC`` :ref:`pragma ` :: {-# OPTIONS_GHC -Wno-name-shadowing #-} module X where @@ -362,17 +352,13 @@ Using ``ghc`` ``--make`` In this mode, GHC will build a multi-module Haskell program by following dependencies from one or more root modules (usually just ``Main``). For example, if your ``Main`` module is in a file called ``Main.hs``, you -could compile and link the program like this: - -:: +could compile and link the program like this: :: ghc --make Main.hs In fact, GHC enters make mode automatically if there are any Haskell source files on the command line and no other mode is specified, so in -this case we could just type - -:: +this case we could just type :: ghc Main.hs @@ -432,9 +418,7 @@ Expression evaluation mode This mode is very similar to interactive mode, except that there is a single expression to evaluate which is specified on the command line as -an argument to the ``-e`` option: - -:: +an argument to the ``-e`` option: :: ghc -e expr @@ -443,16 +427,12 @@ loaded exactly as in interactive mode. The expression is evaluated in the context of the loaded modules. For example, to load and run a Haskell program containing a module -``Main``, we might say - -:: +``Main``, we might say :: ghc -e Main.main Main.hs or we can just use this mode to evaluate expressions in the context of -the ``Prelude``: - -:: +the ``Prelude``: :: $ ghc -e "interact (unlines.map reverse.lines)" hello @@ -608,9 +588,7 @@ See also the ``--help``, ``--version``, ``--numeric-version``, and These three flags control the way in which GHC displays types, in error messages and in GHCi. Using ``-fprint-explicit-foralls`` makes GHC print explicit ``forall`` quantification at the top level of a - type; normally this is suppressed. For example, in GHCi: - - :: + type; normally this is suppressed. For example, in GHCi: :: ghci> let f x = x ghci> :t f @@ -622,17 +600,13 @@ See also the ``--help``, ``--version``, ``--numeric-version``, and However, regardless of the flag setting, the quantifiers are printed under these circumstances: - - For nested ``foralls``, e.g. - - :: + - For nested ``foralls``, e.g. :: ghci> :t GHC.ST.runST GHC.ST.runST :: (forall s. GHC.ST.ST s a) -> a - If any of the quantified type variables has a kind that mentions - a kind variable, e.g. - - :: + a kind variable, e.g. :: ghci> :i Data.Type.Equality.sym Data.Type.Equality.sym :: @@ -642,9 +616,7 @@ See also the ``--help``, ``--version``, ``--numeric-version``, and Using ``-fprint-explicit-kinds`` makes GHC print kind arguments in types, which are normally suppressed. This can be important when you - are using kind polymorphism. For example: - - :: + are using kind polymorphism. For example: :: ghci> :set -XPolyKinds ghci> data T a = MkT @@ -656,9 +628,7 @@ See also the ``--help``, ``--version``, ``--numeric-version``, and When ``-fprint-unicode-syntax`` is enabled, GHC prints type signatures using the unicode symbols from the ``-XUnicodeSyntax`` - extension. - - :: + extension. :: ghci> :set -fprint-unicode-syntax ghci> :t (>>) @@ -684,25 +654,19 @@ See also the ``--help``, ``--version``, ``--numeric-version``, and single: -fprint-expanded-synonyms When enabled, GHC also prints type-synonym-expanded types in type - errors. For example, with this type synonyms: - - :: + errors. For example, with this type synonyms: :: type Foo = Int type Bar = Bool type MyBarST s = ST s Bar - This error message: - - :: + This error message: :: Couldn't match type 'Int' with 'Bool' Expected type: ST s Foo Actual type: MyBarST s - Becomes this: - - :: + Becomes this: :: Couldn't match type 'Int' with 'Bool' Expected type: ST s Foo @@ -716,27 +680,21 @@ See also the ``--help``, ``--version``, ``--numeric-version``, and single: -fprint-typechecker-elaboration When enabled, GHC also prints extra information from the typechecker in - warnings. For example: - - :: + warnings. For example: :: main :: IO () main = do return $ let a = "hello" in a return () - This warning message: - - :: + This warning message: :: A do-notation statement discarded a result of type ?[Char]? Suppress this warning by saying ?_ <- ($) return let a = "hello" in a? or by using the flag -fno-warn-unused-do-bind - Becomes this: - - :: + Becomes this: :: A do-notation statement discarded a result of type ?[Char]? Suppress this warning by saying @@ -760,21 +718,15 @@ See also the ``--help``, ``--version``, ``--numeric-version``, and relating to an error message. Normally, GHC emits the source location of the start of the syntactic entity only. - For example: - - :: + For example: :: test.hs:3:6: parse error on input `where' - becomes: - - :: + becomes: :: test296.hs:3:6-10: parse error on input `where' - And multi-line spans are possible too: - - :: + And multi-line spans are possible too: :: test.hs:(5,4)-(6,7): Conflicting definitions for `a' From git at git.haskell.org Thu Dec 17 12:29:22 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 17 Dec 2015 12:29:22 +0000 (UTC) Subject: [commit: ghc] master: Improve pretty-printing in pprIfaceIdBndr (e7f22bf) Message-ID: <20151217122922.8C3F83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e7f22bfb70d82dc92eb5ac5579d763e1a1f5522d/ghc >--------------------------------------------------------------- commit e7f22bfb70d82dc92eb5ac5579d763e1a1f5522d Author: Simon Peyton Jones Date: Mon Dec 14 13:34:26 2015 +0000 Improve pretty-printing in pprIfaceIdBndr In particular, add parnes when we need an explicit type. >--------------------------------------------------------------- e7f22bfb70d82dc92eb5ac5579d763e1a1f5522d compiler/iface/IfaceType.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/iface/IfaceType.hs b/compiler/iface/IfaceType.hs index f744f81..640d104 100644 --- a/compiler/iface/IfaceType.hs +++ b/compiler/iface/IfaceType.hs @@ -565,7 +565,7 @@ pprIfaceLamBndr (b, IfaceNoOneShot) = ppr b pprIfaceLamBndr (b, IfaceOneShot) = ppr b <> text "[OneShot]" pprIfaceIdBndr :: (IfLclName, IfaceType) -> SDoc -pprIfaceIdBndr (name, ty) = hsep [ppr name, dcolon, ppr ty] +pprIfaceIdBndr (name, ty) = parens (ppr name <+> dcolon <+> ppr ty) pprIfaceTvBndr :: IfaceTvBndr -> SDoc pprIfaceTvBndr (tv, IfaceTyConApp tc ITC_Nil) From git at git.haskell.org Thu Dec 17 12:29:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 17 Dec 2015 12:29:25 +0000 (UTC) Subject: [commit: ghc] master: Remove unused T10524.stderr (e32c2e1) Message-ID: <20151217122925.2BA633A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e32c2e1f2c0adbed1f726233d3552bf5e9aad833/ghc >--------------------------------------------------------------- commit e32c2e1f2c0adbed1f726233d3552bf5e9aad833 Author: Simon Peyton Jones Date: Wed Dec 16 10:38:54 2015 +0000 Remove unused T10524.stderr >--------------------------------------------------------------- e32c2e1f2c0adbed1f726233d3552bf5e9aad833 testsuite/tests/deriving/should_fail/T10524.stderr | 10 ---------- 1 file changed, 10 deletions(-) diff --git a/testsuite/tests/deriving/should_fail/T10524.stderr b/testsuite/tests/deriving/should_fail/T10524.stderr deleted file mode 100644 index 1569972..0000000 --- a/testsuite/tests/deriving/should_fail/T10524.stderr +++ /dev/null @@ -1,10 +0,0 @@ - -T10524.hs:7:58: error: - No instance for (Typeable WrappedFunctor) - arising from the 'deriving' clause of a data type declaration - GHC can't yet do polykinded - Typeable (WrappedFunctor :: (k -> *) -> k -> *) - Possible fix: - use a standalone 'deriving instance' declaration, - so you can specify the instance context yourself - When deriving the instance for (Data (WrappedFunctor f a)) From git at git.haskell.org Thu Dec 17 12:42:02 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 17 Dec 2015 12:42:02 +0000 (UTC) Subject: [commit: ghc] master: Update Cabal submodule (89d70f9) Message-ID: <20151217124202.1FB5C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/89d70f9fe1ea989887cc73de2b71c7701c257e7a/ghc >--------------------------------------------------------------- commit 89d70f9fe1ea989887cc73de2b71c7701c257e7a Author: Ben Gamari Date: Thu Dec 17 13:41:09 2015 +0100 Update Cabal submodule Previously it didn't build on Windows. >--------------------------------------------------------------- 89d70f9fe1ea989887cc73de2b71c7701c257e7a libraries/Cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Cabal b/libraries/Cabal index 4e33454..e275a16 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit 4e33454f5566c1ad3339c4bdf7444dff6c8fc21f +Subproject commit e275a162ccac087f8b25b424551e8a1598dd5943 From git at git.haskell.org Thu Dec 17 15:00:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 17 Dec 2015 15:00:13 +0000 (UTC) Subject: [commit: ghc] master: T9961 allocations crept further upwards (aee58e1) Message-ID: <20151217150013.C50EB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/aee58e166c771ab1f72d22c008ecb326488c0909/ghc >--------------------------------------------------------------- commit aee58e166c771ab1f72d22c008ecb326488c0909 Author: Ben Gamari Date: Thu Dec 17 16:10:18 2015 +0200 T9961 allocations crept further upwards Sad. >--------------------------------------------------------------- aee58e166c771ab1f72d22c008ecb326488c0909 testsuite/tests/perf/compiler/all.T | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index ae093be..184628a 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -714,11 +714,12 @@ test('T9872d', test('T9961', [ only_ways(['normal']), compiler_stats_num_field('bytes allocated', - [(wordsize(64), 708680480, 5), + [(wordsize(64), 745044392, 5), # 2015-01-12 807117816 Initally created # 2015-spring 772510192 Got better # 2015-05-22 663978160 Fix for #10370 improves it more - # 2015-10-28 708680480 Emit Typeable at definition site + # 2015-10-28 708680480 x86_64/Linux Emit Typeable at definition site + # 2015-12-17 745044392 x86_64/Darwin Creep upwards (wordsize(32), 375647160, 5) ]), ], From git at git.haskell.org Thu Dec 17 15:00:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 17 Dec 2015 15:00:16 +0000 (UTC) Subject: [commit: ghc] master: Disable recomp015 on ARM (e2e24f2) Message-ID: <20151217150016.6E08D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e2e24f2808561e5e6e1086e2ee15bf320d879e46/ghc >--------------------------------------------------------------- commit e2e24f2808561e5e6e1086e2ee15bf320d879e46 Author: Ben Gamari Date: Thu Dec 17 15:24:41 2015 +0100 Disable recomp015 on ARM Due to differences in assembly syntax. See #11022. >--------------------------------------------------------------- e2e24f2808561e5e6e1086e2ee15bf320d879e46 testsuite/tests/driver/recomp015/all.T | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/driver/recomp015/all.T b/testsuite/tests/driver/recomp015/all.T index 4ab3e88..1b91218 100644 --- a/testsuite/tests/driver/recomp015/all.T +++ b/testsuite/tests/driver/recomp015/all.T @@ -2,7 +2,9 @@ test('recomp015', [ clean_cmd('$MAKE -s clean'), - unless(opsys('linux') or opsys('solaris2') or opsys('openbsd'), skip)], + # See ticket:11022#comment:7 + unless(opsys('linux') or opsys('solaris2') or opsys('openbsd'), skip), + when(arch('arm'), skip)], run_command, ['$MAKE -s --no-print-directory recomp015']) From git at git.haskell.org Thu Dec 17 15:53:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 17 Dec 2015 15:53:55 +0000 (UTC) Subject: [commit: ghc] master: Remove warning-suppression flags for Cabal (ece8aff) Message-ID: <20151217155355.7948A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ece8aff3470cac4cce497004bf8b7ea52612f095/ghc >--------------------------------------------------------------- commit ece8aff3470cac4cce497004bf8b7ea52612f095 Author: Herbert Valerio Riedel Date: Thu Dec 17 16:52:55 2015 +0100 Remove warning-suppression flags for Cabal Cabal is currently warning free. So let's drop the `-w`-flags. /cc @dcoutts >--------------------------------------------------------------- ece8aff3470cac4cce497004bf8b7ea52612f095 mk/warnings.mk | 5 ----- 1 file changed, 5 deletions(-) diff --git a/mk/warnings.mk b/mk/warnings.mk index dd79673..7efcf08 100644 --- a/mk/warnings.mk +++ b/mk/warnings.mk @@ -47,11 +47,6 @@ SRC_HC_WARNING_OPTS_STAGE2 += -Wnoncanonical-monad-instances # Libraries that have dubious RULES libraries/bytestring_dist-install_EXTRA_HC_OPTS += -Wno-inline-rule-shadowing -# Cabal doesn't promise to be warning-free -utils/ghc-cabal_dist_EXTRA_HC_OPTS += -w -libraries/Cabal/Cabal_dist-boot_EXTRA_HC_OPTS += -w -libraries/Cabal/Cabal_dist-install_EXTRA_HC_OPTS += -w - # Turn off import warnings for bad unused imports libraries/containers_dist-install_EXTRA_HC_OPTS += -Wno-unused-imports libraries/bytestring_dist-install_EXTRA_HC_OPTS += -Wno-unused-imports From git at git.haskell.org Thu Dec 17 17:22:06 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 17 Dec 2015 17:22:06 +0000 (UTC) Subject: [commit: ghc] master: Testsuite: #10712 is fixed (a2f04a2) Message-ID: <20151217172206.844CA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a2f04a26fe6bf989fb3575d73cb2a07464ab81a5/ghc >--------------------------------------------------------------- commit a2f04a26fe6bf989fb3575d73cb2a07464ab81a5 Author: Thomas Miedema Date: Thu Dec 17 18:18:30 2015 +0100 Testsuite: #10712 is fixed Verified by running: make TEST='exceptionsrun001 T3279 conc012 conc014' slowtest >--------------------------------------------------------------- a2f04a26fe6bf989fb3575d73cb2a07464ab81a5 libraries/base/tests/all.T | 2 +- testsuite/tests/concurrent/should_run/all.T | 6 +++--- 2 files changed, 4 insertions(+), 4 deletions(-) diff --git a/libraries/base/tests/all.T b/libraries/base/tests/all.T index 00b653b..da14cb2 100644 --- a/libraries/base/tests/all.T +++ b/libraries/base/tests/all.T @@ -84,7 +84,7 @@ test('enum02', enum_setups, compile_and_run, ['']) test('enum03', enum_setups, compile_and_run, ['']) test('enum04', normal, compile_and_run, ['']) -test('exceptionsrun001', expect_broken_for(10712, opt_ways), compile_and_run, ['']) +test('exceptionsrun001', normal, compile_and_run, ['']) test('exceptionsrun002', normal, compile_and_run, ['']) test('foldableArray', normal, compile_and_run, ['']) test('list001' , when(fast(), skip), compile_and_run, ['']) diff --git a/testsuite/tests/concurrent/should_run/all.T b/testsuite/tests/concurrent/should_run/all.T index 760ac18..1dd1e1a 100644 --- a/testsuite/tests/concurrent/should_run/all.T +++ b/testsuite/tests/concurrent/should_run/all.T @@ -32,7 +32,7 @@ test('T367_letnoescape', test('T1980', normal, compile_and_run, ['']) test('T2910', normal, compile_and_run, ['']) test('T2910a', normal, compile_and_run, ['']) -test('T3279', expect_broken_for(10712, opt_ways), compile_and_run, ['']) +test('T3279', normal, compile_and_run, ['']) # This test takes a long time with the default context switch interval test('T3429', extra_run_opts('+RTS -C0.001 -RTS'), compile_and_run, ['']) @@ -126,11 +126,11 @@ test('conc010', normal, compile_and_run, ['']) # conc012(ghci) needs a smaller stack, or it takes forever test('conc012', - [extra_run_opts('+RTS -K8m -RTS'), expect_broken_for(10712, opt_ways)], + extra_run_opts('+RTS -K8m -RTS'), compile_and_run, ['']) test('conc013', normal, compile_and_run, ['']) -test('conc014', expect_broken_for(10712, opt_ways), compile_and_run, ['']) +test('conc014', normal, compile_and_run, ['']) test('conc015', normal, compile_and_run, ['']) test('conc015a', normal, compile_and_run, ['']) test('conc016', omit_ways(['threaded2']), # see comment in conc016.hs From git at git.haskell.org Thu Dec 17 17:22:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 17 Dec 2015 17:22:09 +0000 (UTC) Subject: [commit: ghc] master: Lexer: update outdated comments [skip ci] (9d9c534) Message-ID: <20151217172209.320823A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9d9c534796bf7ecc6271603707450b8d297aeb4a/ghc >--------------------------------------------------------------- commit 9d9c534796bf7ecc6271603707450b8d297aeb4a Author: Thomas Miedema Date: Wed Nov 11 02:17:56 2015 +0100 Lexer: update outdated comments [skip ci] The test for TemplateHaskell was removed in 09015be8d580bc33f5f1960c8e31d00ba7a459a1. >--------------------------------------------------------------- 9d9c534796bf7ecc6271603707450b8d297aeb4a compiler/parser/Lexer.x | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/compiler/parser/Lexer.x b/compiler/parser/Lexer.x index 084cd9e..cee8540 100644 --- a/compiler/parser/Lexer.x +++ b/compiler/parser/Lexer.x @@ -1425,9 +1425,9 @@ lex_stringgap s = do lex_char_tok :: Action -- Here we are basically parsing character literals, such as 'x' or '\n' --- but, when Template Haskell is on, we additionally spot --- 'x and ''T, returning ITsimpleQuote and ITtyQuote respectively, --- but WITHOUT CONSUMING the x or T part (the parser does that). +-- but we additionally spot 'x and ''T, returning ITsimpleQuote and +-- ITtyQuote respectively, but WITHOUT CONSUMING the x or T part +-- (the parser does that). -- So we have to do two characters of lookahead: when we see 'x we need to -- see if there's a trailing quote lex_char_tok span buf _len = do -- We've seen ' @@ -1460,7 +1460,7 @@ lex_char_tok span buf _len = do -- We've seen ' finish_char_tok buf loc c _other -> do -- We've seen 'x not followed by quote -- (including the possibility of EOF) - -- If TH is on, just parse the quote only + -- Just parse the quote only let (AI end _) = i1 return (L (mkRealSrcSpan loc end) ITsimpleQuote) From git at git.haskell.org Thu Dec 17 17:42:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 17 Dec 2015 17:42:40 +0000 (UTC) Subject: [commit: ghc] master: IO Handles: update comments [skip ci] (1b6323b) Message-ID: <20151217174240.784753A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1b6323b3ad576ef1806170d8cea871038b51de5e/ghc >--------------------------------------------------------------- commit 1b6323b3ad576ef1806170d8cea871038b51de5e Author: Thomas Miedema Date: Mon Dec 14 17:00:27 2015 +0100 IO Handles: update comments [skip ci] * hSetEcho, hGetEcho and hIsTerminalDevice are part of the Haskell2010 report (but not Haskell98) * there are great `Note`s in GHC.IO.Handle.Types. Link to them. >--------------------------------------------------------------- 1b6323b3ad576ef1806170d8cea871038b51de5e libraries/base/GHC/IO/Handle.hs | 2 +- libraries/base/GHC/IO/Handle/Internals.hs | 12 ++++++++---- libraries/base/GHC/IO/Handle/Types.hs | 4 ++-- 3 files changed, 11 insertions(+), 7 deletions(-) diff --git a/libraries/base/GHC/IO/Handle.hs b/libraries/base/GHC/IO/Handle.hs index 750dbf7..c1d15a9 100644 --- a/libraries/base/GHC/IO/Handle.hs +++ b/libraries/base/GHC/IO/Handle.hs @@ -508,7 +508,7 @@ hIsSeekable handle = _ -> IODevice.isSeekable haDevice -- ----------------------------------------------------------------------------- --- Changing echo status (Non-standard GHC extensions) +-- Changing echo status -- | Set the echoing status of a handle connected to a terminal. diff --git a/libraries/base/GHC/IO/Handle/Internals.hs b/libraries/base/GHC/IO/Handle/Internals.hs index 581eb9b..5d8ddfd 100644 --- a/libraries/base/GHC/IO/Handle/Internals.hs +++ b/libraries/base/GHC/IO/Handle/Internals.hs @@ -480,15 +480,19 @@ flushCharBuffer h_ at Handle__{..} = do ReadBuffer -> do flushCharReadBuffer h_ WriteBuffer -> + -- Nothing to do here. Char buffer on a write Handle is always empty + -- between Handle operations. + -- See [note Buffer Flushing], GHC.IO.Handle.Types. when (not (isEmptyBuffer cbuf)) $ error "internal IO library error: Char buffer non-empty" -- ----------------------------------------------------------------------------- -- Writing data (flushing write buffers) --- flushWriteBuffer flushes the buffer iff it contains pending write --- data. Flushes both the Char and the byte buffer, leaving both --- empty. +-- flushWriteBuffer flushes the byte buffer iff it contains pending write +-- data. Because the Char buffer on a write Handle is always empty between +-- Handle operations (see [note Buffer Flushing], GHC.IO.Handle.Types), +-- both buffers are empty after this. flushWriteBuffer :: Handle__ -> IO () flushWriteBuffer h_ at Handle__{..} = do buf <- readIORef haByteBuffer @@ -519,7 +523,7 @@ writeCharBuffer h_ at Handle__{..} !cbuf = do debugIO ("writeCharBuffer after encoding: cbuf=" ++ summaryBuffer cbuf' ++ " bbuf=" ++ summaryBuffer bbuf') - -- flush if the write buffer is full + -- flush the byte buffer if it is full if isFullBuffer bbuf' -- or we made no progress || not (isEmptyBuffer cbuf') && bufL cbuf' == bufL cbuf diff --git a/libraries/base/GHC/IO/Handle/Types.hs b/libraries/base/GHC/IO/Handle/Types.hs index c784c5c..195054a 100644 --- a/libraries/base/GHC/IO/Handle/Types.hs +++ b/libraries/base/GHC/IO/Handle/Types.hs @@ -122,10 +122,10 @@ data Handle__ Handle__ { haDevice :: !dev, haType :: HandleType, -- type (read/write/append etc.) - haByteBuffer :: !(IORef (Buffer Word8)), + haByteBuffer :: !(IORef (Buffer Word8)), -- See [note Buffering Implementation] haBufferMode :: BufferMode, haLastDecode :: !(IORef (dec_state, Buffer Word8)), - haCharBuffer :: !(IORef (Buffer CharBufElem)), -- the current buffer + haCharBuffer :: !(IORef (Buffer CharBufElem)), -- See [note Buffering Implementation] haBuffers :: !(IORef (BufferList CharBufElem)), -- spare buffers haEncoder :: Maybe (TextEncoder enc_state), haDecoder :: Maybe (TextDecoder dec_state), From git at git.haskell.org Thu Dec 17 17:57:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 17 Dec 2015 17:57:47 +0000 (UTC) Subject: [commit: ghc] master: Fix tcTyClTyVars to handle SigTvs (ae86eb9) Message-ID: <20151217175747.ED48D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ae86eb9f72fa7220fe47ac54d6d21395691c1308/ghc >--------------------------------------------------------------- commit ae86eb9f72fa7220fe47ac54d6d21395691c1308 Author: Richard Eisenberg Date: Tue Dec 15 13:47:14 2015 -0500 Fix tcTyClTyVars to handle SigTvs Previously, tcTyClTyVars required that the names of the LHsQTyVars matched up exactly with the names of the kind of the given TyCon. It now does a bit of matching up when necessary to relax this restriction. This commit enables a few tests that had previously been disabled. The shortcoming this addresses is discussed in #11203, but that ticket is not directly addressed here. Test case: polykinds/SigTvKinds, perf/compiler/T9872d >--------------------------------------------------------------- ae86eb9f72fa7220fe47ac54d6d21395691c1308 compiler/typecheck/TcHsType.hs | 179 +++++++++++++++++++++++++----------- testsuite/tests/perf/compiler/all.T | 12 +-- testsuite/tests/polykinds/all.T | 2 +- 3 files changed, 130 insertions(+), 63 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ae86eb9f72fa7220fe47ac54d6d21395691c1308 From git at git.haskell.org Thu Dec 17 17:57:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 17 Dec 2015 17:57:51 +0000 (UTC) Subject: [commit: ghc] master: Fix #11230. (1722fa1) Message-ID: <20151217175751.3AC093A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1722fa106e10e63160bb2322e2ccb830fd5b9ab3/ghc >--------------------------------------------------------------- commit 1722fa106e10e63160bb2322e2ccb830fd5b9ab3 Author: Richard Eisenberg Date: Tue Dec 15 17:36:32 2015 -0500 Fix #11230. Previously, we were optimizing away all case expressions over coercions with dead binders. But sometimes we want to force the coercion expression. Like when it contains an error. Test case: typecheck/should_run/T11230 >--------------------------------------------------------------- 1722fa106e10e63160bb2322e2ccb830fd5b9ab3 compiler/coreSyn/CoreSubst.hs | 11 ++++---- .../indexed-types/should_compile/T7837.stderr | 3 +++ testsuite/tests/typecheck/should_run/T11230.hs | 31 ++++++++++++++++++++++ testsuite/tests/typecheck/should_run/T11230.stdout | 2 ++ testsuite/tests/typecheck/should_run/all.T | 1 + 5 files changed, 42 insertions(+), 6 deletions(-) diff --git a/compiler/coreSyn/CoreSubst.hs b/compiler/coreSyn/CoreSubst.hs index 0668816..e77886b 100644 --- a/compiler/coreSyn/CoreSubst.hs +++ b/compiler/coreSyn/CoreSubst.hs @@ -56,8 +56,7 @@ import Coercion hiding ( substCo, substCoVarBndr ) import TyCon ( tyConArity ) import DataCon -import PrelNames ( heqDataConKey, coercibleDataConKey, unpackCStringIdKey - , unpackCStringUtf8IdKey ) +import PrelNames import OptCoercion ( optCoercion ) import PprCore ( pprCoreBindings, pprRules ) import Module ( Module ) @@ -67,7 +66,6 @@ import Id import Name ( Name ) import Var import IdInfo -import Unique import UniqSupply import Maybes import ErrUtils @@ -840,9 +838,7 @@ separate actions: is made in maybe_substitute. Note the rather specific check for MkCoercible in there. - 2. Stripping silly case expressions, like the Coercible_SCSel one. - A case expression is silly if its binder is dead, it has only one, - DEFAULT, alternative, and the scrutinee is a coercion. + 2. Stripping case expressions like the Coercible_SCSel one. See the `Case` case of simple_opt_expr's `go` function. 3. Look for case expressions that unpack something that was @@ -952,6 +948,9 @@ simple_opt_expr subst expr | isDeadBinder b , [(DEFAULT, _, rhs)] <- as , isCoercionType (varType b) + , (Var fun, _args) <- collectArgs e + , fun `hasKey` coercibleSCSelIdKey + -- without this last check, we get #11230 = go rhs | otherwise diff --git a/testsuite/tests/indexed-types/should_compile/T7837.stderr b/testsuite/tests/indexed-types/should_compile/T7837.stderr index 838a8fb..a4d96b1 100644 --- a/testsuite/tests/indexed-types/should_compile/T7837.stderr +++ b/testsuite/tests/indexed-types/should_compile/T7837.stderr @@ -1,3 +1,6 @@ Rule fired: Class op signum Rule fired: Class op abs Rule fired: normalize/Double +Rule fired: Class op HEq_sc +Rule fired: Class op HEq_sc +Rule fired: Class op HEq_sc diff --git a/testsuite/tests/typecheck/should_run/T11230.hs b/testsuite/tests/typecheck/should_run/T11230.hs new file mode 100644 index 0000000..769b6ba --- /dev/null +++ b/testsuite/tests/typecheck/should_run/T11230.hs @@ -0,0 +1,31 @@ +{-# LANGUAGE RoleAnnotations #-} +{-# OPTIONS_GHC -fdefer-type-errors #-} + +module Main where + +import Control.Exception + +newtype Representational a = Representational () +type role Representational representational + +newtype Phantom a = Phantom () +type role Phantom phantom + +testRepresentational :: Representational Char -> Representational Bool +testRepresentational = id +{-# NOINLINE testRepresentational #-} + +testPhantom :: Phantom Char -> Phantom Bool +testPhantom = id +{-# NOINLINE testPhantom #-} + +throwsException :: String -> a -> IO () +throwsException c v = do + result <- try (evaluate v) + case result of + Right _ -> error (c ++ " (Failure): No exception!") + Left (TypeError _) -> putStrLn (c ++ "(Success): exception found") + +main = do + throwsException "representational" testRepresentational + throwsException "phantom" testPhantom diff --git a/testsuite/tests/typecheck/should_run/T11230.stdout b/testsuite/tests/typecheck/should_run/T11230.stdout new file mode 100644 index 0000000..b0ccf01 --- /dev/null +++ b/testsuite/tests/typecheck/should_run/T11230.stdout @@ -0,0 +1,2 @@ +representational(Success): exception found +phantom(Success): exception found diff --git a/testsuite/tests/typecheck/should_run/all.T b/testsuite/tests/typecheck/should_run/all.T index def9ede..1c4f234 100755 --- a/testsuite/tests/typecheck/should_run/all.T +++ b/testsuite/tests/typecheck/should_run/all.T @@ -111,3 +111,4 @@ test('T9497c-run', [exit_code(1)], compile_and_run, ['-fdefer-type-errors -fno-w test('T9858c', normal, compile_and_run, ['']) test('T9858d', normal, compile_and_run, ['']) test('T10284', exit_code(1), compile_and_run, ['']) +test('T11230', normal, compile_and_run, ['']) From git at git.haskell.org Thu Dec 17 20:25:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 17 Dec 2015 20:25:32 +0000 (UTC) Subject: [commit: ghc] master: Build system: also put scripts in libexecdir/bin (c1bd3d4) Message-ID: <20151217202532.D15883A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c1bd3d444f8c52c688fdbea695ee0ae7f402945d/ghc >--------------------------------------------------------------- commit c1bd3d444f8c52c688fdbea695ee0ae7f402945d Author: Thomas Miedema Date: Thu Dec 17 19:45:13 2015 +0100 Build system: also put scripts in libexecdir/bin This follows a similar change in 4905b83a2d448c65ccced385343d4e8124548a3b, where binaries are installed in libexecdir/bin instead of libexecdir. This fixes a problem with ghc not able to find ghc-split, when SplitObjs=YES. >--------------------------------------------------------------- c1bd3d444f8c52c688fdbea695ee0ae7f402945d ghc.mk | 17 ++++++----------- mk/install.mk.in | 5 ----- rules/build-perl.mk | 6 +++--- 3 files changed, 9 insertions(+), 19 deletions(-) diff --git a/ghc.mk b/ghc.mk index 64eb9bb..4455eb9 100644 --- a/ghc.mk +++ b/ghc.mk @@ -851,7 +851,7 @@ TAGS: TAGS_compiler # Installation install: install_libs install_packages install_libexecs \ - install_bins install_topdirs + install_bins install_libexec_scripts ifeq "$(HADDOCK_DOCS)" "YES" install: install_docs endif @@ -910,14 +910,11 @@ ifeq "$(Windows_Host)" "NO" endif endif -install_topdirs: $(INSTALL_TOPDIR_BINS) $(INSTALL_TOPDIR_SCRIPTS) - $(INSTALL_DIR) "$(DESTDIR)$(topdir)" - for i in $(INSTALL_TOPDIR_BINS); do \ - $(INSTALL_PROGRAM) $(INSTALL_BIN_OPTS) $$i "$(DESTDIR)$(topdir)"; \ - done -ifneq "$(INSTALL_TOPDIR_SCRIPTS)" "" - for i in $(INSTALL_TOPDIR_SCRIPTS); do \ - $(INSTALL_SCRIPT) $(INSTALL_OPTS) $$i "$(DESTDIR)$(topdir)"; \ +install_libexec_scripts: $(INSTALL_LIBEXEC_SCRIPTS) +ifneq "$(INSTALL_LIBEXEC_SCRIPTS)" "" + $(INSTALL_DIR) "$(DESTDIR)$(ghclibexecdir)/bin" + for i in $(INSTALL_LIBEXEC_SCRIPTS); do \ + $(INSTALL_SCRIPT) $(INSTALL_OPTS) $$i "$(DESTDIR)$(ghclibexecdir)/bin"; \ done endif @@ -1035,8 +1032,6 @@ $(eval $(call bindist-list,.,\ $(libffi_HEADERS) \ $(INSTALL_LIBEXECS) \ $(INSTALL_LIBEXEC_SCRIPTS) \ - $(INSTALL_TOPDIR_BINS) \ - $(INSTALL_TOPDIR_SCRIPTS) \ $(INSTALL_BINS) \ $(INSTALL_SCRIPTS) \ $(INSTALL_MANPAGES) \ diff --git a/mk/install.mk.in b/mk/install.mk.in index 38e6459..e404397 100644 --- a/mk/install.mk.in +++ b/mk/install.mk.in @@ -100,11 +100,6 @@ else # Unix: override libdir and datadir to put ghc-specific stuff in # a subdirectory with the version number included. -# -# datadir is set to libdir here as GHC needs package.conf and unlit -# to be in the same place (and things like ghc-pkg need to agree on -# where package.conf is, so we just set it globally). -# ghclibdir = $(libdir)/$(CrossCompilePrefix)ghc-$(ProjectVersion) ghcdocdir = $(datarootdir)/doc/ghc endif diff --git a/rules/build-perl.mk b/rules/build-perl.mk index 5a1660c..58660fc 100644 --- a/rules/build-perl.mk +++ b/rules/build-perl.mk @@ -36,7 +36,7 @@ ifneq "$$($$($1_$2_PROG)_INPLACE)" "" $$(error $$($1_$2_PROG)_INPLACE defined twice) endif ifeq "$$($1_$2_TOPDIR)" "YES" -$$($1_$2_PROG)_INPLACE = $$(INPLACE_TOPDIR)/$$($1_$2_PROG) +$$($1_$2_PROG)_INPLACE = $$(INPLACE_LIB)/bin/$$($1_$2_PROG) else $$($1_$2_PROG)_INPLACE = $$(INPLACE_BIN)/$$($1_$2_PROG) endif @@ -66,11 +66,11 @@ $$($1_$2_INPLACE): $1/$2/$$($1_$2_PROG) | $$$$(dir $$$$@)/. endif ifeq "$$($1_$2_INSTALL)" "YES" -# Don't add to INSTALL_BINS or INSTAL_TOPDIR_BINS, because they will get +# Don't add to INSTALL_BINS or INSTALL_LIBEXECS, because they will get # stripped when calling 'make install-strip', and stripping a Perl script # doesn't work. ifeq "$$($1_$2_TOPDIR)" "YES" -INSTALL_TOPDIR_SCRIPTS += $$($1_$2_INPLACE) +INSTALL_LIBEXEC_SCRIPTS += $$($1_$2_INPLACE) else INSTALL_SCRIPTS += $$($1_$2_INPLACE) endif From git at git.haskell.org Thu Dec 17 20:25:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 17 Dec 2015 20:25:35 +0000 (UTC) Subject: [commit: ghc] master: Testsuite: allow spaces in TEST_HC passed in by the user (272e1cc) Message-ID: <20151217202535.79ADA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/272e1cc811e5d693d8a36e63c90a1ece68a0495a/ghc >--------------------------------------------------------------- commit 272e1cc811e5d693d8a36e63c90a1ece68a0495a Author: Thomas Miedema Date: Wed Oct 28 10:35:08 2015 +0100 Testsuite: allow spaces in TEST_HC passed in by the user Don't use the GNU make function 'realpath' (reverting e66a81c6), because it doesn't handle spaces in paths. Instead, use 'cygpath' to convert Windows style paths (e.g. C:/foo/) to mingw style paths (e.g. c/foo/), and then call 'which'. Tests: * make TEST_HC=ghc * make TEST_HC=/d/home/thomie/ghc-validate/bindisttest/install\ \ \ dir/bin/ghc * make TEST_HC=D:/home/thomie/ghc-validate/bindisttest/install\ \ \ dir/bin/ghc Reviewed by: Phyx Differential Revision: https://phabricator.haskell.org/D1431 >--------------------------------------------------------------- 272e1cc811e5d693d8a36e63c90a1ece68a0495a testsuite/mk/boilerplate.mk | 30 +++++++++++++----------------- 1 file changed, 13 insertions(+), 17 deletions(-) diff --git a/testsuite/mk/boilerplate.mk b/testsuite/mk/boilerplate.mk index 3039879..5f4a3e9 100644 --- a/testsuite/mk/boilerplate.mk +++ b/testsuite/mk/boilerplate.mk @@ -24,7 +24,9 @@ show: define canonicalise # $1 = path variable -$1_CYGPATH := $$(shell $(SHELL) -c "cygpath -m '$$($1)'" 2> /dev/null) +# Don't use 'cygpath -m', because it doesn't change drive letters to +# something 'which' can understand. +$1_CYGPATH := $$(shell $(SHELL) -c "cygpath '$$($1)'" 2> /dev/null) ifneq "$$($1_CYGPATH)" "" # We use 'override' in case we are trying to update a value given on # the commandline (e.g. TEST_HC) @@ -121,25 +123,19 @@ else IMPLICIT_COMPILER = NO endif IN_TREE_COMPILER = NO -# We want to support both "ghc" and "/usr/bin/ghc" as values of TEST_HC -# passed in by the user, but -# which ghc == /usr/bin/ghc -# which /usr/bin/ghc == /usr/bin/ghc -# so on unix-like platforms we can just always 'which' it. -# However, on cygwin, we can't just use which: -# $ which c:/ghc/ghc-7.4.1/bin/ghc.exe -# which: no ghc.exe in (./c:/ghc/ghc-7.4.1/bin) -# so we start off by using realpath, and if that succeeds then we use -# that value. Otherwise we fall back on 'which'. -# + +# As values of TEST_HC passed in by the user, we want to support: +# * both "ghc" and "/usr/bin/ghc" +# We use 'which' to convert the former to the latter. +# * both "C:/path/to/ghc.exe" and "/c/path/to/ghc.exe" +# We use 'cygpath' to convert the former to the latter, because +# 'which' can't handle paths starting with a drive letter. +# * paths that contain spaces +# So we can't use the GNU make function 'realpath'. # Note also that we need to use 'override' in order to override a # value given on the commandline. -TEST_HC_REALPATH := $(realpath $(TEST_HC)) -ifeq "$(TEST_HC_REALPATH)" "" +$(eval $(call canonicaliseExecutable,TEST_HC)) override TEST_HC := $(shell which '$(TEST_HC)') -else -override TEST_HC := $(TEST_HC_REALPATH) -endif endif # "$(TEST_HC)" "" # We can't use $(dir ...) here as TEST_HC might be in a path From git at git.haskell.org Thu Dec 17 20:25:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 17 Dec 2015 20:25:38 +0000 (UTC) Subject: [commit: ghc] master: Build system: allow bindist without docs (116ba5e) Message-ID: <20151217202538.2577E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/116ba5e702916a938ab72970437efa5fd26287b7/ghc >--------------------------------------------------------------- commit 116ba5e702916a938ab72970437efa5fd26287b7 Author: Thomas Miedema Date: Tue Oct 27 23:43:58 2015 +0100 Build system: allow bindist without docs Useful for testing 'make binary-dist-prep' when HADDOCK_DOCS=NO. Reviewed by: bgamari Differential Revision: https://phabricator.haskell.org/D1648 >--------------------------------------------------------------- 116ba5e702916a938ab72970437efa5fd26287b7 ghc.mk | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.mk b/ghc.mk index 4455eb9..ba9aead 100644 --- a/ghc.mk +++ b/ghc.mk @@ -1039,7 +1039,7 @@ $(eval $(call bindist-list,.,\ $(INSTALL_LIBRARY_DOCS) \ $(addsuffix /*,$(INSTALL_HTML_DOC_DIRS)) \ docs/index.html \ - compiler/stage2/doc \ + $(wildcard compiler/stage2/doc) \ $(wildcard libraries/*/dist-install/doc/) \ $(wildcard libraries/*/*/dist-install/doc/) \ $(filter-out settings,$(INSTALL_LIBS)) \ From git at git.haskell.org Thu Dec 17 20:25:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 17 Dec 2015 20:25:40 +0000 (UTC) Subject: [commit: ghc] master: Suppress warnings when compiling primitive and random (f1fa383) Message-ID: <20151217202540.BC1883A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f1fa3839047925c75278f0a83835478e3aa437da/ghc >--------------------------------------------------------------- commit f1fa3839047925c75278f0a83835478e3aa437da Author: Thomas Miedema Date: Thu Oct 22 17:50:03 2015 +0200 Suppress warnings when compiling primitive and random And fix a redundant constraint warning in a test that requires primitive. >--------------------------------------------------------------- f1fa3839047925c75278f0a83835478e3aa437da mk/warnings.mk | 5 +++++ testsuite/tests/deriving/should_compile/T8138.hs | 2 +- 2 files changed, 6 insertions(+), 1 deletion(-) diff --git a/mk/warnings.mk b/mk/warnings.mk index 7efcf08..9107abc 100644 --- a/mk/warnings.mk +++ b/mk/warnings.mk @@ -79,6 +79,11 @@ libraries/pretty_dist-install_EXTRA_HC_OPTS += -Wno-unused-imports # primitive has a warning about deprecated use of GHC.IOBase libraries/primitive_dist-install_EXTRA_HC_OPTS += -Wno-unused-imports +# primitive uses deprecated Control.Monad.Trans.Error +libraries/primitive_dist-install_EXTRA_HC_OPTS += -Wno-deprecations + +# See https://github.com/haskell/random/pull/20 +libraries/random_dist-install_EXTRA_HC_OPTS += -Wno-redundant-constraints # temporarily turn off unused-imports warnings for terminfo libraries/terminfo_dist-boot_EXTRA_HC_OPTS += -fno-warn-unused-imports diff --git a/testsuite/tests/deriving/should_compile/T8138.hs b/testsuite/tests/deriving/should_compile/T8138.hs index 2e7e47b..e6d9781 100644 --- a/testsuite/tests/deriving/should_compile/T8138.hs +++ b/testsuite/tests/deriving/should_compile/T8138.hs @@ -22,7 +22,7 @@ mutableByteArrayFromList xs = do loop arr 0 xs return arr where - loop :: (Prim a) => MutableByteArray s -> Int -> [a] -> ST s () + loop :: MutableByteArray s -> Int -> [a] -> ST s () loop _ _ [] = return () loop arr i (x : xs) = do From git at git.haskell.org Thu Dec 17 20:42:06 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 17 Dec 2015 20:42:06 +0000 (UTC) Subject: [commit: ghc] master: Testsuite: mark frontend01 conditionally expect_broken on #10301 (bc436f9) Message-ID: <20151217204206.6ED2D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bc436f9ec51eb54aaebfbcd7de9c10543d629917/ghc >--------------------------------------------------------------- commit bc436f9ec51eb54aaebfbcd7de9c10543d629917 Author: Thomas Miedema Date: Thu Dec 17 21:42:04 2015 +0100 Testsuite: mark frontend01 conditionally expect_broken on #10301 This should fix validate on Travis. >--------------------------------------------------------------- bc436f9ec51eb54aaebfbcd7de9c10543d629917 testsuite/tests/plugins/all.T | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/plugins/all.T b/testsuite/tests/plugins/all.T index 2e4aacf..1f9ec3b 100644 --- a/testsuite/tests/plugins/all.T +++ b/testsuite/tests/plugins/all.T @@ -63,5 +63,8 @@ test('T10294a', run_command, ['$MAKE -s --no-print-directory T10294a']) -test('frontend01', [ extra_clean(['FrontendPlugin.hi', 'FrontendPlugin.o', 'frontend01', 'frontend01.o', 'frontend01.hi']) ], +test('frontend01', + [extra_clean(['FrontendPlugin.hi', 'FrontendPlugin.o', + 'frontend01', 'frontend01.o', 'frontend01.hi']), + unless(have_dynamic(), expect_broken(10301))], run_command, ['$MAKE -s --no-print-directory frontend01']) From git at git.haskell.org Thu Dec 17 21:03:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 17 Dec 2015 21:03:16 +0000 (UTC) Subject: [commit: ghc] master: Move Data.Functor.(Classes, Compose, Product, Sum) into base (e0e03d5) Message-ID: <20151217210316.98C373A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e0e03d5b9d5cd678f6402534451964d491f16540/ghc >--------------------------------------------------------------- commit e0e03d5b9d5cd678f6402534451964d491f16540 Author: RyanGlScott Date: Thu Dec 17 20:22:25 2015 +0100 Move Data.Functor.(Classes,Compose,Product,Sum) into base These modules were previously provided by the `transformers` package. Hence the submodule update. This patch was originally contributed by M Farkas-Dyck and subsequently taken over and completed by Ryan. The original proposal discussion can be found at https://mail.haskell.org/pipermail/libraries/2015-July/026014.html This addresses #11135 Differential Revision: https://phabricator.haskell.org/D1543 >--------------------------------------------------------------- e0e03d5b9d5cd678f6402534451964d491f16540 libraries/base/Data/Functor/Classes.hs | 470 +++++++++++++++++++++++++++++++++ libraries/base/Data/Functor/Compose.hs | 99 +++++++ libraries/base/Data/Functor/Product.hs | 97 +++++++ libraries/base/Data/Functor/Sum.hs | 77 ++++++ libraries/base/base.cabal | 4 + libraries/base/changelog.md | 4 + libraries/transformers | 2 +- testsuite/tests/perf/haddock/all.T | 3 +- 8 files changed, 754 insertions(+), 2 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc e0e03d5b9d5cd678f6402534451964d491f16540 From git at git.haskell.org Thu Dec 17 21:53:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 17 Dec 2015 21:53:33 +0000 (UTC) Subject: [commit: ghc] wip/aarch64-regd: rts/StgCRun.c: Add d15 to clobbered regs (c8e36e2) Message-ID: <20151217215333.61BB63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/aarch64-regd Link : http://ghc.haskell.org/trac/ghc/changeset/c8e36e230940f850915836fd69f7d4c045ac49a2/ghc >--------------------------------------------------------------- commit c8e36e230940f850915836fd69f7d4c045ac49a2 Author: Erik de Castro Lopo Date: Tue Oct 13 09:45:39 2015 +1100 rts/StgCRun.c: Add d15 to clobbered regs >--------------------------------------------------------------- c8e36e230940f850915836fd69f7d4c045ac49a2 rts/StgCRun.c | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) diff --git a/rts/StgCRun.c b/rts/StgCRun.c index c9bbef0..9e80d02 100644 --- a/rts/StgCRun.c +++ b/rts/StgCRun.c @@ -834,7 +834,12 @@ StgRun(StgFunPtr f, StgRegTable *basereg) { "%x19", "%x20", "%x21", "%x22", "%x23", "%x24", "%x25", "%x26", "%x27", "%x28", /* Exclude %x29 (frame pointer) */ "%x30", - "%d8", "%d9", "%d10", "%d11", "%d12", "%d13", "%d14" + "%d8", "%d9", "%d10", "%d11", "%d12", "%d13", "%d14", "%d15" + /* Since all these registers listed as clobbered are being explicitly + * saved and restored, they should probably not be listed as + * clobbered. Leaving them as is for now while I debug other + * issues. + */ ); return r; } From git at git.haskell.org Thu Dec 17 21:53:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 17 Dec 2015 21:53:36 +0000 (UTC) Subject: [commit: ghc] wip/aarch64-regd: rts: Fix clobbered regs list for aarch64 StgRun (f13bf92) Message-ID: <20151217215336.085743A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/aarch64-regd Link : http://ghc.haskell.org/trac/ghc/changeset/f13bf9287f8f04f69bcbda6df37eedea78fd4336/ghc >--------------------------------------------------------------- commit f13bf9287f8f04f69bcbda6df37eedea78fd4336 Author: Erik de Castro Lopo Date: Wed Jun 3 05:54:23 2015 +0000 rts: Fix clobbered regs list for aarch64 StgRun >--------------------------------------------------------------- f13bf9287f8f04f69bcbda6df37eedea78fd4336 rts/StgCRun.c | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/rts/StgCRun.c b/rts/StgCRun.c index 0a010d4..c9bbef0 100644 --- a/rts/StgCRun.c +++ b/rts/StgCRun.c @@ -829,8 +829,12 @@ StgRun(StgFunPtr f, StgRegTable *basereg) { : "=r" (r) : "r" (f), "r" (basereg), "i" (RESERVED_C_STACK_BYTES) - : "%x19", "%x20", "%x21", "%x22", "%x23", "%x24", "%x25", "%x26", "%x27", "%x28", - "%x16", "%x17", "%x30" + + : "%x16", "%x17", /* Exclude %r18 (platform/temporary register) */ + "%x19", "%x20", "%x21", "%x22", "%x23", "%x24", "%x25", + "%x26", "%x27", "%x28", /* Exclude %x29 (frame pointer) */ + "%x30", + "%d8", "%d9", "%d10", "%d11", "%d12", "%d13", "%d14" ); return r; } From git at git.haskell.org Thu Dec 17 21:53:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 17 Dec 2015 21:53:38 +0000 (UTC) Subject: [commit: ghc] wip/aarch64-regd: Linker: WIP on supporting Arm64/AArch64 (728d57b) Message-ID: <20151217215338.A02963A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/aarch64-regd Link : http://ghc.haskell.org/trac/ghc/changeset/728d57b51343854e29c92cc4ea09147c3afb3ae7/ghc >--------------------------------------------------------------- commit 728d57b51343854e29c92cc4ea09147c3afb3ae7 Author: Erik de Castro Lopo Date: Fri Oct 23 14:35:20 2015 +1100 Linker: WIP on supporting Arm64/AArch64 >--------------------------------------------------------------- 728d57b51343854e29c92cc4ea09147c3afb3ae7 rts/Linker.c | 69 ++++++++++++++++++++++++++++++++++++++++++++++++++++++------ 1 file changed, 62 insertions(+), 7 deletions(-) diff --git a/rts/Linker.c b/rts/Linker.c index 7ca7e94..5a1a991 100644 --- a/rts/Linker.c +++ b/rts/Linker.c @@ -4131,16 +4131,24 @@ ocRunInit_PEi386 ( ObjectCode *oc ) #define FALSE 0 #define TRUE 1 -#if defined(sparc_HOST_ARCH) +#if sparc_HOST_ARCH # define ELF_TARGET_SPARC /* Used inside */ -#elif defined(i386_HOST_ARCH) +#elif i386_HOST_ARCH # define ELF_TARGET_386 /* Used inside */ -#elif defined(x86_64_HOST_ARCH) +#elif x86_64_HOST_ARCH # define ELF_TARGET_X64_64 # define ELF_64BIT # define ELF_TARGET_AMD64 /* Used inside on Solaris 11 */ -#elif defined(powerpc64_HOST_ARCH) +#elif powerpc64_HOST_ARCH +# define ELF_64BIT +#elif aarch64_HOST_ARCH # define ELF_64BIT +#elif (arm_HOST_ARCH || arm_HOST_ARCH_PRE_ARMv7 || arm_HOST_ARCH_PRE_ARMv7 \ + || powerpc_HOST_ARCH) + /* Nothing here */ +#else + /* Need this so that new architectures get a compile error. */ +# error "Unknown HOST_ARCH" #endif #if !defined(openbsd_HOST_OS) @@ -4471,6 +4479,10 @@ ocVerifyImage_ELF ( ObjectCode* oc ) #elif defined(EM_AMD64) case EM_AMD64: IF_DEBUG(linker,debugBelch( "amd64" )); break; #endif +#ifdef EM_AARCH64 + case EM_AARCH64: IF_DEBUG(linker,debugBelch( "aarch64" )); break; +#endif + default: IF_DEBUG(linker,debugBelch( "unknown" )); errorBelch("%s: unknown architecture (e_machine == %d)" , oc->fileName, ehdr->e_machine); @@ -5272,7 +5284,7 @@ do_Elf_Rela_relocations ( ObjectCode* oc, char* ehdrC, #if defined(SHN_XINDEX) Elf_Word* shndx_table = get_shndx_table((Elf_Ehdr*)ehdrC); #endif -#if defined(DEBUG) || defined(sparc_HOST_ARCH) || defined(ia64_HOST_ARCH) || defined(powerpc_HOST_ARCH) || defined(x86_64_HOST_ARCH) +#if defined(DEBUG) || defined(sparc_HOST_ARCH) || defined(ia64_HOST_ARCH) || defined(powerpc_HOST_ARCH) || defined(x86_64_HOST_ARCH) || defined(aarch64_HOST_ARCH) /* This #ifdef only serves to avoid unused-var warnings. */ Elf_Addr targ = (Elf_Addr) oc->sections[target_shndx].start; #endif @@ -5290,7 +5302,7 @@ do_Elf_Rela_relocations ( ObjectCode* oc, char* ehdrC, } for (j = 0; j < nent; j++) { -#if defined(DEBUG) || defined(sparc_HOST_ARCH) || defined(ia64_HOST_ARCH) || defined(powerpc_HOST_ARCH) || defined(x86_64_HOST_ARCH) +#if defined(DEBUG) || defined(sparc_HOST_ARCH) || defined(ia64_HOST_ARCH) || defined(powerpc_HOST_ARCH) || defined(x86_64_HOST_ARCH) || defined(aarch64_HOST_ARCH) /* This #ifdef only serves to avoid unused-var warnings. */ Elf_Addr offset = rtab[j].r_offset; Elf_Addr P = targ + offset; @@ -5595,12 +5607,55 @@ do_Elf_Rela_relocations ( ObjectCode* oc, char* ehdrC, } #endif + case R_AARCH64_ABS64: + puts ("\n\nAArch64: ELF relocation(RelA) R_AARCH64_ABS64"); + *(Elf64_Xword *)P = S + A; + break; + + case R_AARCH64_ADR_PREL_PG_HI21: + puts ("\n\nAArch64: ELF relocation(RelA) R_AARCH64_ADR_PREL_PG_HI21"); + { + uint64_t final_address = (uint64_t) rtab + rtab[j].r_offset ; + // Operation: Page(S+A) - Page(P) + uint64_t result = ((S + A) & ~0xfffULL) - (final_address & ~0xfffULL); + +printf ("ehdrC: %p\nrtab : %p\n\n", ehdrC, rtab) ; + +printf ("rtab 0x%lx + 0x%lx -> 0x%lx\n", (uint64_t) rtab, (uint64_t) rtab[j].r_offset, final_address) ; +printf ("S 0x%lx + A 0x%lx : 0x%lx\n", S, A, S + A) ; +printf ("result 0x%lx\n", result) ; + + // Check that -2^32 <= X < 2^32 + if (result >> 32) + barf ("%s: overflow check failed for relocation", oc->fileName); + + *(Elf64_Xword *)P &= 0x9f00001fU; + // Immediate goes in bits 30:29 + 5:23 of ADRP instruction, taken + // from bits 32:12 of X. + *(Elf64_Xword *)P |= ((result & 0x3000U) << (29 - 12)); + *(Elf64_Xword *)P |= ((result & 0x1ffffc000ULL) >> (14 - 5)); + } + break; + + case R_AARCH64_CALL26: + case R_AARCH64_JUMP26: + puts ("\n\nAArch64: ELF relocation(RelA) R_AARCH64_CALL26/JUMP64"); + { + // These two are handled in the same way. + } + break; + + case R_AARCH64_ADD_ABS_LO12_NC: + puts ("\n\nAArch64: ELF relocation(RelA) R_AARCH64_ADD_ABS_LO12_NC"); + { + } + break; + default: errorBelch("%s: unhandled ELF relocation(RelA) type %" FMT_Word "\n", oc->fileName, (W_)ELF_R_TYPE(info)); return 0; } - } return 1; } From git at git.haskell.org Thu Dec 17 21:53:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 17 Dec 2015 21:53:41 +0000 (UTC) Subject: [commit: ghc] wip/aarch64-regd: Implement AArch64 codegen in `mkJumpToAddr` (for GHCi) (686720d) Message-ID: <20151217215341.4484D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/aarch64-regd Link : http://ghc.haskell.org/trac/ghc/changeset/686720d4f64e7c2244b446697a918c2832db6a65/ghc >--------------------------------------------------------------- commit 686720d4f64e7c2244b446697a918c2832db6a65 Author: Erik de Castro Lopo Date: Thu Dec 17 20:45:17 2015 +1100 Implement AArch64 codegen in `mkJumpToAddr` (for GHCi) >--------------------------------------------------------------- 686720d4f64e7c2244b446697a918c2832db6a65 libraries/ghci/GHCi/InfoTable.hsc | 19 +++++++++++++++++++ 1 file changed, 19 insertions(+) diff --git a/libraries/ghci/GHCi/InfoTable.hsc b/libraries/ghci/GHCi/InfoTable.hsc index d9d6314..cbd58a4 100644 --- a/libraries/ghci/GHCi/InfoTable.hsc +++ b/libraries/ghci/GHCi/InfoTable.hsc @@ -54,6 +54,7 @@ funPtrToInt :: FunPtr a -> Int funPtrToInt (FunPtr a) = I## (addr2Int## a) data Arch = ArchSPARC | ArchPPC | ArchX86 | ArchX86_64 | ArchAlpha | ArchARM + | ArchARM64 deriving Show platform :: Arch @@ -70,6 +71,8 @@ platform = ArchAlpha #elif defined(arm_HOST_ARCH) ArchARM +#elif defined(aarch64_HOST_ARCH) + ArchARM64 #endif mkJumpToAddr :: EntryFunPtr -> ItblCodes @@ -173,6 +176,22 @@ mkJumpToAddr a = case platform of , 0x11, 0xff, 0x2f, 0xe1 , byte0 w32, byte1 w32, byte2 w32, byte3 w32] + ArchARM64 { } -> + -- Generates: + -- + -- ldr x1, label + -- br x1 + -- label: + -- .quad + -- + -- which looks like: + -- 0: 58000041 ldr x1,