From git at git.haskell.org Mon Jun 1 07:07:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 07:07:30 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Don't assume tools are in same directory as ghc in some cases (1ae8363) Message-ID: <20150601070730.28D703A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/1ae8363c81db13f2f894de45cafe36551e7417c1/ghc >--------------------------------------------------------------- commit 1ae8363c81db13f2f894de45cafe36551e7417c1 Author: Phil Ruffwind Date: Sat Mar 7 11:04:00 2015 -0600 Don't assume tools are in same directory as ghc in some cases Summary: Tools such as `ghc-pkg` and `runghc` are no longer required to be in the same directory as `ghc` when running tests, provided that `TEST_HC` is not explicitly set and an in-tree compiler is not used. Fixes #10126. Reviewers: thomie, austin Reviewed By: thomie, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D705 GHC Trac Issues: #10126 (cherry picked from commit 504d8a4b183670830093a81d3c7a6d78416aed20) >--------------------------------------------------------------- 1ae8363c81db13f2f894de45cafe36551e7417c1 testsuite/mk/boilerplate.mk | 23 ++++++++++++++++++----- 1 file changed, 18 insertions(+), 5 deletions(-) diff --git a/testsuite/mk/boilerplate.mk b/testsuite/mk/boilerplate.mk index 98c9886..43bc4df 100644 --- a/testsuite/mk/boilerplate.mk +++ b/testsuite/mk/boilerplate.mk @@ -43,6 +43,7 @@ STAGE3_GHC := $(abspath $(TOP)/../inplace/bin/ghc-stage3) ifneq "$(wildcard $(STAGE1_GHC) $(STAGE1_GHC).exe)" "" +IMPLICIT_COMPILER = NO IN_TREE_COMPILER = YES ifeq "$(BINDIST)" "YES" TEST_HC := $(abspath $(TOP)/../)/bindisttest/install dir/bin/ghc @@ -56,11 +57,17 @@ TEST_HC := $(STAGE2_GHC) endif else +IMPLICIT_COMPILER = YES IN_TREE_COMPILER = NO TEST_HC := $(shell which ghc) endif else +ifeq "$(TEST_HC)" "ghc" +IMPLICIT_COMPILER = YES +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 @@ -87,12 +94,18 @@ endif # containing spaces BIN_ROOT = $(shell dirname '$(TEST_HC)') +ifeq "$(IMPLICIT_COMPILER)" "YES" +find_tool = $(shell which $(1)) +else +find_tool = $(BIN_ROOT)/$(1) +endif + ifeq "$(GHC_PKG)" "" -GHC_PKG := $(BIN_ROOT)/ghc-pkg +GHC_PKG := $(call find_tool,ghc-pkg) endif ifeq "$(RUNGHC)" "" -RUNGHC := $(BIN_ROOT)/runghc +RUNGHC := $(call find_tool,runghc) endif ifeq "$(HADDOCK)" "" @@ -100,15 +113,15 @@ HADDOCK := $(call find_tool,haddock) endif ifeq "$(HSC2HS)" "" -HSC2HS := $(BIN_ROOT)/hsc2hs +HSC2HS := $(call find_tool,hsc2hs) endif ifeq "$(HP2PS_ABS)" "" -HP2PS_ABS := $(BIN_ROOT)/hp2ps +HP2PS_ABS := $(call find_tool,hp2ps) endif ifeq "$(HPC)" "" -HPC := $(BIN_ROOT)/hpc +HPC := $(call find_tool,hpc) endif $(eval $(call canonicaliseExecutable,TEST_HC)) From git at git.haskell.org Mon Jun 1 07:15:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 07:15:41 +0000 (UTC) Subject: [commit: ghc] master: Catch canonicalizePath exceptions, fix #10101 (4756438) Message-ID: <20150601071541.075A53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4756438962a76d2dcedf63b90ec789cb054f9556/ghc >--------------------------------------------------------------- commit 4756438962a76d2dcedf63b90ec789cb054f9556 Author: Flaviu Andrei Csernik (archblob) Date: Mon Jun 1 02:13:36 2015 -0500 Catch canonicalizePath exceptions, fix #10101 Summary: Introduce by #95 'canonicalizePath' throws and exception when given an invalid file in a call to 'sameFile'. There are two cases when this can happen when using ghci: 1) If there is an error at the interactive prompt, "" file is searched for and not found. 2) If there is an error in any loaded file and editing an inexistent/new file with 'e: foo'. Both cases are now tested. Test Plan: validate Reviewers: austin, #ghc Reviewed By: austin, #ghc Subscribers: bgamari, thomie Differential Revision: https://phabricator.haskell.org/D930 GHC Trac Issues: #10101 >--------------------------------------------------------------- 4756438962a76d2dcedf63b90ec789cb054f9556 ghc/InteractiveUI.hs | 9 +++------ testsuite/tests/ghci/prog013/prog013.script | 4 ++++ testsuite/tests/ghci/prog013/prog013.stderr | 14 +++++++++++--- testsuite/tests/ghci/prog013/prog013.stdout | 2 ++ 4 files changed, 20 insertions(+), 9 deletions(-) diff --git a/ghc/InteractiveUI.hs b/ghc/InteractiveUI.hs index 0adc0cd..d3b4368 100644 --- a/ghc/InteractiveUI.hs +++ b/ghc/InteractiveUI.hs @@ -1245,6 +1245,9 @@ editFile str = when (null cmd) $ throwGhcException (CmdLineError "editor not set, use :set editor") lineOpt <- liftIO $ do + let sameFile p1 p2 = liftA2 (==) (canonicalizePath p1) (canonicalizePath p2) + `catchIO` (\_ -> return False) + curFileErrs <- filterM (\(f, _) -> unpackFS f `sameFile` file) errs return $ case curFileErrs of (_, line):_ -> " +" ++ show line @@ -3222,12 +3225,6 @@ expandPathIO p = other -> return other -sameFile :: FilePath -> FilePath -> IO Bool -sameFile path1 path2 = do - absPath1 <- canonicalizePath path1 - absPath2 <- canonicalizePath path2 - return $ absPath1 == absPath2 - wantInterpretedModule :: GHC.GhcMonad m => String -> m Module wantInterpretedModule str = wantInterpretedModuleName (GHC.mkModuleName str) diff --git a/testsuite/tests/ghci/prog013/prog013.script b/testsuite/tests/ghci/prog013/prog013.script index d4b91de..f2e2343 100644 --- a/testsuite/tests/ghci/prog013/prog013.script +++ b/testsuite/tests/ghci/prog013/prog013.script @@ -6,3 +6,7 @@ :e ./Bad.hs :l Good.hs :e ++ +:e foo +:l Bad.hs +:e bar diff --git a/testsuite/tests/ghci/prog013/prog013.stderr b/testsuite/tests/ghci/prog013/prog013.stderr index d8970d4..ce8827f 100644 --- a/testsuite/tests/ghci/prog013/prog013.stderr +++ b/testsuite/tests/ghci/prog013/prog013.stderr @@ -1,9 +1,17 @@ -Bad.hs:3:8: +Bad.hs:3:8: error: lexical error in string/character literal at character '\n' -Bad.hs:3:8: +Bad.hs:3:8: error: lexical error in string/character literal at character '\n' -Bad.hs:3:8: +Bad.hs:3:8: error: + lexical error in string/character literal at character '\n' + +:10:1: error: parse error on input ?+? + +Bad.hs:3:8: error: + lexical error in string/character literal at character '\n' + +Bad.hs:3:8: error: lexical error in string/character literal at character '\n' diff --git a/testsuite/tests/ghci/prog013/prog013.stdout b/testsuite/tests/ghci/prog013/prog013.stdout index 0d621da..024fd79 100644 --- a/testsuite/tests/ghci/prog013/prog013.stdout +++ b/testsuite/tests/ghci/prog013/prog013.stdout @@ -2,3 +2,5 @@ Good.hs Bad.hs +3 ./Bad.hs +3 Good.hs +foo +bar From git at git.haskell.org Mon Jun 1 08:42:42 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 08:42:42 +0000 (UTC) Subject: [commit: ghc] master: In ghci linker, link against all previous temp sos (#10322) (a52f144) Message-ID: <20150601084242.A93113A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a52f1444ea4045a2075dc88bb973a9289ee7e2cf/ghc >--------------------------------------------------------------- commit a52f1444ea4045a2075dc88bb973a9289ee7e2cf Author: Reid Barton Date: Tue May 19 01:23:59 2015 -0500 In ghci linker, link against all previous temp sos (#10322) The OS X dlopen() appears to only resolve undefined symbols in the direct dependencies of the shared library it is loading. Reviewed By: trommler, austin Differential Revision: https://phabricator.haskell.org/D852 GHC Trac Issues: #10322 >--------------------------------------------------------------- a52f1444ea4045a2075dc88bb973a9289ee7e2cf compiler/ghci/Linker.hs | 22 +++++++++++----------- testsuite/tests/ghci/scripts/all.T | 3 +-- 2 files changed, 12 insertions(+), 13 deletions(-) diff --git a/compiler/ghci/Linker.hs b/compiler/ghci/Linker.hs index cec0904..3e8423c 100644 --- a/compiler/ghci/Linker.hs +++ b/compiler/ghci/Linker.hs @@ -119,9 +119,9 @@ data PersistentLinkerState -- that is really important pkgs_loaded :: ![PackageKey], - -- we need to remember the name of the last temporary DLL/.so - -- so we can link it - last_temp_so :: !(Maybe (FilePath, String)) } + -- we need to remember the name of previous temporary DLL/.so + -- libraries so we can link them (see #10322) + temp_sos :: ![(FilePath, String)] } emptyPLS :: DynFlags -> PersistentLinkerState @@ -131,7 +131,7 @@ emptyPLS _ = PersistentLinkerState { pkgs_loaded = init_pkgs, bcos_loaded = [], objs_loaded = [], - last_temp_so = Nothing } + temp_sos = [] } -- Packages that don't need loading, because the compiler -- shares them with the interpreted program. @@ -841,19 +841,19 @@ dynLoadObjs dflags pls objs = do dflags2 = dflags1 { -- We don't want the original ldInputs in -- (they're already linked in), but we do want - -- to link against the previous dynLoadObjs - -- library if there was one, so that the linker + -- to link against previous dynLoadObjs + -- libraries if there were any, so that the linker -- can resolve dependencies when it loads this -- library. ldInputs = - case last_temp_so pls of - Nothing -> [] - Just (lp, l) -> + concatMap + (\(lp, l) -> [ Option ("-L" ++ lp) , Option ("-Wl,-rpath") , Option ("-Wl," ++ lp) , Option ("-l" ++ l) - ], + ]) + (temp_sos pls), -- Even if we're e.g. profiling, we still want -- the vanilla dynamic libraries, so we set the -- ways / build tag to be just WayDyn. @@ -868,7 +868,7 @@ dynLoadObjs dflags pls objs = do consIORef (filesToNotIntermediateClean dflags) soFile m <- loadDLL soFile case m of - Nothing -> return pls { last_temp_so = Just (libPath, libName) } + Nothing -> return pls { temp_sos = (libPath, libName) : temp_sos pls } Just err -> panic ("Loading temp shared object failed: " ++ err) rmDupLinkables :: [Linkable] -- Already loaded diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T index e0f2301..2c48358 100755 --- a/testsuite/tests/ghci/scripts/all.T +++ b/testsuite/tests/ghci/scripts/all.T @@ -207,8 +207,6 @@ test('T9878b', extra_clean(['T9878b.hi','T9878b.o'])], ghci_script, ['T9878b.script']) test('T10122', normal, ghci_script, ['T10122.script']) -test('T10322', when(opsys('darwin'), expect_broken(10322)), - ghci_script, ['T10322.script']) test('T10321', normal, ghci_script, ['T10321.script']) @@ -218,3 +216,4 @@ test('T10408B', normal, run_command, ['$MAKE -s --no-print-directory T10408B']) test('T10248', normal, ghci_script, ['T10248.script']) test('T10110', normal, ghci_script, ['T10110.script']) +test('T10322', normal, ghci_script, ['T10322.script']) From git at git.haskell.org Mon Jun 1 08:45:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 08:45:23 +0000 (UTC) Subject: [commit: ghc] master: compiler/specialise: shut match_co up a bit (f5b43ce) Message-ID: <20150601084523.0AE3C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f5b43ce177e40a34afb1913bc0ec866185ed95d7/ghc >--------------------------------------------------------------- commit f5b43ce177e40a34afb1913bc0ec866185ed95d7 Author: Austin Seipp Date: Mon Jun 1 03:45:11 2015 -0500 compiler/specialise: shut match_co up a bit This stray pprTrace is quite annoying and makes our build logs a bit bigger (hundreds of lines of occurrences), so we should probably just get rid of it. Kept under DEBUG for future brave hackers. Signed-off-by: Austin Seipp Reviewed By: thomie, nomeata Differential Revision: https://phabricator.haskell.org/D934 >--------------------------------------------------------------- f5b43ce177e40a34afb1913bc0ec866185ed95d7 compiler/specialise/Rules.hs | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/compiler/specialise/Rules.hs b/compiler/specialise/Rules.hs index e6e5359..3601253 100644 --- a/compiler/specialise/Rules.hs +++ b/compiler/specialise/Rules.hs @@ -733,9 +733,13 @@ match_co renv subst (TyConAppCo r1 tc1 cos1) co2 | r1 == r2 && tc1 == tc2 -> match_cos renv subst cos1 cos2 _ -> Nothing -match_co _ _ co1 co2 - = pprTrace "match_co: needs more cases" (ppr co1 $$ ppr co2) Nothing +match_co _ _ _co1 _co2 -- Currently just deals with CoVarCo, TyConAppCo and Refl +#ifdef DEBUG + = pprTrace "match_co: needs more cases" (ppr _co1 $$ ppr _co2) Nothing +#else + = Nothing +#endif match_cos :: RuleMatchEnv -> RuleSubst From git at git.haskell.org Mon Jun 1 08:47:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 08:47:29 +0000 (UTC) Subject: [commit: packages/binary] master: Make get :: Get Char total (62c41d7) Message-ID: <20150601084729.164383A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/62c41d79c4df5e26c6d4b39a56b7f54896eaa3ff >--------------------------------------------------------------- commit 62c41d79c4df5e26c6d4b39a56b7f54896eaa3ff Author: Thomas Tuegel Date: Fri Feb 20 12:43:59 2015 -0600 Make get :: Get Char total The old Binary instance for Char used Data.Char.chr, which calls error if given an invalid code point. The instance is modified to call fail instead of error on invalid code points, which is total (within the Get Monad). Calls to error inside Get will escape decodeOrFail. >--------------------------------------------------------------- 62c41d79c4df5e26c6d4b39a56b7f54896eaa3ff src/Data/Binary/Class.hs | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/src/Data/Binary/Class.hs b/src/Data/Binary/Class.hs index 8b7bc13..2477056 100644 --- a/src/Data/Binary/Class.hs +++ b/src/Data/Binary/Class.hs @@ -47,7 +47,7 @@ import Foreign import Data.ByteString.Lazy (ByteString) import qualified Data.ByteString.Lazy as L -import Data.Char (chr,ord) +import Data.Char (ord) import Data.List (unfoldr) -- And needed for the instances: @@ -382,7 +382,11 @@ instance Binary Char where z <- liftM (xor 0x80) getByte return (z .|. shiftL6 (y .|. shiftL6 (x .|. shiftL6 (xor 0xf0 w)))) - return $! chr r + getChr r + where + getChr w + | w <= 0x10ffff = return $! toEnum $ fromEnum w + | otherwise = fail "Not a valid Unicode code point!" ------------------------------------------------------------------------ -- Instances for the first few tuples From git at git.haskell.org Mon Jun 1 08:47:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 08:47:31 +0000 (UTC) Subject: [commit: packages/binary] master: Merge pull request #70 from ttuegel/total-char (ba3eb9d) Message-ID: <20150601084731.1EEDF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/ba3eb9d97b07955ef7c3be857f0800c9b5db4622 >--------------------------------------------------------------- commit ba3eb9d97b07955ef7c3be857f0800c9b5db4622 Merge: ff9a48f 62c41d7 Author: Lennart Kolmodin Date: Mon Feb 23 12:31:39 2015 +0100 Merge pull request #70 from ttuegel/total-char Make get :: Get Char total Fail within the Get monad for some UTF-8 errors >--------------------------------------------------------------- ba3eb9d97b07955ef7c3be857f0800c9b5db4622 src/Data/Binary/Class.hs | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) From git at git.haskell.org Mon Jun 1 08:47:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 08:47:33 +0000 (UTC) Subject: [commit: packages/binary] master: Bump version to 0.7.4.0 (607fced) Message-ID: <20150601084733.27A963A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/607fcedaf1ccd042b38a9280ac1c597243902156 >--------------------------------------------------------------- commit 607fcedaf1ccd042b38a9280ac1c597243902156 Author: Lennart Kolmodin Date: Mon Feb 23 18:28:42 2015 +0100 Bump version to 0.7.4.0 and update the changelog. >--------------------------------------------------------------- 607fcedaf1ccd042b38a9280ac1c597243902156 binary.cabal | 2 +- changelog.md | 7 +++++++ 2 files changed, 8 insertions(+), 1 deletion(-) diff --git a/binary.cabal b/binary.cabal index 3303025..b46ed48 100644 --- a/binary.cabal +++ b/binary.cabal @@ -1,5 +1,5 @@ name: binary -version: 0.7.3.0 +version: 0.7.4.0 license: BSD3 license-file: LICENSE author: Lennart Kolmodin diff --git a/changelog.md b/changelog.md index 3d0f2f7..4f4a1bf 100644 --- a/changelog.md +++ b/changelog.md @@ -2,6 +2,13 @@ binary ====== +binary-0.7.4.0 +-------------- + +- Some invalid UTF-8 strings caused an exception when decoded. Those errors will + now now fail in the Get monad instead. See #70. + Patch contributed by @ttuegel. + binary-0.7.3.0 -------------- From git at git.haskell.org Mon Jun 1 08:47:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 08:47:35 +0000 (UTC) Subject: [commit: packages/binary] master: Switch to arbitrarySizedNatural from QuickCheck >= 2.8 (3c78d66) Message-ID: <20150601084735.319CC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/3c78d66f905c3fd45d0f2766672ab89e2dd3c9f0 >--------------------------------------------------------------- commit 3c78d66f905c3fd45d0f2766672ab89e2dd3c9f0 Author: Lennart Kolmodin Date: Sat May 23 16:48:26 2015 +0200 Switch to arbitrarySizedNatural from QuickCheck >= 2.8 arbitrarySizedNatural got implemented in QuickCheck 2.8, so we no longer need to keep our own implementation. Bump the dependency on QuickCheck to >= 2.8. >--------------------------------------------------------------- 3c78d66f905c3fd45d0f2766672ab89e2dd3c9f0 binary.cabal | 2 +- tests/Arbitrary.hs | 22 ---------------------- tests/QC.hs | 12 ++++++------ 3 files changed, 7 insertions(+), 29 deletions(-) diff --git a/binary.cabal b/binary.cabal index b46ed48..322ff9b 100644 --- a/binary.cabal +++ b/binary.cabal @@ -71,7 +71,7 @@ test-suite qc random>=1.0.1.0, test-framework, test-framework-quickcheck2 >= 0.3, - QuickCheck>=2.7 + QuickCheck>=2.8 -- build dependencies from using binary source rather than depending on the library build-depends: array, containers diff --git a/tests/Arbitrary.hs b/tests/Arbitrary.hs index c19a192..dcb9d44 100644 --- a/tests/Arbitrary.hs +++ b/tests/Arbitrary.hs @@ -1,10 +1,6 @@ {-# LANGUAGE CPP #-} {-# OPTIONS_GHC -fno-warn-orphans #-} -#if MIN_VERSION_base(4,8,0) -#define HAS_NATURAL -#endif - module Arbitrary where import Test.QuickCheck @@ -12,10 +8,6 @@ import Test.QuickCheck import qualified Data.ByteString as B import qualified Data.ByteString.Lazy as L -#ifdef HAS_NATURAL -import Numeric.Natural -#endif - instance Arbitrary L.ByteString where arbitrary = fmap L.fromChunks arbitrary @@ -61,17 +53,3 @@ instance (Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e, (a,b,c,d,e) <- arbitrary (f,g,h,i,j) <- arbitrary return (a,b,c,d,e,f,g,h,i,j) - - -#ifdef HAS_NATURAL --- | Generates a natural number. The number must be positive --- and its maximum value depends on the size parameter. -arbitrarySizedNatural :: Gen Natural -arbitrarySizedNatural = - sized $ \n0 -> - let n = toInteger n0 in - inBounds fromInteger (choose (0, n*n)) - -inBounds :: Integral a => (Integer -> a) -> Gen Integer -> Gen a -inBounds fi g = fmap fi (g `suchThat` (\x -> toInteger (fi x) == x)) -#endif \ No newline at end of file diff --git a/tests/QC.hs b/tests/QC.hs index 9e00616..b0b4c8f 100644 --- a/tests/QC.hs +++ b/tests/QC.hs @@ -16,16 +16,16 @@ import Data.Int import Data.Ratio import System.IO.Unsafe +#ifdef HAS_NATURAL +import Numeric.Natural +#endif + import Test.Framework import Test.Framework.Providers.QuickCheck2 import Test.QuickCheck import qualified Action (tests) -import Arbitrary ( -#ifdef HAS_NATURAL - arbitrarySizedNatural -#endif - ) +import Arbitrary () import Data.Binary import Data.Binary.Get import Data.Binary.Put @@ -361,7 +361,7 @@ main = defaultMain tests -- | Until the QuickCheck library implements instance Arbitrary Natural, -- we need this test. prop_test_Natural :: Property -prop_test_Natural = forAll arbitrarySizedNatural test +prop_test_Natural = forAll (arbitrarySizedNatural :: Gen Natural) test #endif ------------------------------------------------------------------------ From git at git.haskell.org Mon Jun 1 08:47:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 08:47:37 +0000 (UTC) Subject: [commit: packages/binary] master: Remove quadratic behaviour in `ensureN`. (e46b7b6) Message-ID: <20150601084737.39F753A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/e46b7b61111579befcc99954be8a0f48738f8ef7 >--------------------------------------------------------------- commit e46b7b61111579befcc99954be8a0f48738f8ef7 Author: Francesco Mazzoli Date: Thu May 28 00:16:53 2015 +0200 Remove quadratic behaviour in `ensureN`. Chains of `B.append`s were being created by repeated calls to `demandInput`. Try the following program, which writes and read 100MB, to appreciate the difference: ``` import qualified Data.ByteString as BS import qualified Data.ByteString.Lazy as BSL import Data.Binary (encode, decode) import Data.Char (ord) main :: IO () main = do let inBs = BS.replicate 100000000 (fromIntegral $ ord 'a') BSL.writeFile "bs.bin" (encode inBs) putStrLn "writing done" bin <- BSL.readFile "bs.bin" -- This takes around 30 seconds and causes more than 10GB to be -- allocated. let outBs = decode bin print $ inBs == outBs ``` >--------------------------------------------------------------- e46b7b61111579befcc99954be8a0f48738f8ef7 src/Data/Binary/Get/Internal.hs | 24 ++++++++++++++---------- 1 file changed, 14 insertions(+), 10 deletions(-) diff --git a/src/Data/Binary/Get/Internal.hs b/src/Data/Binary/Get/Internal.hs index 9b53831..4cb7f15 100644 --- a/src/Data/Binary/Get/Internal.hs +++ b/src/Data/Binary/Get/Internal.hs @@ -381,16 +381,20 @@ readN !n f = ensureN n >> unsafeReadN n f -- | Ensure that there are at least @n@ bytes available. If not, the -- computation will escape with 'Partial'. ensureN :: Int -> Get () -ensureN !n0 = C $ \inp ks -> do - if B.length inp >= n0 - then ks inp () - else runCont (go n0) inp ks - where -- might look a bit funny, but plays very well with GHC's inliner. - -- GHC won't inline recursive functions, so we make ensureN non-recursive - go n = C $ \inp ks -> do - if B.length inp >= n - then ks inp () - else runCont (demandInput >> go n) inp ks +ensureN !n0 = go n0 [] + where + go !remaining0 bss0 = C $ \inp ks -> + let remaining = remaining0 - B.length inp + bss = inp : bss0 + in if remaining <= 0 + then ks (B.concat $ reverse bss) () + else + Partial $ \mbBs -> case mbBs of + Just bs -> runCont (go remaining bss) bs ks + -- We keep the error message referencing @demandInput@, + -- for legacy reasons -- people have been seeing this for + -- years. + Nothing -> Fail (B.concat $ reverse bss) "demandInput: not enough bytes" {-# INLINE ensureN #-} unsafeReadN :: Int -> (B.ByteString -> a) -> Get a From git at git.haskell.org Mon Jun 1 08:47:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 08:47:39 +0000 (UTC) Subject: [commit: packages/binary] master: Make `ensureN` more inliner-friendly... (f947333) Message-ID: <20150601084739.40E9D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/f947333e0b4e66f412d44db3be5f6f42a1d958d5 >--------------------------------------------------------------- commit f947333e0b4e66f412d44db3be5f6f42a1d958d5 Author: Francesco Mazzoli Date: Thu May 28 14:38:17 2015 +0200 Make `ensureN` more inliner-friendly... ...by making the common case (when the input is big enough) non-recursive. >--------------------------------------------------------------- f947333e0b4e66f412d44db3be5f6f42a1d958d5 src/Data/Binary/Get/Internal.hs | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/src/Data/Binary/Get/Internal.hs b/src/Data/Binary/Get/Internal.hs index 4cb7f15..7989cbf 100644 --- a/src/Data/Binary/Get/Internal.hs +++ b/src/Data/Binary/Get/Internal.hs @@ -381,7 +381,11 @@ readN !n f = ensureN n >> unsafeReadN n f -- | Ensure that there are at least @n@ bytes available. If not, the -- computation will escape with 'Partial'. ensureN :: Int -> Get () -ensureN !n0 = go n0 [] +ensureN !n0 = C $ \inp ks -> do + let inpLen = B.length inp + if inpLen >= n0 + then ks inp () + else runCont (go n0 []) inp ks where go !remaining0 bss0 = C $ \inp ks -> let remaining = remaining0 - B.length inp From git at git.haskell.org Mon Jun 1 08:47:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 08:47:41 +0000 (UTC) Subject: [commit: packages/binary] master: Refactor and remove compiler warnings from ensureN. (d8c1ee8) Message-ID: <20150601084741.486D73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/d8c1ee8df945899fa413e155672ec214e1d91e55 >--------------------------------------------------------------- commit d8c1ee8df945899fa413e155672ec214e1d91e55 Author: Lennart Kolmodin Date: Thu May 28 21:40:00 2015 +0200 Refactor and remove compiler warnings from ensureN. >--------------------------------------------------------------- d8c1ee8df945899fa413e155672ec214e1d91e55 src/Data/Binary/Get/Internal.hs | 37 ++++++++++++++++++++----------------- 1 file changed, 20 insertions(+), 17 deletions(-) diff --git a/src/Data/Binary/Get/Internal.hs b/src/Data/Binary/Get/Internal.hs index 7989cbf..957b969 100644 --- a/src/Data/Binary/Get/Internal.hs +++ b/src/Data/Binary/Get/Internal.hs @@ -168,14 +168,17 @@ noMeansNo r0 = go r0 Done _ _ -> r prompt :: B.ByteString -> Decoder a -> (B.ByteString -> Decoder a) -> Decoder a -prompt inp kf ks = - let loop = - Partial $ \sm -> - case sm of - Just s | B.null s -> loop - | otherwise -> ks (inp `B.append` s) - Nothing -> kf - in loop +prompt inp kf ks = prompt' kf (\inp' -> ks (inp `B.append` inp')) + +prompt' :: Decoder a -> (B.ByteString -> Decoder a) -> Decoder a +prompt' kf ks = + let loop = + Partial $ \sm -> + case sm of + Just s | B.null s -> loop + | otherwise -> ks s + Nothing -> kf + in loop -- | Get the total number of bytes read to this point. bytesRead :: Get Int64 @@ -382,23 +385,23 @@ readN !n f = ensureN n >> unsafeReadN n f -- computation will escape with 'Partial'. ensureN :: Int -> Get () ensureN !n0 = C $ \inp ks -> do - let inpLen = B.length inp - if inpLen >= n0 + if B.length inp >= n0 then ks inp () else runCont (go n0 []) inp ks - where - go !remaining0 bss0 = C $ \inp ks -> - let remaining = remaining0 - B.length inp + where -- might look a bit funny, but plays very well with GHC's inliner. + -- GHC won't inline recursive functions, so we make ensureN non-recursive + go !n bss0 = C $ \inp ks -> + let n' = n - B.length inp bss = inp : bss0 - in if remaining <= 0 + in if n' <= 0 then ks (B.concat $ reverse bss) () else - Partial $ \mbBs -> case mbBs of - Just bs -> runCont (go remaining bss) bs ks + prompt' -- We keep the error message referencing @demandInput@, -- for legacy reasons -- people have been seeing this for -- years. - Nothing -> Fail (B.concat $ reverse bss) "demandInput: not enough bytes" + (Fail (B.concat $ reverse bss) "demandInput: not enough bytes") + (\inp' -> runCont (go n' bss) inp' ks) {-# INLINE ensureN #-} unsafeReadN :: Int -> (B.ByteString -> a) -> Get a From git at git.haskell.org Mon Jun 1 08:47:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 08:47:43 +0000 (UTC) Subject: [commit: packages/binary] master: Simplify the skip, get*LazyByteString* functions. (6c9c47f) Message-ID: <20150601084743.520233A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/6c9c47f8db5d23360d1147288086e33f9d93350e >--------------------------------------------------------------- commit 6c9c47f8db5d23360d1147288086e33f9d93350e Author: Lennart Kolmodin Date: Sat May 30 11:14:27 2015 +0200 Simplify the skip, get*LazyByteString* functions. Affects; - skip - getLazyByteString - getLazyByteStringNul - getRemainingLazyByteString These functions all read input chunks until some condition, reading enough bytes, reaching a NUL character, or it has consumed all bytes. They're now implemented by withInputChunks. This fixes a bug where the position in the input previously wasn't correctly reported if you ran out of input bytes. Tests have been added for getLazyByteString and skip to Action.hs. Tests for getLazyByteStringNul and getRemainingLazyByteString already exist in QC.hs. >--------------------------------------------------------------- 6c9c47f8db5d23360d1147288086e33f9d93350e src/Data/Binary/Get.hs | 64 ++++++++++++++++------------------------- src/Data/Binary/Get/Internal.hs | 36 ++++++++++++++--------- tests/Action.hs | 26 ++++++++++++++++- 3 files changed, 71 insertions(+), 55 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 6c9c47f8db5d23360d1147288086e33f9d93350e From git at git.haskell.org Mon Jun 1 08:47:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 08:47:45 +0000 (UTC) Subject: [commit: packages/binary] master: Fix compilation error on GHC < 7.10. (c2d8fe2) Message-ID: <20150601084745.5900A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/c2d8fe2f71a93bf8f5822b6b148c7cb1eb477590 >--------------------------------------------------------------- commit c2d8fe2f71a93bf8f5822b6b148c7cb1eb477590 Author: Lennart Kolmodin Date: Sat May 30 11:58:48 2015 +0200 Fix compilation error on GHC < 7.10. >--------------------------------------------------------------- c2d8fe2f71a93bf8f5822b6b148c7cb1eb477590 src/Data/Binary/Get/Internal.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Data/Binary/Get/Internal.hs b/src/Data/Binary/Get/Internal.hs index 5549655..6659727 100644 --- a/src/Data/Binary/Get/Internal.hs +++ b/src/Data/Binary/Get/Internal.hs @@ -232,7 +232,7 @@ withInputChunks initS consume onSucc onFail = go initS [] Left state' -> do let acc' = inp : acc prompt' - (runCont (onFail (reverse acc')) mempty ks) + (runCont (onFail (reverse acc')) B.empty ks) (\str' -> runCont (go state' acc') str' ks) Right (want,rest) -> do ks rest (onSucc (reverse (want:acc))) From git at git.haskell.org Mon Jun 1 08:47:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 08:47:47 +0000 (UTC) Subject: [commit: packages/binary] master: Remove obsolete index.html, Makefiles. (f05a797) Message-ID: <20150601084747.619AC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/f05a797f6c5f3cbf2967b44b2618a6c02a9b8414 >--------------------------------------------------------------- commit f05a797f6c5f3cbf2967b44b2618a6c02a9b8414 Author: Lennart Kolmodin Date: Sat May 30 13:45:45 2015 +0200 Remove obsolete index.html, Makefiles. >--------------------------------------------------------------- f05a797f6c5f3cbf2967b44b2618a6c02a9b8414 benchmarks/Makefile | 34 ----------- binary.cabal | 5 +- index.html | 161 ---------------------------------------------------- tests/Makefile | 20 ------- 4 files changed, 2 insertions(+), 218 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc f05a797f6c5f3cbf2967b44b2618a6c02a9b8414 From git at git.haskell.org Mon Jun 1 08:47:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 08:47:49 +0000 (UTC) Subject: [commit: packages/binary] master: Port ensureN to use withInputChunks. (384dd59) Message-ID: <20150601084749.6A81C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/384dd591258b287547023dc38c99345cdd2797a5 >--------------------------------------------------------------- commit 384dd591258b287547023dc38c99345cdd2797a5 Author: Lennart Kolmodin Date: Sat May 30 14:28:10 2015 +0200 Port ensureN to use withInputChunks. >--------------------------------------------------------------- 384dd591258b287547023dc38c99345cdd2797a5 src/Data/Binary/Get/Internal.hs | 16 ++++++---------- 1 file changed, 6 insertions(+), 10 deletions(-) diff --git a/src/Data/Binary/Get/Internal.hs b/src/Data/Binary/Get/Internal.hs index 6659727..804fde1 100644 --- a/src/Data/Binary/Get/Internal.hs +++ b/src/Data/Binary/Get/Internal.hs @@ -398,18 +398,14 @@ ensureN :: Int -> Get () ensureN !n0 = C $ \inp ks -> do if B.length inp >= n0 then ks inp () - else runCont (go n0 []) inp ks + else runCont (withInputChunks n0 enoughChunks onSucc onFail >>= put) inp ks where -- might look a bit funny, but plays very well with GHC's inliner. -- GHC won't inline recursive functions, so we make ensureN non-recursive - go !n bss0 = C $ \inp ks -> - let n' = n - B.length inp - bss = inp : bss0 - in if n' <= 0 - then ks (B.concat $ reverse bss) () - else - prompt' - (Fail (B.concat $ reverse bss) "not enough bytes") - (\inp' -> runCont (go n' bss) inp' ks) + enoughChunks n str + | B.length str >= n = Right (str,B.empty) + | otherwise = Left (n - B.length str) + onSucc = B.concat + onFail bss = C $ \_ _ -> Fail (B.concat bss) "not enough bytes" {-# INLINE ensureN #-} unsafeReadN :: Int -> (B.ByteString -> a) -> Get a From git at git.haskell.org Mon Jun 1 08:47:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 08:47:51 +0000 (UTC) Subject: [commit: packages/binary] master: Fix memory leak when decoding Float and Double. (497a181) Message-ID: <20150601084751.720DA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/497a181c083fa9faf7fa3aa64d1d8deb9ac76ecb >--------------------------------------------------------------- commit 497a181c083fa9faf7fa3aa64d1d8deb9ac76ecb Author: Lennart Kolmodin Date: Sat May 30 16:14:03 2015 +0200 Fix memory leak when decoding Float and Double. >--------------------------------------------------------------- 497a181c083fa9faf7fa3aa64d1d8deb9ac76ecb src/Data/Binary/Class.hs | 10 ++++++++-- 1 file changed, 8 insertions(+), 2 deletions(-) diff --git a/src/Data/Binary/Class.hs b/src/Data/Binary/Class.hs index 2477056..5aa6c05 100644 --- a/src/Data/Binary/Class.hs +++ b/src/Data/Binary/Class.hs @@ -537,11 +537,17 @@ instance (Binary e) => Binary (Seq.Seq e) where instance Binary Double where put d = put (decodeFloat d) - get = liftM2 encodeFloat get get + get = do + x <- get + y <- get + return $! encodeFloat x y instance Binary Float where put f = put (decodeFloat f) - get = liftM2 encodeFloat get get + get = do + x <- get + y <- get + return $! encodeFloat x y ------------------------------------------------------------------------ -- Trees From git at git.haskell.org Mon Jun 1 08:47:53 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 08:47:53 +0000 (UTC) Subject: [commit: packages/binary] master: Increase test coverage for Binary Natural instance. (916372c) Message-ID: <20150601084753.791FF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/916372c846e50e84da0ce262f57c685be22f46ba >--------------------------------------------------------------- commit 916372c846e50e84da0ce262f57c685be22f46ba Author: Lennart Kolmodin Date: Sun May 31 16:41:04 2015 +0200 Increase test coverage for Binary Natural instance. The arbitrarySizedNatural creates too small Naturals so we didn't test all code paths. Use a custom generator to get bigger numbers. >--------------------------------------------------------------- 916372c846e50e84da0ce262f57c685be22f46ba tests/QC.hs | 16 +++++++++++++--- 1 file changed, 13 insertions(+), 3 deletions(-) diff --git a/tests/QC.hs b/tests/QC.hs index b0b4c8f..addf185 100644 --- a/tests/QC.hs +++ b/tests/QC.hs @@ -358,10 +358,20 @@ main = defaultMain tests ------------------------------------------------------------------------ #ifdef HAS_NATURAL --- | Until the QuickCheck library implements instance Arbitrary Natural, --- we need this test. prop_test_Natural :: Property -prop_test_Natural = forAll (arbitrarySizedNatural :: Gen Natural) test +prop_test_Natural = forAll (gen :: Gen Natural) test + where + gen :: Gen Natural + gen = do + b <- arbitrary + if b + then do + x <- arbitrarySizedNatural :: Gen Natural + -- arbitrarySizedNatural generates numbers smaller than + -- (maxBound :: Word64), so let's make them bigger to better test + -- the Binary instance. + return (x + fromIntegral (maxBound :: Word64)) + else arbitrarySizedNatural #endif ------------------------------------------------------------------------ From git at git.haskell.org Mon Jun 1 08:47:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 08:47:55 +0000 (UTC) Subject: [commit: packages/binary] master: Sync dependencies in .travis.yml to binary.cabal (5faca82) Message-ID: <20150601084755.802753A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/5faca823298c26b9fe32bd50dbe61f2ffa73a037 >--------------------------------------------------------------- commit 5faca823298c26b9fe32bd50dbe61f2ffa73a037 Author: Lennart Kolmodin Date: Sun May 31 16:47:01 2015 +0200 Sync dependencies in .travis.yml to binary.cabal >--------------------------------------------------------------- 5faca823298c26b9fe32bd50dbe61f2ffa73a037 .travis.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.travis.yml b/.travis.yml index 832819a..eb66f2c 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.7.3" 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 -j script: - cabal configure --enable-tests --enable-benchmarks -v2 --ghc-options=-fno-spec-constr From git at git.haskell.org Mon Jun 1 08:47:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 08:47:57 +0000 (UTC) Subject: [commit: packages/binary] master: Bump version to 0.7.5.0 (86e4c9a) Message-ID: <20150601084757.875143A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/86e4c9a6125cdddb0592a653f48c699a574ccf7b >--------------------------------------------------------------- commit 86e4c9a6125cdddb0592a653f48c699a574ccf7b Author: Lennart Kolmodin Date: Sun May 31 17:03:00 2015 +0200 Bump version to 0.7.5.0 and update the changelog. >--------------------------------------------------------------- 86e4c9a6125cdddb0592a653f48c699a574ccf7b binary.cabal | 2 +- changelog.md | 10 ++++++++++ 2 files changed, 11 insertions(+), 1 deletion(-) diff --git a/binary.cabal b/binary.cabal index e271f06..f8ccb69 100644 --- a/binary.cabal +++ b/binary.cabal @@ -1,5 +1,5 @@ name: binary -version: 0.7.4.0 +version: 0.7.5.0 license: BSD3 license-file: LICENSE author: Lennart Kolmodin diff --git a/changelog.md b/changelog.md index 4f4a1bf..6763f96 100644 --- a/changelog.md +++ b/changelog.md @@ -1,6 +1,16 @@ binary ====== +binary-0.7.5.0 +-------------- + +- Fix performance bug that was noticable when you get a big strict ByteString + and the input to the decoder consists of many small chunks. + - https://github.com/kolmodin/binary/issues/73 + - https://github.com/kolmodin/binary/pull/76 +- Fix memory leak when decoding Double and Float. + - Commit 497a181c083fa9faf7fa3aa64d1d8deb9ac76ecb +- We now require QuickCheck >= 2.8. Remove our version of arbitrarySizedNatural. binary-0.7.4.0 -------------- From git at git.haskell.org Mon Jun 1 08:48:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 08:48:09 +0000 (UTC) Subject: [commit: packages/binary] tag 'binary-0.7.5.0-release' created Message-ID: <20150601084809.8680B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary New tag : binary-0.7.5.0-release Referencing: beae163875375ed8ed6bcab9f0234d31552a06c7 From git at git.haskell.org Mon Jun 1 09:40:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 09:40:57 +0000 (UTC) Subject: [commit: ghc] master: rts: Fix aarch64 implementation of xchg (f6ca695) Message-ID: <20150601094057.9D21A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f6ca6959e54ede0b28735ab7e011c16b3cb172db/ghc >--------------------------------------------------------------- commit f6ca6959e54ede0b28735ab7e011c16b3cb172db Author: Erik de Castro Lopo Date: Thu May 28 02:57:28 2015 +0000 rts: Fix aarch64 implementation of xchg In the previous implementation, the `stlxr` instruction clobbered the value that was supposed to be returned by the the `xchg` function. Signed-off-by: Erik de Castro Lopo Test Plan: build on aarch64 Reviewers: austin, bgamari, rwbarton Subscribers: bgamari, thomie Differential Revision: https://phabricator.haskell.org/D932 >--------------------------------------------------------------- f6ca6959e54ede0b28735ab7e011c16b3cb172db includes/stg/SMP.h | 6 ++---- 1 file changed, 2 insertions(+), 4 deletions(-) diff --git a/includes/stg/SMP.h b/includes/stg/SMP.h index 10ef83e..fbc8bdc 100644 --- a/includes/stg/SMP.h +++ b/includes/stg/SMP.h @@ -158,13 +158,11 @@ xchg(StgPtr p, StgWord w) : "memory" ); #elif aarch64_HOST_ARCH - // Don't think we actually use tmp here, but leaving - // it for consistent numbering StgWord tmp; __asm__ __volatile__ ( "1: ldaxr %0, [%3]\n" - " stlxr %w0, %2, [%3]\n" - " cbnz %w0, 1b\n" + " stlxr %w1, %2, [%3]\n" + " cbnz %w1, 1b\n" " dmb sy\n" : "=&r" (result), "=&r" (tmp) : "r" (w), "r" (p) From git at git.haskell.org Mon Jun 1 09:51:24 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 09:51:24 +0000 (UTC) Subject: [commit: ghc] master: ApiAnnotations : rationalise tests (e00910b) Message-ID: <20150601095124.2E5023A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e00910b0f83eaafd91dcb59cec0779b3ea9f0d30/ghc >--------------------------------------------------------------- commit e00910b0f83eaafd91dcb59cec0779b3ea9f0d30 Author: Alan Zimmerman Date: Mon Jun 1 11:51:27 2015 +0200 ApiAnnotations : rationalise tests Summary: At the moment the API Annotations tests have a driver that has been copy/pasted multiple times. Compile it once, and run it for each test case. Test Plan: ./validate Reviewers: hvr, austin Reviewed By: austin Subscribers: bgamari, thomie Differential Revision: https://phabricator.haskell.org/D913 GHC Trac Issues: #10452 >--------------------------------------------------------------- e00910b0f83eaafd91dcb59cec0779b3ea9f0d30 testsuite/tests/ghc-api/annotations/.gitignore | 14 +- .../annotations/{t10278.hs => CheckUtils.hs} | 15 +- testsuite/tests/ghc-api/annotations/Makefile | 173 ++++++++++++--------- testsuite/tests/ghc-api/annotations/T10255.stderr | 3 - testsuite/tests/ghc-api/annotations/T10255.stdout | 2 + testsuite/tests/ghc-api/annotations/T10268.stderr | 6 +- testsuite/tests/ghc-api/annotations/T10268.stdout | 2 + testsuite/tests/ghc-api/annotations/T10269.stdout | 2 + testsuite/tests/ghc-api/annotations/T10280.stderr | 6 +- testsuite/tests/ghc-api/annotations/T10280.stdout | 2 + testsuite/tests/ghc-api/annotations/T10307.stdout | 2 + testsuite/tests/ghc-api/annotations/T10309.stdout | 2 + testsuite/tests/ghc-api/annotations/T10312.stdout | 2 + testsuite/tests/ghc-api/annotations/T10358.stderr | 12 -- testsuite/tests/ghc-api/annotations/T10358.stdout | 2 +- testsuite/tests/ghc-api/annotations/T10399.stderr | 12 +- testsuite/tests/ghc-api/annotations/T10399.stdout | 146 ++++++++--------- testsuite/tests/ghc-api/annotations/Test10255.hs | 2 +- testsuite/tests/ghc-api/annotations/Test10278.hs | 2 +- testsuite/tests/ghc-api/annotations/Test10358.hs | 2 +- testsuite/tests/ghc-api/annotations/Test10399.hs | 3 + testsuite/tests/ghc-api/annotations/all.T | 14 +- testsuite/tests/ghc-api/annotations/boolFormula.hs | 106 +------------ .../tests/ghc-api/annotations/boolFormula.stdout | 2 + testsuite/tests/ghc-api/annotations/exampleTest.hs | 111 +------------ .../tests/ghc-api/annotations/exampleTest.stdout | 2 + testsuite/tests/ghc-api/annotations/t10255.hs | 105 +------------ testsuite/tests/ghc-api/annotations/t10268.hs | 106 +------------ testsuite/tests/ghc-api/annotations/t10269.hs | 106 +------------ testsuite/tests/ghc-api/annotations/t10278.hs | 117 +------------- testsuite/tests/ghc-api/annotations/t10280.hs | 106 +------------ testsuite/tests/ghc-api/annotations/t10307.hs | 105 +------------ testsuite/tests/ghc-api/annotations/t10309.hs | 105 +------------ testsuite/tests/ghc-api/annotations/t10312.hs | 105 +------------ testsuite/tests/ghc-api/annotations/t10354.hs | 117 +------------- testsuite/tests/ghc-api/annotations/t10357.hs | 117 +------------- testsuite/tests/ghc-api/annotations/t10358.hs | 117 +------------- testsuite/tests/ghc-api/annotations/t10396.hs | 117 +------------- testsuite/tests/ghc-api/annotations/t10399.hs | 117 +------------- 39 files changed, 275 insertions(+), 1812 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc e00910b0f83eaafd91dcb59cec0779b3ea9f0d30 From git at git.haskell.org Mon Jun 1 10:55:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 10:55:30 +0000 (UTC) Subject: [commit: ghc] master: Update binary submodule to 0.7.5.0 release (7dd0ea7) Message-ID: <20150601105530.B2C1E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7dd0ea7428379df848e3d13528921b39b7bf5b95/ghc >--------------------------------------------------------------- commit 7dd0ea7428379df848e3d13528921b39b7bf5b95 Author: Herbert Valerio Riedel Date: Mon Jun 1 10:50:17 2015 +0200 Update binary submodule to 0.7.5.0 release Quoting the changelog, this pulls in the following fixes: binary-0.7.5.0 -------------- - Fix performance bug that was noticable when you get a big strict ByteString and the input to the decoder consists of many small chunks. - https://github.com/kolmodin/binary/issues/73 - https://github.com/kolmodin/binary/pull/76 - Fix memory leak when decoding Double and Float. - Commit 497a181c083fa9faf7fa3aa64d1d8deb9ac76ecb - We now require QuickCheck >= 2.8. Remove our version of arbitrarySizedNatural. binary-0.7.4.0 -------------- - Some invalid UTF-8 strings caused an exception when decoded. Those errors will now now fail in the Get monad instead. See issue 70. Patch contributed by @ttuegel. >--------------------------------------------------------------- 7dd0ea7428379df848e3d13528921b39b7bf5b95 libraries/binary | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/binary b/libraries/binary index ff9a48f..86e4c9a 160000 --- a/libraries/binary +++ b/libraries/binary @@ -1 +1 @@ -Subproject commit ff9a48fb213c2d1fd2e58b19c92264a3efadff7a +Subproject commit 86e4c9a6125cdddb0592a653f48c699a574ccf7b From git at git.haskell.org Mon Jun 1 12:16:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 12:16:40 +0000 (UTC) Subject: [commit: ghc] master: ApiAnnotations : strings in warnings do not return SourceText (e6191d1) Message-ID: <20150601121640.A5B833A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e6191d1cc37e98785af8b309100ea840084fa3ba/ghc >--------------------------------------------------------------- commit e6191d1cc37e98785af8b309100ea840084fa3ba Author: Alan Zimmerman Date: Mon Jun 1 14:16:41 2015 +0200 ApiAnnotations : strings in warnings do not return SourceText Summary: The strings used in a WARNING pragma are captured via strings :: { Located ([AddAnn],[Located FastString]) } : STRING { sL1 $1 ([],[L (gl $1) (getSTRING $1)]) } .. The STRING token has a method getSTRINGs that returns the original source text for a string. A warning of the form {-# WARNING Logic , mkSolver , mkSimpleSolver , mkSolverForLogic , solverSetParams , solverPush , solverPop , solverReset , solverGetNumScopes , solverAssertCnstr , solverAssertAndTrack , solverCheck , solverCheckAndGetModel , solverGetReasonUnknown "New Z3 API support is still incomplete and fragile: \ \you may experience segmentation faults!" #-} returns the concatenated warning string rather than the original source. This patch now deals with all remaining instances of getSTRING to bring in a SourceText for each. This updates the haddock submodule as well, for the AST change. Test Plan: ./validate Reviewers: hvr, austin, goldfire Reviewed By: austin Subscribers: bgamari, thomie, mpickering Differential Revision: https://phabricator.haskell.org/D907 GHC Trac Issues: #10313 >--------------------------------------------------------------- e6191d1cc37e98785af8b309100ea840084fa3ba compiler/basicTypes/BasicTypes.hs | 14 +++-- compiler/codeGen/StgCmmForeign.hs | 4 +- compiler/deSugar/Desugar.hs | 4 +- compiler/deSugar/DsCCall.hs | 3 +- compiler/deSugar/DsExpr.hs | 2 +- compiler/deSugar/DsForeign.hs | 15 +++-- compiler/deSugar/DsMeta.hs | 12 ++-- compiler/ghci/ByteCodeGen.hs | 4 +- compiler/hsSyn/Convert.hs | 5 +- compiler/hsSyn/HsDecls.hs | 13 +++-- compiler/hsSyn/HsExpr.hs | 13 +++-- compiler/hsSyn/HsImpExp.hs | 6 +- compiler/iface/MkIface.hs | 2 +- compiler/main/DriverMkDepend.hs | 2 +- compiler/main/GhcMake.hs | 3 +- compiler/main/HscMain.hs | 2 +- compiler/parser/Parser.y | 40 ++++++------- compiler/parser/RdrHsSyn.hs | 19 +++--- compiler/prelude/ForeignCall.hs | 38 +++++++----- compiler/prelude/TysWiredIn.hs | 22 +++---- compiler/rename/RnNames.hs | 8 +-- compiler/rename/RnSource.hs | 9 +-- compiler/stgSyn/CoreToStg.hs | 3 +- compiler/typecheck/TcForeign.hs | 8 +-- compiler/typecheck/TcRules.hs | 10 ++-- ghc/InteractiveUI.hs | 7 ++- testsuite/tests/ghc-api/annotations/.gitignore | 1 + testsuite/tests/ghc-api/annotations/Makefile | 6 ++ testsuite/tests/ghc-api/annotations/T10313.stderr | 29 ++++++++++ testsuite/tests/ghc-api/annotations/T10313.stdout | 27 +++++++++ testsuite/tests/ghc-api/annotations/Test10313.hs | 38 ++++++++++++ testsuite/tests/ghc-api/annotations/all.T | 1 + .../annotations/{parseTree.hs => stringSource.hs} | 67 +++++++++++++++++----- utils/haddock | 2 +- 34 files changed, 304 insertions(+), 135 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc e6191d1cc37e98785af8b309100ea840084fa3ba From git at git.haskell.org Mon Jun 1 13:10:53 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 13:10:53 +0000 (UTC) Subject: [commit: ghc] branch 'wip/api-annots-7.10-2' deleted Message-ID: <20150601131053.9E0443A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/api-annots-7.10-2 From git at git.haskell.org Mon Jun 1 13:11:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 13:11:18 +0000 (UTC) Subject: [commit: ghc] branch 'wip/api-annots-7.10' deleted Message-ID: <20150601131118.BA2933A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/api-annots-7.10 From git at git.haskell.org Mon Jun 1 13:18:06 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 13:18:06 +0000 (UTC) Subject: [commit: ghc] master: Add constraint creation functions to TcPluginM API (e8a7254) Message-ID: <20150601131806.6838F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e8a72548884beb94586041900562e55883d85189/ghc >--------------------------------------------------------------- commit e8a72548884beb94586041900562e55883d85189 Author: Adam Gundry Date: Mon Jun 1 13:36:57 2015 +0100 Add constraint creation functions to TcPluginM API Summary: This extends the TcPluginM API with functions to create new constraints, as described here: https://ghc.haskell.org/trac/ghc/wiki/Plugins/TypeChecker#Post-7.10changestoTcPluginMAPI Test Plan: validate and hope Reviewers: austin, yav, christiaanb Reviewed By: christiaanb Subscribers: bgamari, thomie Differential Revision: https://phabricator.haskell.org/D909 >--------------------------------------------------------------- e8a72548884beb94586041900562e55883d85189 compiler/typecheck/TcPluginM.hs | 67 +++++++++++++++++++++++++++++++++++++--- compiler/typecheck/TcRnDriver.hs | 4 +-- compiler/typecheck/TcRnTypes.hs | 23 +++++++++----- compiler/typecheck/TcSMonad.hs | 2 +- 4 files changed, 81 insertions(+), 15 deletions(-) diff --git a/compiler/typecheck/TcPluginM.hs b/compiler/typecheck/TcPluginM.hs index 5acf1b8..ecf8ed9 100644 --- a/compiler/typecheck/TcPluginM.hs +++ b/compiler/typecheck/TcPluginM.hs @@ -31,12 +31,24 @@ module TcPluginM ( matchFam, -- * Type variables + newUnique, newFlexiTyVar, isTouchableTcPluginM, -- * Zonking zonkTcType, - zonkCt + zonkCt, + + -- * Creating constraints + newWanted, + newDerived, + newGiven, + + -- * Manipulating evidence bindings + newEvVar, + setEvBind, + getEvBindsTcPluginM, + getEvBindsTcPluginM_maybe #endif ) where @@ -51,11 +63,14 @@ import qualified IfaceEnv import qualified Finder import FamInstEnv ( FamInstEnv ) -import TcRnMonad ( TcGblEnv, TcLclEnv, Ct, TcPluginM - , unsafeTcPluginTcM, liftIO, traceTc ) +import TcRnMonad ( TcGblEnv, TcLclEnv, Ct, CtLoc, TcPluginM + , unsafeTcPluginTcM, getEvBindsTcPluginM_maybe + , liftIO, traceTc ) import TcMType ( TcTyVar, TcType ) import TcEnv ( TcTyThing ) -import TcEvidence ( TcCoercion ) +import TcEvidence ( TcCoercion, EvTerm, EvBind, EvBindsVar, mkGivenEvBind ) +import TcRnTypes ( CtEvidence(..) ) +import Var ( EvVar ) import Module import Name @@ -68,6 +83,8 @@ import Type import Id import InstEnv import FastString +import Maybes +import Unique -- | Perform some IO, typically to interact with an external tool. @@ -123,6 +140,9 @@ matchFam :: TyCon -> [Type] -> TcPluginM (Maybe (TcCoercion, TcType)) matchFam tycon args = unsafeTcPluginTcM $ TcSMonad.matchFamTcM tycon args +newUnique :: TcPluginM Unique +newUnique = unsafeTcPluginTcM TcRnMonad.newUnique + newFlexiTyVar :: Kind -> TcPluginM TcTyVar newFlexiTyVar = unsafeTcPluginTcM . TcMType.newFlexiTyVar @@ -135,4 +155,43 @@ zonkTcType = unsafeTcPluginTcM . TcMType.zonkTcType zonkCt :: Ct -> TcPluginM Ct zonkCt = unsafeTcPluginTcM . TcMType.zonkCt + + +-- | Create a new wanted constraint. +newWanted :: CtLoc -> PredType -> TcPluginM CtEvidence +newWanted loc pty = do + new_ev <- newEvVar pty + return CtWanted { ctev_pred = pty, ctev_evar = new_ev, ctev_loc = loc } + +-- | Create a new derived constraint. +newDerived :: CtLoc -> PredType -> TcPluginM CtEvidence +newDerived loc pty = return CtDerived { ctev_pred = pty, ctev_loc = loc } + +-- | Create a new given constraint, with the supplied evidence. This +-- must not be invoked from 'tcPluginInit' or 'tcPluginStop', or it +-- will panic. +newGiven :: CtLoc -> PredType -> EvTerm -> TcPluginM CtEvidence +newGiven loc pty evtm = do + new_ev <- newEvVar pty + setEvBind $ mkGivenEvBind new_ev evtm + return CtGiven { ctev_pred = pty, ctev_evar = new_ev, ctev_loc = loc } + +-- | Create a fresh evidence variable. +newEvVar :: PredType -> TcPluginM EvVar +newEvVar = unsafeTcPluginTcM . TcMType.newEvVar + +-- | Bind an evidence variable. This must not be invoked from +-- 'tcPluginInit' or 'tcPluginStop', or it will panic. +setEvBind :: EvBind -> TcPluginM () +setEvBind ev_bind = do + tc_evbinds <- getEvBindsTcPluginM + unsafeTcPluginTcM $ TcMType.addTcEvBind tc_evbinds ev_bind + +-- | Access the 'EvBindsVar' carried by the 'TcPluginM' during +-- constraint solving. This must not be invoked from 'tcPluginInit' +-- or 'tcPluginStop', or it will panic. +getEvBindsTcPluginM :: TcPluginM EvBindsVar +getEvBindsTcPluginM = fmap (expectJust oops) getEvBindsTcPluginM_maybe + where + oops = "plugin attempted to read EvBindsVar outside the constraint solver" #endif diff --git a/compiler/typecheck/TcRnDriver.hs b/compiler/typecheck/TcRnDriver.hs index ec22699..1df1ca3 100644 --- a/compiler/typecheck/TcRnDriver.hs +++ b/compiler/typecheck/TcRnDriver.hs @@ -2157,13 +2157,13 @@ withTcPlugins hsc_env m = -- error occurs during compilation (Fix of #10078) eitherRes <- tryM $ do updGblEnv (\e -> e { tcg_tc_plugins = solvers }) m - mapM_ runTcPluginM stops + mapM_ (flip runTcPluginM Nothing) stops case eitherRes of Left _ -> failM Right res -> return res where startPlugin (TcPlugin start solve stop) = - do s <- runTcPluginM start + do s <- runTcPluginM start Nothing return (solve s, stop s) loadTcPlugins :: HscEnv -> IO [TcPlugin] diff --git a/compiler/typecheck/TcRnTypes.hs b/compiler/typecheck/TcRnTypes.hs index 3014755..5262e18 100644 --- a/compiler/typecheck/TcRnTypes.hs +++ b/compiler/typecheck/TcRnTypes.hs @@ -84,6 +84,7 @@ module TcRnTypes( -- Constraint solver plugins TcPlugin(..), TcPluginResult(..), TcPluginSolver, TcPluginM, runTcPluginM, unsafeTcPluginTcM, + getEvBindsTcPluginM_maybe, CtFlavour(..), ctEvFlavour, @@ -2209,7 +2210,7 @@ type TcPluginSolver = [Ct] -- given -> [Ct] -- wanted -> TcPluginM TcPluginResult -newtype TcPluginM a = TcPluginM (TcM a) +newtype TcPluginM a = TcPluginM (Maybe EvBindsVar -> TcM a) instance Functor TcPluginM where fmap = liftM @@ -2219,21 +2220,27 @@ instance Applicative TcPluginM where (<*>) = ap instance Monad TcPluginM where - return x = TcPluginM (return x) - fail x = TcPluginM (fail x) + return x = TcPluginM (const $ return x) + fail x = TcPluginM (const $ fail x) TcPluginM m >>= k = - TcPluginM (do a <- m - let TcPluginM m1 = k a - m1) + TcPluginM (\ ev -> do a <- m ev + runTcPluginM (k a) ev) -runTcPluginM :: TcPluginM a -> TcM a +runTcPluginM :: TcPluginM a -> Maybe EvBindsVar -> TcM a runTcPluginM (TcPluginM m) = m -- | This function provides an escape for direct access to -- the 'TcM` monad. It should not be used lightly, and -- the provided 'TcPluginM' API should be favoured instead. unsafeTcPluginTcM :: TcM a -> TcPluginM a -unsafeTcPluginTcM = TcPluginM +unsafeTcPluginTcM = TcPluginM . const + +-- | Access the 'EvBindsVar' carried by the 'TcPluginM' during +-- constraint solving. Returns 'Nothing' if invoked during +-- 'tcPluginInit' or 'tcPluginStop'. +getEvBindsTcPluginM_maybe :: TcPluginM (Maybe EvBindsVar) +getEvBindsTcPluginM_maybe = TcPluginM return + data TcPlugin = forall s. TcPlugin { tcPluginInit :: TcPluginM s diff --git a/compiler/typecheck/TcSMonad.hs b/compiler/typecheck/TcSMonad.hs index 39b01e7..3a3f912 100644 --- a/compiler/typecheck/TcSMonad.hs +++ b/compiler/typecheck/TcSMonad.hs @@ -1241,7 +1241,7 @@ traceTcS :: String -> SDoc -> TcS () traceTcS herald doc = wrapTcS (TcM.traceTc herald doc) runTcPluginTcS :: TcPluginM a -> TcS a -runTcPluginTcS = wrapTcS . runTcPluginM +runTcPluginTcS m = wrapTcS . runTcPluginM m . Just =<< getTcEvBinds instance HasDynFlags TcS where getDynFlags = wrapTcS getDynFlags From git at git.haskell.org Mon Jun 1 14:58:58 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 14:58:58 +0000 (UTC) Subject: [commit: ghc] master: Fix dropped event registrations (1c38325) Message-ID: <20150601145858.CD5B23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1c3832597b3e75456fc61628c4cd289d211c733b/ghc >--------------------------------------------------------------- commit 1c3832597b3e75456fc61628c4cd289d211c733b Author: Ben Gamari Date: Mon Jun 1 02:27:30 2015 -0500 Fix dropped event registrations D347 introduced a bug wherein the event manager would drop registrations that should be retained during processing. This occurs when an fd has multiple registrations, not all of which fire, as well as the case of multi-shot registrations. I also do some general house-keeping, try to better document things, and fix a bug which could result in unnecessary calls to `epoll_ctl` Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D849 GHC Trac Issues: #10317 >--------------------------------------------------------------- 1c3832597b3e75456fc61628c4cd289d211c733b libraries/base/GHC/Event/Internal.hs | 7 +++++-- libraries/base/GHC/Event/Manager.hs | 40 +++++++++++++++++++++++++----------- 2 files changed, 33 insertions(+), 14 deletions(-) diff --git a/libraries/base/GHC/Event/Internal.hs b/libraries/base/GHC/Event/Internal.hs index 3b75c8b..a093352 100644 --- a/libraries/base/GHC/Event/Internal.hs +++ b/libraries/base/GHC/Event/Internal.hs @@ -83,10 +83,12 @@ evtConcat :: [Event] -> Event evtConcat = foldl' evtCombine evtNothing {-# INLINE evtConcat #-} --- | The lifetime of a registration. +-- | The lifetime of an event registration. -- -- @since 4.8.1.0 -data Lifetime = OneShot | MultiShot +data Lifetime = OneShot -- ^ the registration will be active for only one + -- event + | MultiShot -- ^ the registration will trigger multiple times deriving (Show, Eq) -- | The longer of two lifetimes. @@ -95,6 +97,7 @@ elSupremum OneShot OneShot = OneShot elSupremum _ _ = MultiShot {-# INLINE elSupremum #-} +-- | @mappend@ == @elSupremum@ instance Monoid Lifetime where mempty = OneShot mappend = elSupremum diff --git a/libraries/base/GHC/Event/Manager.hs b/libraries/base/GHC/Event/Manager.hs index 11b01ad..b674866 100644 --- a/libraries/base/GHC/Event/Manager.hs +++ b/libraries/base/GHC/Event/Manager.hs @@ -456,20 +456,35 @@ onFdEvent mgr fd evs | otherwise = do fdds <- withMVar (callbackTableVar mgr fd) $ \tbl -> - IT.delete (fromIntegral fd) tbl >>= maybe (return []) selectCallbacks + IT.delete (fromIntegral fd) tbl >>= maybe (return []) (selectCallbacks tbl) forM_ fdds $ \(FdData reg _ cb) -> cb reg evs where -- | Here we look through the list of registrations for the fd of interest - -- and sort out which match the events that were triggered. We re-arm - -- the fd as appropriate and return this subset. - selectCallbacks :: [FdData] -> IO [FdData] - selectCallbacks fdds = do - let matches :: FdData -> Bool + -- and sort out which match the events that were triggered. We, + -- + -- 1. re-arm the fd as appropriate + -- 2. reinsert registrations that weren't triggered and multishot + -- registrations + -- 3. return a list containing the callbacks that should be invoked. + selectCallbacks :: IntTable [FdData] -> [FdData] -> IO [FdData] + selectCallbacks tbl fdds = do + let -- figure out which registrations have been triggered + matches :: FdData -> Bool matches fd' = evs `I.eventIs` I.elEvent (fdEvents fd') - (triggered, saved) = partition matches fdds + (triggered, notTriggered) = partition matches fdds + + -- sort out which registrations we need to retain + isMultishot :: FdData -> Bool + isMultishot fd' = I.elLifetime (fdEvents fd') == MultiShot + saved = notTriggered ++ filter isMultishot triggered + savedEls = eventsOf saved allEls = eventsOf fdds + -- Reinsert multishot registrations. + -- We deleted the table entry for this fd above so we there isn't a preexisting entry + _ <- IT.insertWith (\_ _ -> saved) (fromIntegral fd) saved tbl + case I.elLifetime allEls of -- we previously armed the fd for multiple shots, no need to rearm MultiShot | allEls == savedEls -> @@ -477,17 +492,18 @@ onFdEvent mgr fd evs -- either we previously registered for one shot or the -- events of interest have changed, we must re-arm - _ -> do + _ -> case I.elLifetime savedEls of OneShot | haveOneShot -> - -- if there are no saved events there is no need to re-arm - unless (OneShot == I.elLifetime (eventsOf triggered) - && mempty == savedEls) $ + -- if there are no saved events and we registered with one-shot + -- semantics then there is no need to re-arm + unless (OneShot == I.elLifetime allEls + && mempty == I.elEvent savedEls) $ do void $ I.modifyFdOnce (emBackend mgr) fd (I.elEvent savedEls) _ -> + -- we need to re-arm with multi-shot semantics void $ I.modifyFd (emBackend mgr) fd (I.elEvent allEls) (I.elEvent savedEls) - return () return triggered From git at git.haskell.org Mon Jun 1 15:01:42 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 15:01:42 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Catch canonicalizePath exceptions, fix #10101 (8203730) Message-ID: <20150601150142.38E4A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/8203730db984b31d2df5597af3870ad47df82f64/ghc >--------------------------------------------------------------- commit 8203730db984b31d2df5597af3870ad47df82f64 Author: Flaviu Andrei Csernik (archblob) Date: Mon Jun 1 02:13:36 2015 -0500 Catch canonicalizePath exceptions, fix #10101 Summary: Introduce by #95 'canonicalizePath' throws and exception when given an invalid file in a call to 'sameFile'. There are two cases when this can happen when using ghci: 1) If there is an error at the interactive prompt, "" file is searched for and not found. 2) If there is an error in any loaded file and editing an inexistent/new file with 'e: foo'. Both cases are now tested. Test Plan: validate Reviewers: austin, #ghc Reviewed By: austin, #ghc Subscribers: bgamari, thomie Differential Revision: https://phabricator.haskell.org/D930 GHC Trac Issues: #10101 (cherry picked from commit 4756438962a76d2dcedf63b90ec789cb054f9556) >--------------------------------------------------------------- 8203730db984b31d2df5597af3870ad47df82f64 ghc/InteractiveUI.hs | 9 +++------ testsuite/tests/ghci/prog013/prog013.script | 4 ++++ testsuite/tests/ghci/prog013/prog013.stderr | 14 +++++++++++--- testsuite/tests/ghci/prog013/prog013.stdout | 2 ++ 4 files changed, 20 insertions(+), 9 deletions(-) diff --git a/ghc/InteractiveUI.hs b/ghc/InteractiveUI.hs index 06fbc57..7bb3c06 100644 --- a/ghc/InteractiveUI.hs +++ b/ghc/InteractiveUI.hs @@ -1225,6 +1225,9 @@ editFile str = when (null cmd) $ throwGhcException (CmdLineError "editor not set, use :set editor") lineOpt <- liftIO $ do + let sameFile p1 p2 = liftA2 (==) (canonicalizePath p1) (canonicalizePath p2) + `catchIO` (\_ -> return False) + curFileErrs <- filterM (\(f, _) -> unpackFS f `sameFile` file) errs return $ case curFileErrs of (_, line):_ -> " +" ++ show line @@ -3191,12 +3194,6 @@ expandPathIO p = other -> return other -sameFile :: FilePath -> FilePath -> IO Bool -sameFile path1 path2 = do - absPath1 <- canonicalizePath path1 - absPath2 <- canonicalizePath path2 - return $ absPath1 == absPath2 - wantInterpretedModule :: GHC.GhcMonad m => String -> m Module wantInterpretedModule str = wantInterpretedModuleName (GHC.mkModuleName str) diff --git a/testsuite/tests/ghci/prog013/prog013.script b/testsuite/tests/ghci/prog013/prog013.script index d4b91de..f2e2343 100644 --- a/testsuite/tests/ghci/prog013/prog013.script +++ b/testsuite/tests/ghci/prog013/prog013.script @@ -6,3 +6,7 @@ :e ./Bad.hs :l Good.hs :e ++ +:e foo +:l Bad.hs +:e bar diff --git a/testsuite/tests/ghci/prog013/prog013.stderr b/testsuite/tests/ghci/prog013/prog013.stderr index d8970d4..ce8827f 100644 --- a/testsuite/tests/ghci/prog013/prog013.stderr +++ b/testsuite/tests/ghci/prog013/prog013.stderr @@ -1,9 +1,17 @@ -Bad.hs:3:8: +Bad.hs:3:8: error: lexical error in string/character literal at character '\n' -Bad.hs:3:8: +Bad.hs:3:8: error: lexical error in string/character literal at character '\n' -Bad.hs:3:8: +Bad.hs:3:8: error: + lexical error in string/character literal at character '\n' + +:10:1: error: parse error on input ?+? + +Bad.hs:3:8: error: + lexical error in string/character literal at character '\n' + +Bad.hs:3:8: error: lexical error in string/character literal at character '\n' diff --git a/testsuite/tests/ghci/prog013/prog013.stdout b/testsuite/tests/ghci/prog013/prog013.stdout index 0d621da..024fd79 100644 --- a/testsuite/tests/ghci/prog013/prog013.stdout +++ b/testsuite/tests/ghci/prog013/prog013.stdout @@ -2,3 +2,5 @@ Good.hs Bad.hs +3 ./Bad.hs +3 Good.hs +foo +bar From git at git.haskell.org Mon Jun 1 15:01:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 15:01:45 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: compiler/specialise: shut match_co up a bit (71d1574) Message-ID: <20150601150145.1A4233A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/71d1574479a4f413358fd0c0526b722d2d797ea6/ghc >--------------------------------------------------------------- commit 71d1574479a4f413358fd0c0526b722d2d797ea6 Author: Austin Seipp Date: Mon Jun 1 03:45:11 2015 -0500 compiler/specialise: shut match_co up a bit This stray pprTrace is quite annoying and makes our build logs a bit bigger (hundreds of lines of occurrences), so we should probably just get rid of it. Kept under DEBUG for future brave hackers. Signed-off-by: Austin Seipp Reviewed By: thomie, nomeata Differential Revision: https://phabricator.haskell.org/D934 (cherry picked from commit f5b43ce177e40a34afb1913bc0ec866185ed95d7) >--------------------------------------------------------------- 71d1574479a4f413358fd0c0526b722d2d797ea6 compiler/specialise/Rules.hs | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/compiler/specialise/Rules.hs b/compiler/specialise/Rules.hs index b66d973..2169dc7 100644 --- a/compiler/specialise/Rules.hs +++ b/compiler/specialise/Rules.hs @@ -739,9 +739,13 @@ match_co renv subst (TyConAppCo r1 tc1 cos1) co2 | r1 == r2 && tc1 == tc2 -> match_cos renv subst cos1 cos2 _ -> Nothing -match_co _ _ co1 co2 - = pprTrace "match_co: needs more cases" (ppr co1 $$ ppr co2) Nothing +match_co _ _ _co1 _co2 -- Currently just deals with CoVarCo, TyConAppCo and Refl +#ifdef DEBUG + = pprTrace "match_co: needs more cases" (ppr _co1 $$ ppr _co2) Nothing +#else + = Nothing +#endif match_cos :: RuleMatchEnv -> RuleSubst From git at git.haskell.org Mon Jun 1 15:01:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 15:01:47 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: rts: Fix aarch64 implementation of xchg (1cce187) Message-ID: <20150601150147.E3C523A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/1cce18721b1497894fd2b14fc4557f0beafa6f50/ghc >--------------------------------------------------------------- commit 1cce18721b1497894fd2b14fc4557f0beafa6f50 Author: Erik de Castro Lopo Date: Thu May 28 02:57:28 2015 +0000 rts: Fix aarch64 implementation of xchg In the previous implementation, the `stlxr` instruction clobbered the value that was supposed to be returned by the the `xchg` function. Signed-off-by: Erik de Castro Lopo Test Plan: build on aarch64 Reviewers: austin, bgamari, rwbarton Subscribers: bgamari, thomie Differential Revision: https://phabricator.haskell.org/D932 (cherry picked from commit f6ca6959e54ede0b28735ab7e011c16b3cb172db) >--------------------------------------------------------------- 1cce18721b1497894fd2b14fc4557f0beafa6f50 includes/stg/SMP.h | 6 ++---- 1 file changed, 2 insertions(+), 4 deletions(-) diff --git a/includes/stg/SMP.h b/includes/stg/SMP.h index 5460a2b..156ee42 100644 --- a/includes/stg/SMP.h +++ b/includes/stg/SMP.h @@ -158,13 +158,11 @@ xchg(StgPtr p, StgWord w) : "memory" ); #elif aarch64_HOST_ARCH - // Don't think we actually use tmp here, but leaving - // it for consistent numbering StgWord tmp; __asm__ __volatile__ ( "1: ldaxr %0, [%3]\n" - " stlxr %w0, %2, [%3]\n" - " cbnz %w0, 1b\n" + " stlxr %w1, %2, [%3]\n" + " cbnz %w1, 1b\n" " dmb sy\n" : "=&r" (result), "=&r" (tmp) : "r" (w), "r" (p) From git at git.haskell.org Mon Jun 1 15:01:50 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 15:01:50 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Fix dropped event registrations (53ef912) Message-ID: <20150601150150.AAAA73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/53ef9124b67515c589ee444933c168e4686d618b/ghc >--------------------------------------------------------------- commit 53ef9124b67515c589ee444933c168e4686d618b Author: Ben Gamari Date: Mon Jun 1 02:27:30 2015 -0500 Fix dropped event registrations D347 introduced a bug wherein the event manager would drop registrations that should be retained during processing. This occurs when an fd has multiple registrations, not all of which fire, as well as the case of multi-shot registrations. I also do some general house-keeping, try to better document things, and fix a bug which could result in unnecessary calls to `epoll_ctl` Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D849 GHC Trac Issues: #10317 (cherry picked from commit 1c3832597b3e75456fc61628c4cd289d211c733b) >--------------------------------------------------------------- 53ef9124b67515c589ee444933c168e4686d618b libraries/base/GHC/Event/Internal.hs | 7 +++++-- libraries/base/GHC/Event/Manager.hs | 40 +++++++++++++++++++++++++----------- 2 files changed, 33 insertions(+), 14 deletions(-) diff --git a/libraries/base/GHC/Event/Internal.hs b/libraries/base/GHC/Event/Internal.hs index 3b75c8b..a093352 100644 --- a/libraries/base/GHC/Event/Internal.hs +++ b/libraries/base/GHC/Event/Internal.hs @@ -83,10 +83,12 @@ evtConcat :: [Event] -> Event evtConcat = foldl' evtCombine evtNothing {-# INLINE evtConcat #-} --- | The lifetime of a registration. +-- | The lifetime of an event registration. -- -- @since 4.8.1.0 -data Lifetime = OneShot | MultiShot +data Lifetime = OneShot -- ^ the registration will be active for only one + -- event + | MultiShot -- ^ the registration will trigger multiple times deriving (Show, Eq) -- | The longer of two lifetimes. @@ -95,6 +97,7 @@ elSupremum OneShot OneShot = OneShot elSupremum _ _ = MultiShot {-# INLINE elSupremum #-} +-- | @mappend@ == @elSupremum@ instance Monoid Lifetime where mempty = OneShot mappend = elSupremum diff --git a/libraries/base/GHC/Event/Manager.hs b/libraries/base/GHC/Event/Manager.hs index 11b01ad..b674866 100644 --- a/libraries/base/GHC/Event/Manager.hs +++ b/libraries/base/GHC/Event/Manager.hs @@ -456,20 +456,35 @@ onFdEvent mgr fd evs | otherwise = do fdds <- withMVar (callbackTableVar mgr fd) $ \tbl -> - IT.delete (fromIntegral fd) tbl >>= maybe (return []) selectCallbacks + IT.delete (fromIntegral fd) tbl >>= maybe (return []) (selectCallbacks tbl) forM_ fdds $ \(FdData reg _ cb) -> cb reg evs where -- | Here we look through the list of registrations for the fd of interest - -- and sort out which match the events that were triggered. We re-arm - -- the fd as appropriate and return this subset. - selectCallbacks :: [FdData] -> IO [FdData] - selectCallbacks fdds = do - let matches :: FdData -> Bool + -- and sort out which match the events that were triggered. We, + -- + -- 1. re-arm the fd as appropriate + -- 2. reinsert registrations that weren't triggered and multishot + -- registrations + -- 3. return a list containing the callbacks that should be invoked. + selectCallbacks :: IntTable [FdData] -> [FdData] -> IO [FdData] + selectCallbacks tbl fdds = do + let -- figure out which registrations have been triggered + matches :: FdData -> Bool matches fd' = evs `I.eventIs` I.elEvent (fdEvents fd') - (triggered, saved) = partition matches fdds + (triggered, notTriggered) = partition matches fdds + + -- sort out which registrations we need to retain + isMultishot :: FdData -> Bool + isMultishot fd' = I.elLifetime (fdEvents fd') == MultiShot + saved = notTriggered ++ filter isMultishot triggered + savedEls = eventsOf saved allEls = eventsOf fdds + -- Reinsert multishot registrations. + -- We deleted the table entry for this fd above so we there isn't a preexisting entry + _ <- IT.insertWith (\_ _ -> saved) (fromIntegral fd) saved tbl + case I.elLifetime allEls of -- we previously armed the fd for multiple shots, no need to rearm MultiShot | allEls == savedEls -> @@ -477,17 +492,18 @@ onFdEvent mgr fd evs -- either we previously registered for one shot or the -- events of interest have changed, we must re-arm - _ -> do + _ -> case I.elLifetime savedEls of OneShot | haveOneShot -> - -- if there are no saved events there is no need to re-arm - unless (OneShot == I.elLifetime (eventsOf triggered) - && mempty == savedEls) $ + -- if there are no saved events and we registered with one-shot + -- semantics then there is no need to re-arm + unless (OneShot == I.elLifetime allEls + && mempty == I.elEvent savedEls) $ do void $ I.modifyFdOnce (emBackend mgr) fd (I.elEvent savedEls) _ -> + -- we need to re-arm with multi-shot semantics void $ I.modifyFd (emBackend mgr) fd (I.elEvent allEls) (I.elEvent savedEls) - return () return triggered From git at git.haskell.org Mon Jun 1 15:16:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 15:16:29 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Test case for indirect dependencies in ghci linker (#10322) (eae1ac8) Message-ID: <20150601151629.C68883A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/eae1ac8b61714f2d50c3b47709a96ab7708329cb/ghc >--------------------------------------------------------------- commit eae1ac8b61714f2d50c3b47709a96ab7708329cb Author: Reid Barton Date: Wed Apr 15 16:46:47 2015 -0400 Test case for indirect dependencies in ghci linker (#10322) (cherry picked from commit 88b84063c11a48820011805a8341d95f7fcd59db) >--------------------------------------------------------------- eae1ac8b61714f2d50c3b47709a96ab7708329cb testsuite/tests/ghci/scripts/T10322.script | 5 +++++ testsuite/tests/ghci/scripts/{T8696.stdout => T10322.stdout} | 1 + testsuite/tests/ghci/scripts/{T10110A.hs => T10322A.hs} | 2 +- testsuite/tests/ghci/scripts/T10322B.hs | 4 ++++ testsuite/tests/ghci/scripts/T10322C.hs | 5 +++++ testsuite/tests/ghci/scripts/all.T | 2 ++ 6 files changed, 18 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/ghci/scripts/T10322.script b/testsuite/tests/ghci/scripts/T10322.script new file mode 100644 index 0000000..75f2a39 --- /dev/null +++ b/testsuite/tests/ghci/scripts/T10322.script @@ -0,0 +1,5 @@ +:set -fobject-code +:load T10322A T10322B T10322C +T10322A.a +T10322B.b +T10322C.c diff --git a/testsuite/tests/ghci/scripts/T8696.stdout b/testsuite/tests/ghci/scripts/T10322.stdout similarity index 66% copy from testsuite/tests/ghci/scripts/T8696.stdout copy to testsuite/tests/ghci/scripts/T10322.stdout index b944734..de9da6d 100644 --- a/testsuite/tests/ghci/scripts/T8696.stdout +++ b/testsuite/tests/ghci/scripts/T10322.stdout @@ -1,2 +1,3 @@ 3 4 +7 diff --git a/testsuite/tests/ghci/scripts/T10110A.hs b/testsuite/tests/ghci/scripts/T10322A.hs similarity index 57% copy from testsuite/tests/ghci/scripts/T10110A.hs copy to testsuite/tests/ghci/scripts/T10322A.hs index 8482e7f..ba01fd2 100644 --- a/testsuite/tests/ghci/scripts/T10110A.hs +++ b/testsuite/tests/ghci/scripts/T10322A.hs @@ -1,4 +1,4 @@ -module T10110A (a) where +module T10322A (a) where {-# NOINLINE a #-} a :: Int a = 3 diff --git a/testsuite/tests/ghci/scripts/T10322B.hs b/testsuite/tests/ghci/scripts/T10322B.hs new file mode 100644 index 0000000..aa0b73a --- /dev/null +++ b/testsuite/tests/ghci/scripts/T10322B.hs @@ -0,0 +1,4 @@ +module T10322B (b) where +import T10322A (a) +b :: Int +b = a+1 diff --git a/testsuite/tests/ghci/scripts/T10322C.hs b/testsuite/tests/ghci/scripts/T10322C.hs new file mode 100644 index 0000000..b6ad6e9 --- /dev/null +++ b/testsuite/tests/ghci/scripts/T10322C.hs @@ -0,0 +1,5 @@ +module T10322C (c) where +import T10322A (a) +import T10322B (b) +c :: Int +c = a+b diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T index 69c5254..631d6dc 100755 --- a/testsuite/tests/ghci/scripts/all.T +++ b/testsuite/tests/ghci/scripts/all.T @@ -209,3 +209,5 @@ test('T9878b', test('T10321', normal, ghci_script, ['T10321.script']) test('T10110', normal, ghci_script, ['T10110.script']) +test('T10322', when(opsys('darwin'), expect_broken(10322)), + ghci_script, ['T10322.script']) From git at git.haskell.org Mon Jun 1 15:16:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 15:16:32 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: In ghci linker, link against all previous temp sos (#10322) (96d4d03) Message-ID: <20150601151632.8BC6E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/96d4d036fadaf5468a63b075ffea848e19d08d34/ghc >--------------------------------------------------------------- commit 96d4d036fadaf5468a63b075ffea848e19d08d34 Author: Reid Barton Date: Tue May 19 01:23:59 2015 -0500 In ghci linker, link against all previous temp sos (#10322) The OS X dlopen() appears to only resolve undefined symbols in the direct dependencies of the shared library it is loading. Reviewed By: trommler, austin Differential Revision: https://phabricator.haskell.org/D852 GHC Trac Issues: #10322 (cherry picked from commit a52f1444ea4045a2075dc88bb973a9289ee7e2cf) >--------------------------------------------------------------- 96d4d036fadaf5468a63b075ffea848e19d08d34 compiler/ghci/Linker.hs | 22 +++++++++++----------- testsuite/tests/ghci/scripts/all.T | 3 +-- 2 files changed, 12 insertions(+), 13 deletions(-) diff --git a/compiler/ghci/Linker.hs b/compiler/ghci/Linker.hs index f9467e1..b5979e8 100644 --- a/compiler/ghci/Linker.hs +++ b/compiler/ghci/Linker.hs @@ -118,9 +118,9 @@ data PersistentLinkerState -- that is really important pkgs_loaded :: ![PackageKey], - -- we need to remember the name of the last temporary DLL/.so - -- so we can link it - last_temp_so :: !(Maybe (FilePath, String)) } + -- we need to remember the name of previous temporary DLL/.so + -- libraries so we can link them (see #10322) + temp_sos :: ![(FilePath, String)] } emptyPLS :: DynFlags -> PersistentLinkerState @@ -130,7 +130,7 @@ emptyPLS _ = PersistentLinkerState { pkgs_loaded = init_pkgs, bcos_loaded = [], objs_loaded = [], - last_temp_so = Nothing } + temp_sos = [] } -- Packages that don't need loading, because the compiler -- shares them with the interpreted program. @@ -826,19 +826,19 @@ dynLoadObjs dflags pls objs = do dflags2 = dflags1 { -- We don't want the original ldInputs in -- (they're already linked in), but we do want - -- to link against the previous dynLoadObjs - -- library if there was one, so that the linker + -- to link against previous dynLoadObjs + -- libraries if there were any, so that the linker -- can resolve dependencies when it loads this -- library. ldInputs = - case last_temp_so pls of - Nothing -> [] - Just (lp, l) -> + concatMap + (\(lp, l) -> [ Option ("-L" ++ lp) , Option ("-Wl,-rpath") , Option ("-Wl," ++ lp) , Option ("-l" ++ l) - ], + ]) + (temp_sos pls), -- Even if we're e.g. profiling, we still want -- the vanilla dynamic libraries, so we set the -- ways / build tag to be just WayDyn. @@ -853,7 +853,7 @@ dynLoadObjs dflags pls objs = do consIORef (filesToNotIntermediateClean dflags) soFile m <- loadDLL soFile case m of - Nothing -> return pls { last_temp_so = Just (libPath, libName) } + Nothing -> return pls { temp_sos = (libPath, libName) : temp_sos pls } Just err -> panic ("Loading temp shared object failed: " ++ err) rmDupLinkables :: [Linkable] -- Already loaded diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T index 631d6dc..686d3bb 100755 --- a/testsuite/tests/ghci/scripts/all.T +++ b/testsuite/tests/ghci/scripts/all.T @@ -209,5 +209,4 @@ test('T9878b', test('T10321', normal, ghci_script, ['T10321.script']) test('T10110', normal, ghci_script, ['T10110.script']) -test('T10322', when(opsys('darwin'), expect_broken(10322)), - ghci_script, ['T10322.script']) +test('T10322', normal, ghci_script, ['T10322.script']) From git at git.haskell.org Mon Jun 1 16:15:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 16:15:41 +0000 (UTC) Subject: [commit: ghc] master: Use seq rather than (==) to force the size (928f536) Message-ID: <20150601161541.06EE33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/928f536cc5a7d333335795b658bb3072f1b5df18/ghc >--------------------------------------------------------------- commit 928f536cc5a7d333335795b658bb3072f1b5df18 Author: Simon Peyton Jones Date: Mon Jun 1 08:49:09 2015 +0100 Use seq rather than (==) to force the size Just a minor refactoring >--------------------------------------------------------------- 928f536cc5a7d333335795b658bb3072f1b5df18 compiler/simplCore/SimplCore.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/simplCore/SimplCore.hs b/compiler/simplCore/SimplCore.hs index da27c35..d83ab89 100644 --- a/compiler/simplCore/SimplCore.hs +++ b/compiler/simplCore/SimplCore.hs @@ -599,7 +599,7 @@ simplifyPgmIO pass@(CoreDoSimplify max_iterations mode) -- Try and force thunks off the binds; significantly reduces -- space usage, especially with -O. JRS, 000620. | let sz = coreBindsSize binds - , sz == sz -- Force it + , () <- sz `seq` () -- Force it = do { -- Occurrence analysis let { -- Note [Vectorisation declarations and occurrences] From git at git.haskell.org Mon Jun 1 16:15:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 16:15:43 +0000 (UTC) Subject: [commit: ghc] master: Move seqExpr, seqIdInfo etc to CoreUtils (5eee6a1) Message-ID: <20150601161543.C152C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5eee6a1ffa6e1705a1517631ba599fdb4455b416/ghc >--------------------------------------------------------------- commit 5eee6a1ffa6e1705a1517631ba599fdb4455b416 Author: Simon Peyton Jones Date: Mon Jun 1 08:51:10 2015 +0100 Move seqExpr, seqIdInfo etc to CoreUtils Refactoring only : it just brings some scattered "seq" code together >--------------------------------------------------------------- 5eee6a1ffa6e1705a1517631ba599fdb4455b416 compiler/basicTypes/Id.hs | 2 +- compiler/basicTypes/IdInfo.hs | 38 +-------------- compiler/coreSyn/CoreSyn.hs | 73 +--------------------------- compiler/coreSyn/CoreUtils.hs | 108 ++++++++++++++++++++++++++++++++++++++++++ compiler/coreSyn/PprCore.hs | 2 +- 5 files changed, 112 insertions(+), 111 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 5eee6a1ffa6e1705a1517631ba599fdb4455b416 From git at git.haskell.org Mon Jun 1 16:15:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 16:15:46 +0000 (UTC) Subject: [commit: ghc] master: Add some missing seqs to Coercion.seqCo (20d8621) Message-ID: <20150601161546.919DA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/20d8621148b3e12da8ee7d6e5952d7c7222428ea/ghc >--------------------------------------------------------------- commit 20d8621148b3e12da8ee7d6e5952d7c7222428ea Author: Simon Peyton Jones Date: Mon Jun 1 08:51:42 2015 +0100 Add some missing seqs to Coercion.seqCo >--------------------------------------------------------------- 20d8621148b3e12da8ee7d6e5952d7c7222428ea compiler/types/Coercion.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/compiler/types/Coercion.hs b/compiler/types/Coercion.hs index 797f785..3a55bcc 100644 --- a/compiler/types/Coercion.hs +++ b/compiler/types/Coercion.hs @@ -1855,14 +1855,14 @@ seqCo :: Coercion -> () seqCo (Refl eq ty) = eq `seq` seqType ty seqCo (TyConAppCo eq tc cos) = eq `seq` tc `seq` seqCos cos seqCo (AppCo co1 co2) = seqCo co1 `seq` seqCo co2 -seqCo (ForAllCo tv co) = tv `seq` seqCo co +seqCo (ForAllCo tv co) = seqType (tyVarKind tv) `seq` seqCo co seqCo (CoVarCo cv) = cv `seq` () seqCo (AxiomInstCo con ind cos) = con `seq` ind `seq` seqCos cos seqCo (UnivCo s r ty1 ty2) = s `seq` r `seq` seqType ty1 `seq` seqType ty2 seqCo (SymCo co) = seqCo co seqCo (TransCo co1 co2) = seqCo co1 `seq` seqCo co2 -seqCo (NthCo _ co) = seqCo co -seqCo (LRCo _ co) = seqCo co +seqCo (NthCo n co) = n `seq` seqCo co +seqCo (LRCo lr co) = lr `seq` seqCo co seqCo (InstCo co ty) = seqCo co `seq` seqType ty seqCo (SubCo co) = seqCo co seqCo (AxiomRuleCo _ ts cs) = seqTypes ts `seq` seqCos cs From git at git.haskell.org Mon Jun 1 16:15:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 16:15:49 +0000 (UTC) Subject: [commit: ghc] master: Use named fields in SimplCont.Select constructor (d245787) Message-ID: <20150601161549.59C403A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d2457877c487ed3543bd7804358739aed7f37287/ghc >--------------------------------------------------------------- commit d2457877c487ed3543bd7804358739aed7f37287 Author: Simon Peyton Jones Date: Mon Jun 1 08:57:01 2015 +0100 Use named fields in SimplCont.Select constructor Just refactoring >--------------------------------------------------------------- d2457877c487ed3543bd7804358739aed7f37287 compiler/simplCore/SimplUtils.hs | 41 +++++++++++++++++++++------------------- compiler/simplCore/Simplify.hs | 28 ++++++++++++++++----------- 2 files changed, 39 insertions(+), 30 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d2457877c487ed3543bd7804358739aed7f37287 From git at git.haskell.org Mon Jun 1 16:15:52 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 16:15:52 +0000 (UTC) Subject: [commit: ghc] master: Comments only (403cfc9) Message-ID: <20150601161552.2C61E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/403cfc9187b9df560768bb809f4d280fb999639c/ghc >--------------------------------------------------------------- commit 403cfc9187b9df560768bb809f4d280fb999639c Author: Simon Peyton Jones Date: Mon Jun 1 08:57:23 2015 +0100 Comments only >--------------------------------------------------------------- 403cfc9187b9df560768bb809f4d280fb999639c compiler/typecheck/TcValidity.hs | 15 +++++++++++---- 1 file changed, 11 insertions(+), 4 deletions(-) diff --git a/compiler/typecheck/TcValidity.hs b/compiler/typecheck/TcValidity.hs index 16059e6..370cad2 100644 --- a/compiler/typecheck/TcValidity.hs +++ b/compiler/typecheck/TcValidity.hs @@ -132,12 +132,19 @@ We call checkAmbiguity (b) in checkValidType Conncerning (b), you might wonder about nested foralls. What about - f :: (forall a. Eq a => Int) -> Int + f :: forall b. (forall a. Eq a => b) -> b The nested forall is ambiguous. Originally we called checkAmbiguity -in the forall case of check_type, but that had a bad consequence: -we got two error messages about (Eq b) in a nested forall like this: - g :: forall a. Eq a => forall b. Eq b => a -> a +in the forall case of check_type, but that had two bad consequences: + * We got two error messages about (Eq b) in a nested forall like this: + g :: forall a. Eq a => forall b. Eq b => a -> a + * If we try to check for ambiguity of an nested forall like + (forall a. Eq a => b), the implication constraint doesn't bind + all the skolems, which results in "No skolem info" in error + messages (see Trac #10432). + To avoid this, we call checkAmbiguity once, at the top, in checkValidType. +(I'm still a bit worried about unbound skolems when the type mentions +in-scope type variables.) In fact, because of the co/contra-variance implemented in tcSubType, this *does* catch function f above. too. From git at git.haskell.org Mon Jun 1 16:19:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 16:19:44 +0000 (UTC) Subject: [commit: ghc] branch 'wip/api-annots-7.10-3' created Message-ID: <20150601161944.3AA903A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/api-annots-7.10-3 Referencing: d06ce0317f38d4ea9f979208a73abf691aecee06 From git at git.haskell.org Mon Jun 1 16:19:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 16:19:47 +0000 (UTC) Subject: [commit: ghc] wip/api-annots-7.10-3: ApiAnnotations : rationalise tests (9f7eb94) Message-ID: <20150601161947.55F7B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/api-annots-7.10-3 Link : http://ghc.haskell.org/trac/ghc/changeset/9f7eb944e64c0e57ebbad2b795c519ed37f24bf8/ghc >--------------------------------------------------------------- commit 9f7eb944e64c0e57ebbad2b795c519ed37f24bf8 Author: Alan Zimmerman Date: Mon Jun 1 11:51:27 2015 +0200 ApiAnnotations : rationalise tests Summary: At the moment the API Annotations tests have a driver that has been copy/pasted multiple times. Compile it once, and run it for each test case. Test Plan: ./validate Reviewers: hvr, austin Reviewed By: austin Subscribers: bgamari, thomie Differential Revision: https://phabricator.haskell.org/D913 GHC Trac Issues: #10452 (cherry picked from commit e00910b0f83eaafd91dcb59cec0779b3ea9f0d30) Conflicts: testsuite/tests/ghc-api/annotations/T10358.stderr testsuite/tests/ghc-api/annotations/T10399.stderr >--------------------------------------------------------------- 9f7eb944e64c0e57ebbad2b795c519ed37f24bf8 testsuite/tests/ghc-api/annotations/.gitignore | 14 +- .../annotations/{t10278.hs => CheckUtils.hs} | 15 +- testsuite/tests/ghc-api/annotations/Makefile | 173 ++++++++++++--------- testsuite/tests/ghc-api/annotations/T10255.stderr | 3 - testsuite/tests/ghc-api/annotations/T10255.stdout | 2 + testsuite/tests/ghc-api/annotations/T10268.stdout | 2 + testsuite/tests/ghc-api/annotations/T10269.stdout | 2 + testsuite/tests/ghc-api/annotations/T10280.stdout | 2 + testsuite/tests/ghc-api/annotations/T10307.stdout | 2 + testsuite/tests/ghc-api/annotations/T10309.stdout | 2 + testsuite/tests/ghc-api/annotations/T10312.stdout | 2 + testsuite/tests/ghc-api/annotations/T10358.stderr | 12 -- testsuite/tests/ghc-api/annotations/T10358.stdout | 2 +- testsuite/tests/ghc-api/annotations/T10399.stderr | 12 +- testsuite/tests/ghc-api/annotations/T10399.stdout | 146 ++++++++--------- testsuite/tests/ghc-api/annotations/Test10255.hs | 2 +- testsuite/tests/ghc-api/annotations/Test10278.hs | 2 +- testsuite/tests/ghc-api/annotations/Test10358.hs | 2 +- testsuite/tests/ghc-api/annotations/Test10399.hs | 3 + testsuite/tests/ghc-api/annotations/all.T | 14 +- testsuite/tests/ghc-api/annotations/boolFormula.hs | 106 +------------ .../tests/ghc-api/annotations/boolFormula.stdout | 2 + testsuite/tests/ghc-api/annotations/exampleTest.hs | 111 +------------ .../tests/ghc-api/annotations/exampleTest.stdout | 2 + testsuite/tests/ghc-api/annotations/t10255.hs | 105 +------------ testsuite/tests/ghc-api/annotations/t10268.hs | 106 +------------ testsuite/tests/ghc-api/annotations/t10269.hs | 106 +------------ testsuite/tests/ghc-api/annotations/t10278.hs | 117 +------------- testsuite/tests/ghc-api/annotations/t10280.hs | 106 +------------ testsuite/tests/ghc-api/annotations/t10307.hs | 105 +------------ testsuite/tests/ghc-api/annotations/t10309.hs | 105 +------------ testsuite/tests/ghc-api/annotations/t10312.hs | 105 +------------ testsuite/tests/ghc-api/annotations/t10354.hs | 117 +------------- testsuite/tests/ghc-api/annotations/t10357.hs | 117 +------------- testsuite/tests/ghc-api/annotations/t10358.hs | 117 +------------- testsuite/tests/ghc-api/annotations/t10396.hs | 117 +------------- testsuite/tests/ghc-api/annotations/t10399.hs | 117 +------------- 37 files changed, 269 insertions(+), 1806 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 9f7eb944e64c0e57ebbad2b795c519ed37f24bf8 From git at git.haskell.org Mon Jun 1 16:19:50 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 16:19:50 +0000 (UTC) Subject: [commit: ghc] wip/api-annots-7.10-3: ApiAnnotations : strings in warnings do not return SourceText (d06ce03) Message-ID: <20150601161950.E742E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/api-annots-7.10-3 Link : http://ghc.haskell.org/trac/ghc/changeset/d06ce0317f38d4ea9f979208a73abf691aecee06/ghc >--------------------------------------------------------------- commit d06ce0317f38d4ea9f979208a73abf691aecee06 Author: Alan Zimmerman Date: Mon Jun 1 14:16:41 2015 +0200 ApiAnnotations : strings in warnings do not return SourceText Summary: The strings used in a WARNING pragma are captured via strings :: { Located ([AddAnn],[Located FastString]) } : STRING { sL1 $1 ([],[L (gl $1) (getSTRING $1)]) } .. The STRING token has a method getSTRINGs that returns the original source text for a string. A warning of the form {-# WARNING Logic , mkSolver , mkSimpleSolver , mkSolverForLogic , solverSetParams , solverPush , solverPop , solverReset , solverGetNumScopes , solverAssertCnstr , solverAssertAndTrack , solverCheck , solverCheckAndGetModel , solverGetReasonUnknown "New Z3 API support is still incomplete and fragile: \ \you may experience segmentation faults!" #-} returns the concatenated warning string rather than the original source. This patch now deals with all remaining instances of getSTRING to bring in a SourceText for each. This updates the haddock submodule as well, for the AST change. Test Plan: ./validate Reviewers: hvr, austin, goldfire Reviewed By: austin Subscribers: bgamari, thomie, mpickering Differential Revision: https://phabricator.haskell.org/D907 GHC Trac Issues: #10313 (cherry picked from commit e6191d1cc37e98785af8b309100ea840084fa3ba) Conflicts: compiler/parser/Parser.y compiler/typecheck/TcRules.hs utils/haddock >--------------------------------------------------------------- d06ce0317f38d4ea9f979208a73abf691aecee06 compiler/basicTypes/BasicTypes.hs | 14 +++-- compiler/codeGen/StgCmmForeign.hs | 4 +- compiler/deSugar/Desugar.hs | 4 +- compiler/deSugar/DsCCall.hs | 3 +- compiler/deSugar/DsExpr.hs | 2 +- compiler/deSugar/DsForeign.hs | 15 +++-- compiler/deSugar/DsMeta.hs | 12 ++-- compiler/ghci/ByteCodeGen.hs | 4 +- compiler/hsSyn/Convert.hs | 5 +- compiler/hsSyn/HsDecls.hs | 13 +++-- compiler/hsSyn/HsExpr.hs | 13 +++-- compiler/hsSyn/HsImpExp.hs | 6 +- compiler/iface/MkIface.hs | 2 +- compiler/main/DriverMkDepend.hs | 2 +- compiler/main/GhcMake.hs | 3 +- compiler/main/HscMain.hs | 2 +- compiler/parser/Parser.y | 40 ++++++------- compiler/parser/RdrHsSyn.hs | 19 +++--- compiler/prelude/ForeignCall.hs | 38 +++++++----- compiler/prelude/TysWiredIn.hs | 22 +++---- compiler/rename/RnNames.hs | 8 +-- compiler/rename/RnSource.hs | 9 +-- compiler/stgSyn/CoreToStg.hs | 3 +- compiler/typecheck/TcForeign.hs | 8 +-- compiler/typecheck/TcRules.hs | 10 ++-- ghc/InteractiveUI.hs | 7 ++- testsuite/tests/ghc-api/annotations/.gitignore | 1 + testsuite/tests/ghc-api/annotations/Makefile | 6 ++ testsuite/tests/ghc-api/annotations/T10313.stderr | 28 +++++++++ testsuite/tests/ghc-api/annotations/T10313.stdout | 27 +++++++++ testsuite/tests/ghc-api/annotations/Test10313.hs | 38 ++++++++++++ testsuite/tests/ghc-api/annotations/all.T | 1 + .../annotations/{parseTree.hs => stringSource.hs} | 67 +++++++++++++++++----- utils/haddock | 2 +- 34 files changed, 303 insertions(+), 135 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d06ce0317f38d4ea9f979208a73abf691aecee06 From git at git.haskell.org Mon Jun 1 16:33:08 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 16:33:08 +0000 (UTC) Subject: [commit: ghc] master: Replace tabs with spaces. (931268a) Message-ID: <20150601163308.650A83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/931268a2dfea91b4114cba87bc36fc93428ed144/ghc >--------------------------------------------------------------- commit 931268a2dfea91b4114cba87bc36fc93428ed144 Author: Edward Z. Yang Date: Mon Jun 1 09:33:14 2015 -0700 Replace tabs with spaces. Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- 931268a2dfea91b4114cba87bc36fc93428ed144 docs/users_guide/ffi-chap.xml | 236 +++++++++++++++++++++--------------------- 1 file changed, 118 insertions(+), 118 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 931268a2dfea91b4114cba87bc36fc93428ed144 From git at git.haskell.org Mon Jun 1 16:46:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 16:46:16 +0000 (UTC) Subject: [commit: ghc] master: Add information about allowed foreign prim args, see #10460. (98b0b2e) Message-ID: <20150601164616.5CFDE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/98b0b2e41f2bdc66bf815ff5f3825832b2b6d34d/ghc >--------------------------------------------------------------- commit 98b0b2e41f2bdc66bf815ff5f3825832b2b6d34d Author: Edward Z. Yang Date: Mon Jun 1 09:46:20 2015 -0700 Add information about allowed foreign prim args, see #10460. Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- 98b0b2e41f2bdc66bf815ff5f3825832b2b6d34d docs/users_guide/ffi-chap.xml | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/docs/users_guide/ffi-chap.xml b/docs/users_guide/ffi-chap.xml index acd6f72..0f9cfba 100644 --- a/docs/users_guide/ffi-chap.xml +++ b/docs/users_guide/ffi-chap.xml @@ -73,7 +73,13 @@ OK: foreign import prim "foo" foo :: ByteArray# -> (# Int#, Int# #) This is used to import functions written in Cmm code that follow an - internal GHC calling convention. This feature is not intended for + internal GHC calling convention. The arguments and results must + be unboxed types, except that an argument may be of type + Any (by way of unsafeCoerce#) + and the result type is allowed to be an unboxed tuple + + + This feature is not intended for use outside of the core libraries that come with GHC. For more details see the GHC developer wiki. From git at git.haskell.org Mon Jun 1 17:06:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 17:06:36 +0000 (UTC) Subject: [commit: ghc] master: Typofix: missing period. (#10460) (e5be846) Message-ID: <20150601170636.DFC7C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e5be846ba929da54472c03a7c3b05fdd1e483c01/ghc >--------------------------------------------------------------- commit e5be846ba929da54472c03a7c3b05fdd1e483c01 Author: Edward Z. Yang Date: Mon Jun 1 10:05:46 2015 -0700 Typofix: missing period. (#10460) Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- e5be846ba929da54472c03a7c3b05fdd1e483c01 docs/users_guide/ffi-chap.xml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/docs/users_guide/ffi-chap.xml b/docs/users_guide/ffi-chap.xml index 0f9cfba..a5ab9e7 100644 --- a/docs/users_guide/ffi-chap.xml +++ b/docs/users_guide/ffi-chap.xml @@ -76,7 +76,7 @@ OK: internal GHC calling convention. The arguments and results must be unboxed types, except that an argument may be of type Any (by way of unsafeCoerce#) - and the result type is allowed to be an unboxed tuple + and the result type is allowed to be an unboxed tuple. This feature is not intended for From git at git.haskell.org Mon Jun 1 17:57:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 17:57:37 +0000 (UTC) Subject: [commit: ghc] master: Add (failing) test case for #7672. (a27fb46) Message-ID: <20150601175737.6C0B03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a27fb46ff1ea46a45e0084c3db92a24475e3bab5/ghc >--------------------------------------------------------------- commit a27fb46ff1ea46a45e0084c3db92a24475e3bab5 Author: Edward Z. Yang Date: Mon Jun 1 10:39:48 2015 -0700 Add (failing) test case for #7672. Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- a27fb46ff1ea46a45e0084c3db92a24475e3bab5 testsuite/tests/rename/should_compile/T7672.hs | 3 +++ testsuite/tests/rename/should_compile/T7672.hs-boot | 2 ++ testsuite/tests/rename/should_compile/T7672a.hs | 2 ++ testsuite/tests/rename/should_compile/all.T | 1 + 4 files changed, 8 insertions(+) diff --git a/testsuite/tests/rename/should_compile/T7672.hs b/testsuite/tests/rename/should_compile/T7672.hs new file mode 100644 index 0000000..405c853 --- /dev/null +++ b/testsuite/tests/rename/should_compile/T7672.hs @@ -0,0 +1,3 @@ +module T7672 where +import qualified T7672a +data T = S B.T diff --git a/testsuite/tests/rename/should_compile/T7672.hs-boot b/testsuite/tests/rename/should_compile/T7672.hs-boot new file mode 100644 index 0000000..90b4f16 --- /dev/null +++ b/testsuite/tests/rename/should_compile/T7672.hs-boot @@ -0,0 +1,2 @@ +module T7672 where +data T diff --git a/testsuite/tests/rename/should_compile/T7672a.hs b/testsuite/tests/rename/should_compile/T7672a.hs new file mode 100644 index 0000000..361c770 --- /dev/null +++ b/testsuite/tests/rename/should_compile/T7672a.hs @@ -0,0 +1,2 @@ +module T7672a(Decl.T) where +import {-# SOURCE #-} qualified T7672 as Decl diff --git a/testsuite/tests/rename/should_compile/all.T b/testsuite/tests/rename/should_compile/all.T index 0747f98..fc5d125 100644 --- a/testsuite/tests/rename/should_compile/all.T +++ b/testsuite/tests/rename/should_compile/all.T @@ -212,6 +212,7 @@ test('T7167', normal, compile, ['']) test('T7336', expect_broken(7336), compile, ['-Wall']) test('T2435', normal, multimod_compile, ['T2435','-v0']) +test('T7672', expect_broken(7672), multimod_compile, ['T7672','']) test('T7963', [extra_clean(['T7963a.hi', 'T7963a.o', 'T7963.imports'])], From git at git.haskell.org Mon Jun 1 18:39:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 18:39:34 +0000 (UTC) Subject: [commit: ghc] master: Newline after type of allocate(). (f82e866) Message-ID: <20150601183934.0EB343A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f82e866504259c674d6fb3f66e67ae943a688b3f/ghc >--------------------------------------------------------------- commit f82e866504259c674d6fb3f66e67ae943a688b3f Author: Edward Z. Yang Date: Mon Jun 1 11:37:01 2015 -0700 Newline after type of allocate(). Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- f82e866504259c674d6fb3f66e67ae943a688b3f rts/sm/Storage.c | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/rts/sm/Storage.c b/rts/sm/Storage.c index 50926b7..85884fa 100644 --- a/rts/sm/Storage.c +++ b/rts/sm/Storage.c @@ -738,7 +738,8 @@ move_STACK (StgStack *src, StgStack *dest) that operation fails, then the whole process will be killed. -------------------------------------------------------------------------- */ -StgPtr allocate (Capability *cap, W_ n) +StgPtr +allocate (Capability *cap, W_ n) { bdescr *bd; StgPtr p; From git at git.haskell.org Mon Jun 1 19:53:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 19:53:54 +0000 (UTC) Subject: [commit: ghc] branch 'wip/run-api-tests-alone' created Message-ID: <20150601195354.6DA7F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/run-api-tests-alone Referencing: 1828eb65b85e1a0bd4c606771cd097d593fb02c0 From git at git.haskell.org Mon Jun 1 19:53:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 19:53:57 +0000 (UTC) Subject: [commit: ghc] wip/run-api-tests-alone: testsuite: Run ghc api tests alone (1828eb6) Message-ID: <20150601195357.444BC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/run-api-tests-alone Link : http://ghc.haskell.org/trac/ghc/changeset/1828eb65b85e1a0bd4c606771cd097d593fb02c0/ghc >--------------------------------------------------------------- commit 1828eb65b85e1a0bd4c606771cd097d593fb02c0 Author: Joachim Breitner Date: Mon Jun 1 21:53:32 2015 +0200 testsuite: Run ghc api tests alone to reduce the risk of running out of memory. >--------------------------------------------------------------- 1828eb65b85e1a0bd4c606771cd097d593fb02c0 testsuite/tests/ghc-api/T4891/all.T | 2 ++ testsuite/tests/ghc-api/T7478/all.T | 2 ++ testsuite/tests/ghc-api/all.T | 2 ++ testsuite/tests/ghc-api/annotations-literals/all.T | 2 ++ testsuite/tests/ghc-api/annotations/all.T | 2 ++ testsuite/tests/ghc-api/apirecomp001/all.T | 2 ++ testsuite/tests/ghc-api/dynCompileExpr/all.T | 2 ++ testsuite/tests/ghc-api/landmines/all.T | 2 ++ testsuite/tests/ghc-api/show-srcspan/all.T | 2 ++ 9 files changed, 18 insertions(+) diff --git a/testsuite/tests/ghc-api/T4891/all.T b/testsuite/tests/ghc-api/T4891/all.T index b9c08c3..2e2bcfc 100644 --- a/testsuite/tests/ghc-api/T4891/all.T +++ b/testsuite/tests/ghc-api/T4891/all.T @@ -1,3 +1,5 @@ +setTestOpts(alone) + test('T4891', extra_clean(['X.hi', 'X.o']), run_command, ['$MAKE -s --no-print-directory T4891']) diff --git a/testsuite/tests/ghc-api/T7478/all.T b/testsuite/tests/ghc-api/T7478/all.T index b3a69a8..129136a 100644 --- a/testsuite/tests/ghc-api/T7478/all.T +++ b/testsuite/tests/ghc-api/T7478/all.T @@ -1,3 +1,5 @@ +setTestOpts(alone) + test('T7478', [ unless(have_dynamic(),skip) , extra_clean(['A','A.exe','B.o','B.hi','C.o','C.hi']) diff --git a/testsuite/tests/ghc-api/all.T b/testsuite/tests/ghc-api/all.T index 11e8c42..6143364 100644 --- a/testsuite/tests/ghc-api/all.T +++ b/testsuite/tests/ghc-api/all.T @@ -1,3 +1,5 @@ +setTestOpts(alone) + test('ghcApi', normal, compile_and_run, ['-package ghc']) test('T6145', normal, run_command, diff --git a/testsuite/tests/ghc-api/annotations-literals/all.T b/testsuite/tests/ghc-api/annotations-literals/all.T index 999c5a4..33892f4 100644 --- a/testsuite/tests/ghc-api/annotations-literals/all.T +++ b/testsuite/tests/ghc-api/annotations-literals/all.T @@ -1,2 +1,4 @@ +setTestOpts(alone) + test('literals', normal, run_command, ['$MAKE -s --no-print-directory literals']) test('parsed', normal, run_command, ['$MAKE -s --no-print-directory parsed']) diff --git a/testsuite/tests/ghc-api/annotations/all.T b/testsuite/tests/ghc-api/annotations/all.T index f6cb955..cb500dc 100644 --- a/testsuite/tests/ghc-api/annotations/all.T +++ b/testsuite/tests/ghc-api/annotations/all.T @@ -1,3 +1,5 @@ +setTestOpts(alone) + test('annotations', normal, run_command, ['$MAKE -s --no-print-directory annotations']) test('parseTree', normal, run_command, ['$MAKE -s --no-print-directory parseTree']) test('comments', normal, run_command, ['$MAKE -s --no-print-directory comments']) diff --git a/testsuite/tests/ghc-api/apirecomp001/all.T b/testsuite/tests/ghc-api/apirecomp001/all.T index f58352a..7b3826c 100644 --- a/testsuite/tests/ghc-api/apirecomp001/all.T +++ b/testsuite/tests/ghc-api/apirecomp001/all.T @@ -1,3 +1,5 @@ +setTestOpts(alone) + test('apirecomp001', normal, run_command, diff --git a/testsuite/tests/ghc-api/dynCompileExpr/all.T b/testsuite/tests/ghc-api/dynCompileExpr/all.T index c6034ea..73bcb5a 100644 --- a/testsuite/tests/ghc-api/dynCompileExpr/all.T +++ b/testsuite/tests/ghc-api/dynCompileExpr/all.T @@ -1,3 +1,5 @@ +setTestOpts(alone) + test('dynCompileExpr', [ extra_run_opts('"' + config.libdir + '"'), when(opsys('mingw32'), expect_broken_for(5987, ['dyn'])), diff --git a/testsuite/tests/ghc-api/landmines/all.T b/testsuite/tests/ghc-api/landmines/all.T index b03a97f..23105e2 100644 --- a/testsuite/tests/ghc-api/landmines/all.T +++ b/testsuite/tests/ghc-api/landmines/all.T @@ -1,2 +1,4 @@ +setTestOpts(alone) + test('landmines', normal, run_command, ['$MAKE -s --no-print-directory landmines']) diff --git a/testsuite/tests/ghc-api/show-srcspan/all.T b/testsuite/tests/ghc-api/show-srcspan/all.T index fbb8d04..85aeb93 100644 --- a/testsuite/tests/ghc-api/show-srcspan/all.T +++ b/testsuite/tests/ghc-api/show-srcspan/all.T @@ -1 +1,3 @@ +setTestOpts(alone) + test('showsrcspan', normal, run_command, ['$MAKE -s --no-print-directory showsrcspan']) From git at git.haskell.org Mon Jun 1 20:24:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 20:24:51 +0000 (UTC) Subject: [commit: ghc] branch 'wip/high_memory_usage' created Message-ID: <20150601202451.90E4D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/high_memory_usage Referencing: 9a919e82d9f56c5a150bd058767705d164b9c0d7 From git at git.haskell.org Mon Jun 1 20:24:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 20:24:54 +0000 (UTC) Subject: [commit: ghc] wip/high_memory_usage: Limit number of concurrent tests (9a919e8) Message-ID: <20150601202454.51ACC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/high_memory_usage Link : http://ghc.haskell.org/trac/ghc/changeset/9a919e82d9f56c5a150bd058767705d164b9c0d7/ghc >--------------------------------------------------------------- commit 9a919e82d9f56c5a150bd058767705d164b9c0d7 Author: Alan Zimmerman Date: Mon Jun 1 22:24:29 2015 +0200 Limit number of concurrent tests >--------------------------------------------------------------- 9a919e82d9f56c5a150bd058767705d164b9c0d7 testsuite/tests/ghc-api/annotations/all.T | 40 +++++++++++++++---------------- 1 file changed, 20 insertions(+), 20 deletions(-) diff --git a/testsuite/tests/ghc-api/annotations/all.T b/testsuite/tests/ghc-api/annotations/all.T index f6cb955..61551e8 100644 --- a/testsuite/tests/ghc-api/annotations/all.T +++ b/testsuite/tests/ghc-api/annotations/all.T @@ -1,20 +1,20 @@ -test('annotations', normal, run_command, ['$MAKE -s --no-print-directory annotations']) -test('parseTree', normal, run_command, ['$MAKE -s --no-print-directory parseTree']) -test('comments', normal, run_command, ['$MAKE -s --no-print-directory comments']) -test('exampleTest', normal, run_command, ['$MAKE -s --no-print-directory exampleTest']) -test('listcomps', normal, run_command, ['$MAKE -s --no-print-directory listcomps']) -test('T10255', normal, run_command, ['$MAKE -s --no-print-directory T10255']) -test('T10268', normal, run_command, ['$MAKE -s --no-print-directory T10268']) -test('T10269', normal, run_command, ['$MAKE -s --no-print-directory T10269']) -test('T10280', normal, run_command, ['$MAKE -s --no-print-directory T10280']) -test('T10312', normal, run_command, ['$MAKE -s --no-print-directory T10312']) -test('T10307', normal, run_command, ['$MAKE -s --no-print-directory T10307']) -test('T10309', normal, run_command, ['$MAKE -s --no-print-directory T10309']) -test('boolFormula', normal, run_command, ['$MAKE -s --no-print-directory boolFormula']) -test('T10357', normal, run_command, ['$MAKE -s --no-print-directory T10357']) -test('T10358', normal, run_command, ['$MAKE -s --no-print-directory T10358']) -test('T10278', normal, run_command, ['$MAKE -s --no-print-directory T10278']) -test('T10354', normal, run_command, ['$MAKE -s --no-print-directory T10354']) -test('T10396', normal, run_command, ['$MAKE -s --no-print-directory T10396']) -test('T10399', normal, run_command, ['$MAKE -s --no-print-directory T10399']) -test('T10313', normal, run_command, ['$MAKE -s --no-print-directory T10313']) +test('annotations', [high_memory_usage], run_command, ['$MAKE -s --no-print-directory annotations']) +test('parseTree', [high_memory_usage], run_command, ['$MAKE -s --no-print-directory parseTree']) +test('comments', [high_memory_usage], run_command, ['$MAKE -s --no-print-directory comments']) +test('exampleTest', [high_memory_usage], run_command, ['$MAKE -s --no-print-directory exampleTest']) +test('listcomps', [high_memory_usage], run_command, ['$MAKE -s --no-print-directory listcomps']) +test('T10255', [high_memory_usage], run_command, ['$MAKE -s --no-print-directory T10255']) +test('T10268', [high_memory_usage], run_command, ['$MAKE -s --no-print-directory T10268']) +test('T10269', [high_memory_usage], run_command, ['$MAKE -s --no-print-directory T10269']) +test('T10280', [high_memory_usage], run_command, ['$MAKE -s --no-print-directory T10280']) +test('T10312', [high_memory_usage], run_command, ['$MAKE -s --no-print-directory T10312']) +test('T10307', [high_memory_usage], run_command, ['$MAKE -s --no-print-directory T10307']) +test('T10309', [high_memory_usage], run_command, ['$MAKE -s --no-print-directory T10309']) +test('boolFormula', [high_memory_usage], run_command, ['$MAKE -s --no-print-directory boolFormula']) +test('T10357', [high_memory_usage], run_command, ['$MAKE -s --no-print-directory T10357']) +test('T10358', [high_memory_usage], run_command, ['$MAKE -s --no-print-directory T10358']) +test('T10278', [high_memory_usage], run_command, ['$MAKE -s --no-print-directory T10278']) +test('T10354', [high_memory_usage], run_command, ['$MAKE -s --no-print-directory T10354']) +test('T10396', [high_memory_usage], run_command, ['$MAKE -s --no-print-directory T10396']) +test('T10399', [high_memory_usage], run_command, ['$MAKE -s --no-print-directory T10399']) +test('T10313', [high_memory_usage], run_command, ['$MAKE -s --no-print-directory T10313']) From git at git.haskell.org Mon Jun 1 20:34:02 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 20:34:02 +0000 (UTC) Subject: [commit: ghc] master: Don't call DEAD_WEAK finalizer again on shutdown (#7170) (dfdc50d) Message-ID: <20150601203402.538593A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/dfdc50d666498c5a1118557d67209fe067c61cc1/ghc >--------------------------------------------------------------- commit dfdc50d666498c5a1118557d67209fe067c61cc1 Author: Simon Marlow Date: Mon Jun 1 21:34:02 2015 +0100 Don't call DEAD_WEAK finalizer again on shutdown (#7170) Summary: There's a race condition like this: # A foreign pointer gets promoted to the last generation # It has its finalizer called manually # We start shutting down the runtime in `hs_exit_` from the main thread # A minor GC starts running (`scheduleDoGC`) on one of the threads # The minor GC notices that we're in `SCHED_INTERRUPTING` state and advances to `SCHED_SHUTTING_DOWN` # The main thread tries to do major GC (with `scheduleDoGC`), but it exits early because we're in `SCHED_SHUTTING_DOWN` state # We end up with a `DEAD_WEAK` left on the list of weak pointers of the last generation, because it relied on major GC removing it from that list This change: * Ignores DEAD_WEAK finalizers when shutting down * Makes the major GC on shutdown more likely * Fixes a bogus assert Test Plan: before this diff https://ghc.haskell.org/trac/ghc/ticket/7170#comment:5 reproduced and after it doesn't Reviewers: ezyang, austin, simonmar Reviewed By: simonmar Subscribers: bgamari, thomie Differential Revision: https://phabricator.haskell.org/D921 GHC Trac Issues: #7170 >--------------------------------------------------------------- dfdc50d666498c5a1118557d67209fe067c61cc1 rts/Schedule.c | 7 +++++-- rts/Weak.c | 11 ++++++++++- rts/sm/MarkWeak.c | 3 ++- 3 files changed, 17 insertions(+), 4 deletions(-) diff --git a/rts/Schedule.c b/rts/Schedule.c index 957aa4b..f81fc0e 100644 --- a/rts/Schedule.c +++ b/rts/Schedule.c @@ -251,7 +251,7 @@ schedule (Capability *initialCapability, Task *task) case SCHED_INTERRUPTING: debugTrace(DEBUG_sched, "SCHED_INTERRUPTING"); /* scheduleDoGC() deletes all the threads */ - scheduleDoGC(&cap,task,rtsFalse); + scheduleDoGC(&cap,task,rtsTrue); // after scheduleDoGC(), we must be shutting down. Either some // other Capability did the final GC, or we did it above, @@ -1458,6 +1458,7 @@ scheduleDoGC (Capability **pcap, Task *task USED_IF_THREADS, Capability *cap = *pcap; rtsBool heap_census; nat collect_gen; + rtsBool major_gc; #ifdef THREADED_RTS nat gc_type; nat i, sync; @@ -1476,6 +1477,7 @@ scheduleDoGC (Capability **pcap, Task *task USED_IF_THREADS, // Figure out which generation we are collecting, so that we can // decide whether this is a parallel GC or not. collect_gen = calcNeeded(force_major || heap_census, NULL); + major_gc = (collect_gen == RtsFlags.GcFlags.generations-1); #ifdef THREADED_RTS if (sched_state < SCHED_INTERRUPTING @@ -1618,8 +1620,9 @@ delete_threads_and_gc: * We now have all the capabilities; if we're in an interrupting * state, then we should take the opportunity to delete all the * threads in the system. + * Checking for major_gc ensures that the last GC is major. */ - if (sched_state == SCHED_INTERRUPTING) { + if (sched_state == SCHED_INTERRUPTING && major_gc) { deleteAllThreads(cap); #if defined(THREADED_RTS) // Discard all the sparks from every Capability. Why? diff --git a/rts/Weak.c b/rts/Weak.c index f8faa4e..92f1bdb 100644 --- a/rts/Weak.c +++ b/rts/Weak.c @@ -43,7 +43,16 @@ runAllCFinalizers(StgWeak *list) } for (w = list; w; w = w->link) { - runCFinalizers((StgCFinalizerList *)w->cfinalizers); + // We need to filter out DEAD_WEAK objects, because it's not guaranteed + // that the list will not have them when shutting down. + // They only get filtered out during GC for the generation they + // belong to. + // If there's no major GC between the time that the finalizer for the + // object from the oldest generation is manually called and shutdown + // we end up running the same finalizer twice. See #7170. + if (w->header.info != &stg_DEAD_WEAK_info) { + runCFinalizers((StgCFinalizerList *)w->cfinalizers); + } } if (task != NULL) { diff --git a/rts/sm/MarkWeak.c b/rts/sm/MarkWeak.c index c5a107c..60ac53f 100644 --- a/rts/sm/MarkWeak.c +++ b/rts/sm/MarkWeak.c @@ -348,7 +348,8 @@ static void checkWeakPtrSanity(StgWeak *hd, StgWeak *tl) { StgWeak *w, *prev; for (w = hd; w != NULL; prev = w, w = w->link) { - ASSERT(INFO_PTR_TO_STRUCT(UNTAG_CLOSURE((StgClosure*)w)->header.info)->type == WEAK); + ASSERT(INFO_PTR_TO_STRUCT(UNTAG_CLOSURE((StgClosure*)w)->header.info)->type == WEAK + || UNTAG_CLOSURE((StgClosure*)w)->header.info == &stg_DEAD_WEAK_info); checkClosure((StgClosure*)w); } if (tl != NULL) { From git at git.haskell.org Mon Jun 1 21:09:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 21:09:25 +0000 (UTC) Subject: [commit: ghc] branch 'wip/run-api-tests-alone' deleted Message-ID: <20150601210925.ED5F93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/run-api-tests-alone From git at git.haskell.org Mon Jun 1 22:48:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 1 Jun 2015 22:48:36 +0000 (UTC) Subject: [commit: ghc] master: Re-center perf numbers for T5631 (34dcf8a) Message-ID: <20150601224836.793323A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/34dcf8a0939c813a861bed9fa01c05ec7fe7decd/ghc >--------------------------------------------------------------- commit 34dcf8a0939c813a861bed9fa01c05ec7fe7decd Author: Herbert Valerio Riedel Date: Mon Jun 1 17:48:29 2015 -0500 Re-center perf numbers for T5631 7dd0ea7428379df848e3d13528921b39b7bf5b95 seems to have tipped this one over, although 7dd0ea74283 itself had only a minimal impact on my local system. Locally, I measured right before 7dd0ea74283: Expected T5631(normal) bytes allocated: 776121120 +/-5% Actual T5631(normal) bytes allocated: 811973144 Deviation T5631(normal) bytes allocated: 4.6 % and at 7dd0ea74283: Expected T5631(normal) bytes allocated: 776121120 +/-5% Actual T5631(normal) bytes allocated: 812288344 Deviation T5631(normal) bytes allocated: 4.7 % Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D936 >--------------------------------------------------------------- 34dcf8a0939c813a861bed9fa01c05ec7fe7decd 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 43f0b23..ea7e293 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -361,12 +361,13 @@ test('T5631', # expected value: 392904228 (x86/Linux) # 2014-04-04: 346389856 (x86 Windows, 64 bit machine) # 2014-12-01: 390199244 (Windows laptop) - (wordsize(64), 776121120, 5)]), + (wordsize(64), 812288344, 5)]), # expected value: 774595008 (amd64/Linux): # expected value: 735486328 (amd64/Linux) 2012/12/12: # expected value: 690742040 (amd64/Linux) Call Arity improvements # 2014-09-09: 739704712 (amd64/Linux) AMP changes # 2014-11-04: 776121120 (amd64/Linux) new-flatten-skolems + # 2015-06-01: 812288344 (amd64/Linux) unknown cause only_ways(['normal']) ], compile, From git at git.haskell.org Tue Jun 2 09:34:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Jun 2015 09:34:09 +0000 (UTC) Subject: [commit: ghc] master: White space only (2f0011a) Message-ID: <20150602093409.440DC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2f0011aca137055f139bed484302679c10238d55/ghc >--------------------------------------------------------------- commit 2f0011aca137055f139bed484302679c10238d55 Author: Simon Peyton Jones Date: Sun May 31 00:06:13 2015 +0100 White space only >--------------------------------------------------------------- 2f0011aca137055f139bed484302679c10238d55 compiler/main/InteractiveEval.hs | 1 - compiler/main/TidyPgm.hs | 2 +- 2 files changed, 1 insertion(+), 2 deletions(-) diff --git a/compiler/main/InteractiveEval.hs b/compiler/main/InteractiveEval.hs index 5458368..59224e8 100644 --- a/compiler/main/InteractiveEval.hs +++ b/compiler/main/InteractiveEval.hs @@ -1104,4 +1104,3 @@ reconstructType hsc_env bound id = do mkRuntimeUnkTyVar :: Name -> Kind -> TyVar mkRuntimeUnkTyVar name kind = mkTcTyVar name kind RuntimeUnk #endif /* GHCI */ - diff --git a/compiler/main/TidyPgm.hs b/compiler/main/TidyPgm.hs index e9dd8d1..91aaaee 100644 --- a/compiler/main/TidyPgm.hs +++ b/compiler/main/TidyPgm.hs @@ -144,9 +144,9 @@ mkBootModDetailsTc hsc_env ; showPassIO dflags CoreTidy ; let { insts' = map (tidyClsInstDFun globaliseAndTidyId) insts + ; pat_syns' = map (tidyPatSynIds globaliseAndTidyId) pat_syns ; type_env1 = mkBootTypeEnv (availsToNameSet exports) (typeEnvIds type_env) tcs fam_insts - ; pat_syns' = map (tidyPatSynIds globaliseAndTidyId) pat_syns ; type_env2 = extendTypeEnvWithPatSyns pat_syns' type_env1 ; dfun_ids = map instanceDFunId insts' ; type_env' = extendTypeEnvWithIds type_env2 dfun_ids From git at git.haskell.org Tue Jun 2 09:34:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Jun 2015 09:34:11 +0000 (UTC) Subject: [commit: ghc] master: Treat pattern-synonym binders more consistently (11d8f84) Message-ID: <20150602093411.F0E183A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/11d8f84fd3237c3821c8f826716fc4c9adfccb8c/ghc >--------------------------------------------------------------- commit 11d8f84fd3237c3821c8f826716fc4c9adfccb8c Author: Simon Peyton Jones Date: Mon Jun 1 23:42:10 2015 +0100 Treat pattern-synonym binders more consistently Pattern-synonyms are in value declarations, but were being bound by getLocalNonValBinders. This seemed odd, and indeed staightening it out allowed me to remove a field from TopSigCtxt. The main changes are in RnSource.rnSrcDecls. Nice. >--------------------------------------------------------------- 11d8f84fd3237c3821c8f826716fc4c9adfccb8c compiler/hsSyn/HsUtils.hs | 5 +++-- compiler/rename/RnBinds.hs | 4 ++-- compiler/rename/RnEnv.hs | 38 +++++++++++++++----------------------- compiler/rename/RnNames.hs | 10 +++------- compiler/rename/RnSource.hs | 40 +++++++++++++++++++++------------------- compiler/typecheck/TcDeriv.hs | 2 +- 6 files changed, 45 insertions(+), 54 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 11d8f84fd3237c3821c8f826716fc4c9adfccb8c From git at git.haskell.org Tue Jun 2 09:34:14 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Jun 2015 09:34:14 +0000 (UTC) Subject: [commit: ghc] master: Mark sigof02 tests as expect_broken (90fde52) Message-ID: <20150602093414.9D5243A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/90fde5220c80bf02d7c6e1d6b4cfe631f068aa0b/ghc >--------------------------------------------------------------- commit 90fde5220c80bf02d7c6e1d6b4cfe631f068aa0b Author: Simon Peyton Jones Date: Tue Jun 2 00:41:54 2015 +0100 Mark sigof02 tests as expect_broken Consequence of the GlobalRdrEnv refactoring; see Trac #10472 >--------------------------------------------------------------- 90fde5220c80bf02d7c6e1d6b4cfe631f068aa0b testsuite/tests/driver/sigof02/all.T | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/testsuite/tests/driver/sigof02/all.T b/testsuite/tests/driver/sigof02/all.T index 62f50a6..9cb1ea5 100644 --- a/testsuite/tests/driver/sigof02/all.T +++ b/testsuite/tests/driver/sigof02/all.T @@ -4,7 +4,7 @@ test('sigof02', ['$MAKE -s --no-print-directory sigof02']) test('sigof02t', - [ clean_cmd('rm -rf tmp_sigof02t') ], + [ expect_broken(10472), clean_cmd('rm -rf tmp_sigof02t') ], run_command, ['$MAKE -s --no-print-directory sigof02t']) @@ -14,7 +14,7 @@ test('sigof02m', ['$MAKE -s --no-print-directory sigof02m']) test('sigof02mt', - [ clean_cmd('rm -rf tmp_sigof02mt') ], + [ expect_broken(10472), clean_cmd('rm -rf tmp_sigof02mt') ], run_command, ['$MAKE -s --no-print-directory sigof02mt']) @@ -24,7 +24,7 @@ test('sigof02d', ['$MAKE -s --no-print-directory sigof02d']) test('sigof02dt', - [ clean_cmd('rm -rf tmp_sigof02dt') ], + [ expect_broken(10472), clean_cmd('rm -rf tmp_sigof02dt') ], run_command, ['$MAKE -s --no-print-directory sigof02dt']) @@ -35,7 +35,7 @@ test('sigof02dm', ['$MAKE -s --no-print-directory sigof02dm']) test('sigof02dmt', - [ clean_cmd('rm -rf tmp_sigof02dmt') ], + [ expect_broken(10472), clean_cmd('rm -rf tmp_sigof02dmt') ], run_command, ['$MAKE -s --no-print-directory sigof02dmt']) From git at git.haskell.org Tue Jun 2 09:34:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Jun 2015 09:34:17 +0000 (UTC) Subject: [commit: ghc] master: Refactor the GlobalRdrEnv, fixing #7672 (9b73cb1) Message-ID: <20150602093417.698D03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9b73cb16485f331d9dc1f37826c6d503e24a5b0b/ghc >--------------------------------------------------------------- commit 9b73cb16485f331d9dc1f37826c6d503e24a5b0b Author: Simon Peyton Jones Date: Tue Jun 2 00:02:03 2015 +0100 Refactor the GlobalRdrEnv, fixing #7672 This patch started innocently enough, by deleting a single call from rnImportDecl, namely let gbl_env = mkGlobalRdrEnv (filterOut from_this_mod gres) The 'filterOut' makes no sense, and was the cause of #7672. But that little loose end led to into a twisty maze of little passages, all alike, which has taken me an unreasonably long time to straighten out. Happily, I think the result is really much better. In particular: * INVARIANT 1 of the GlobalRdrEnv type was simply not true: we had multiple GlobalRdrElts in a list with the same gre_name field. This kludgily implmented one form of shadowing. * Meanwhile, extendGlobalRdrEnvRn implemented a second form of shadowing, by deleting stuff from the GlobalRdrEnv. * In turn, much of this shadowing stuff depended on the Names of the Ids bound in the GHCi InteractiveContext being Internal names, even though the TyCons and suchlike all had External Names. Very confusing. So I have made the following changes * I re-established INVARIANT 1 of GlobalRdrEnv. As a result some strange code in RdrName.pickGREs goes away. * RnNames.extendGlobalRdrEnvRn now makes one call to deal with shadowing, where necessary, and another to extend the environment. It deals separately with duplicate bindings. The very complicated RdrName.extendGlobalRdrEnv becomes much simpler; we need to export the shadowing function, now called RdrName.shadowNames; and we can nuke RdrName.findLocalDupsRdrEnv altogether. RdrName Note [GlobalRdrEnv shadowing] summarises the shadowing story * The Names of the Ids bound in the GHCi interactive context are now all External. See Note [Interactively-bound Ids in GHCi] in HscTypes. * Names for Ids created by the debugger are now made by IfaceEnv.newInteractiveBinder. This fixes a lurking bug which was that the debugger was using mkNewUniqueSupply 'I' to make uniques, which does NOT guarantee a fresh supply of uniques on successive calls. * Note [Template Haskell ambiguity] in RnEnv shows that one TH-related error is reported lazily (on occurrences) when it might be better reported when extending the environment. In some (but not all) cases this was done before; but now it's uniformly at occurrences. In some ways it'd be better to report when extending the environment, but it's a tiresome test and the error is rare, so I'm leaving it at the lookup site for now, with the above Note. * A small thing: RnNames.greAvail becomes RdrName.availFromGRE, where it joins the dual RdrName.gresFromAvail. >--------------------------------------------------------------- 9b73cb16485f331d9dc1f37826c6d503e24a5b0b compiler/basicTypes/RdrName.hs | 206 ++++++++++----------- compiler/ghci/Debugger.hs | 29 ++- compiler/iface/IfaceEnv.hs | 62 ++++--- compiler/main/HscTypes.hs | 44 +++-- compiler/main/InteractiveEval.hs | 71 ++++--- compiler/rename/RnEnv.hs | 144 ++++++++------ compiler/rename/RnNames.hs | 118 ++++++------ compiler/typecheck/TcEnv.hs | 69 +------ compiler/typecheck/TcRnDriver.hs | 100 +++++++--- .../tests/ghci.debugger/scripts/break027.stdout | 8 +- testsuite/tests/ghci/scripts/T10248.stderr | 10 +- testsuite/tests/ghci/scripts/T5564.stderr | 7 +- testsuite/tests/module/mod110.stderr | 6 +- testsuite/tests/module/mod151.stderr | 6 +- testsuite/tests/module/mod152.stderr | 13 +- testsuite/tests/module/mod153.stderr | 6 +- testsuite/tests/rename/should_compile/T1972.stderr | 8 +- testsuite/tests/rename/should_fail/T5533.stderr | 4 +- testsuite/tests/rename/should_fail/T7906.stderr | 4 +- testsuite/tests/rename/should_fail/rn_dup.stderr | 20 +- .../tests/rename/should_fail/rnfail044.stderr | 6 +- testsuite/tests/th/T7241.stderr | 10 +- testsuite/tests/th/T8932.stderr | 8 +- .../tests/typecheck/should_fail/tcfail037.stderr | 7 +- 24 files changed, 489 insertions(+), 477 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 9b73cb16485f331d9dc1f37826c6d503e24a5b0b From git at git.haskell.org Tue Jun 2 09:34:20 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Jun 2015 09:34:20 +0000 (UTC) Subject: [commit: ghc] master: Re-do superclass solving (again); fixes #10423 (1189196) Message-ID: <20150602093420.2F3D33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1189196ce7f064af408c9d16874a4c0b78f3a006/ghc >--------------------------------------------------------------- commit 1189196ce7f064af408c9d16874a4c0b78f3a006 Author: Simon Peyton Jones Date: Tue Jun 2 00:33:14 2015 +0100 Re-do superclass solving (again); fixes #10423 TcInstDcls.tcSuperClasses was getting increasingly baroque as a succession of tickets (#10423 being the latest) pointed out that my cunning plan was not so cunning. The big issue is how to restrict the evidence that we generate for superclass constraints in an instance declaration to avoid superclass loops. See Note [Recursive superclasses] in TcInstDcls which explains the plan. The question is how to implement the plan. The new implementation is much neater, and is described in Note [Solving superclass constraints] in TcInstDcls. >--------------------------------------------------------------- 1189196ce7f064af408c9d16874a4c0b78f3a006 compiler/typecheck/TcCanonical.hs | 12 ++- compiler/typecheck/TcInstDcls.hs | 156 ++++++++++---------------------------- compiler/typecheck/TcInteract.hs | 117 ++++++++++++++++++++-------- compiler/typecheck/TcRnTypes.hs | 15 +++- compiler/typecheck/TcSimplify.hs | 4 +- compiler/typecheck/TcType.hs | 81 +++++++++++++++++++- compiler/typecheck/TcValidity.hs | 79 +------------------ 7 files changed, 233 insertions(+), 231 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1189196ce7f064af408c9d16874a4c0b78f3a006 From git at git.haskell.org Tue Jun 2 09:34:22 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Jun 2015 09:34:22 +0000 (UTC) Subject: [commit: ghc] master: Improve constraint tuples (Trac #10451) (b095c97) Message-ID: <20150602093422.C514A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b095c97d6e8e5841c28464eb5db67d3c1ca055b8/ghc >--------------------------------------------------------------- commit b095c97d6e8e5841c28464eb5db67d3c1ca055b8 Author: Simon Peyton Jones Date: Tue Jun 2 00:40:44 2015 +0100 Improve constraint tuples (Trac #10451) * Increase max constraint tuple size to 16 * Produce a civilised error message if the max size is exceeded >--------------------------------------------------------------- b095c97d6e8e5841c28464eb5db67d3c1ca055b8 compiler/main/Constants.hs | 2 +- compiler/typecheck/TcHsType.hs | 21 ++++++++++++++++----- 2 files changed, 17 insertions(+), 6 deletions(-) diff --git a/compiler/main/Constants.hs b/compiler/main/Constants.hs index 22bd4e6..229e007 100644 --- a/compiler/main/Constants.hs +++ b/compiler/main/Constants.hs @@ -18,7 +18,7 @@ mAX_TUPLE_SIZE = 62 -- Should really match the number -- of decls in Data.Tuple mAX_CTUPLE_SIZE :: Int -- Constraint tuples -mAX_CTUPLE_SIZE = 8 -- Should match the number of decls in GHC.Classes +mAX_CTUPLE_SIZE = 16 -- Should match the number of decls in GHC.Classes -- | Default maximum depth for both class instance search and type family -- reduction. See also Trac #5395. diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs index 785dce7..15d647b 100644 --- a/compiler/typecheck/TcHsType.hs +++ b/compiler/typecheck/TcHsType.hs @@ -61,6 +61,8 @@ import TysWiredIn import BasicTypes import SrcLoc import DynFlags ( ExtensionFlag( Opt_DataKinds ), getDynFlags ) +import Constants ( mAX_CTUPLE_SIZE ) +import ErrUtils( MsgDoc ) import Unique import UniqSupply import Outputable @@ -569,11 +571,14 @@ finish_tuple hs_ty tup_sort tau_tys exp_kind = do { traceTc "finish_tuple" (ppr res_kind $$ ppr exp_kind $$ ppr exp_kind) ; checkExpectedKind hs_ty res_kind exp_kind ; tycon <- case tup_sort of - ConstraintTuple -> tcLookupTyCon (cTupleTyConName arity) - BoxedTuple -> do { let tc = tupleTyCon Boxed arity - ; checkWiredInTyCon tc - ; return tc } - UnboxedTuple -> return (tupleTyCon Unboxed arity) + ConstraintTuple + | arity > mAX_CTUPLE_SIZE + -> failWith (bigConstraintTuple arity) + | otherwise -> tcLookupTyCon (cTupleTyConName arity) + BoxedTuple -> do { let tc = tupleTyCon Boxed arity + ; checkWiredInTyCon tc + ; return tc } + UnboxedTuple -> return (tupleTyCon Unboxed arity) ; return (mkTyConApp tycon tau_tys) } where arity = length tau_tys @@ -582,6 +587,12 @@ finish_tuple hs_ty tup_sort tau_tys exp_kind BoxedTuple -> liftedTypeKind ConstraintTuple -> constraintKind +bigConstraintTuple :: Arity -> MsgDoc +bigConstraintTuple arity + = hang (ptext (sLit "Constraint tuple arity too large:") <+> int arity + <+> parens (ptext (sLit "max arity =") <+> int mAX_CTUPLE_SIZE)) + 2 (ptext (sLit "Instead, use a nested tuple")) + --------------------------- tcInferApps :: Outputable a => a From git at git.haskell.org Tue Jun 2 09:34:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Jun 2015 09:34:25 +0000 (UTC) Subject: [commit: ghc] master: Set 32-bit perf figure (dbcdfe2) Message-ID: <20150602093425.6C9093A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/dbcdfe23f5a3d82d832f2cbf1310dbf5569a5e2f/ghc >--------------------------------------------------------------- commit dbcdfe23f5a3d82d832f2cbf1310dbf5569a5e2f Author: Simon Peyton Jones Date: Tue Jun 2 00:48:12 2015 +0100 Set 32-bit perf figure >--------------------------------------------------------------- dbcdfe23f5a3d82d832f2cbf1310dbf5569a5e2f testsuite/tests/perf/should_run/all.T | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/perf/should_run/all.T b/testsuite/tests/perf/should_run/all.T index c95dfa0..6302022 100644 --- a/testsuite/tests/perf/should_run/all.T +++ b/testsuite/tests/perf/should_run/all.T @@ -3,7 +3,7 @@ test('T10359', [stats_num_field('bytes allocated', [(wordsize(64), 499512, 5), - (wordsize(32), 250000, 5)]), + (wordsize(32), 374056, 5)]), only_ways(['normal']) ], compile_and_run, From git at git.haskell.org Tue Jun 2 10:38:42 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Jun 2015 10:38:42 +0000 (UTC) Subject: [commit: ghc] master: Remove redundant import (d6c01fa) Message-ID: <20150602103842.7AC723A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d6c01faed26f05ff2023587eccef822f91da23ad/ghc >--------------------------------------------------------------- commit d6c01faed26f05ff2023587eccef822f91da23ad Author: Simon Peyton Jones Date: Tue Jun 2 11:37:53 2015 +0100 Remove redundant import >--------------------------------------------------------------- d6c01faed26f05ff2023587eccef822f91da23ad compiler/ghci/Debugger.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/compiler/ghci/Debugger.hs b/compiler/ghci/Debugger.hs index 6e891ba..ccd7f16 100644 --- a/compiler/ghci/Debugger.hs +++ b/compiler/ghci/Debugger.hs @@ -24,7 +24,6 @@ import IfaceEnv( newInteractiveBinder ) import Name import Var hiding ( varName ) import VarSet -import UniqSupply import Type import Kind import GHC From git at git.haskell.org Tue Jun 2 10:38:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Jun 2015 10:38:45 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #10423 (b1b2b44) Message-ID: <20150602103845.998713A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b1b2b44a86a34dae9eadd27af507c8b2c847ae2d/ghc >--------------------------------------------------------------- commit b1b2b44a86a34dae9eadd27af507c8b2c847ae2d Author: Simon Peyton Jones Date: Tue Jun 2 11:38:28 2015 +0100 Test Trac #10423 >--------------------------------------------------------------- b1b2b44a86a34dae9eadd27af507c8b2c847ae2d testsuite/tests/typecheck/should_compile/T10423.hs | 9 +++++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 2 files changed, 10 insertions(+) diff --git a/testsuite/tests/typecheck/should_compile/T10423.hs b/testsuite/tests/typecheck/should_compile/T10423.hs new file mode 100644 index 0000000..5a8ff02 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T10423.hs @@ -0,0 +1,9 @@ +{-# LANGUAGE FlexibleInstances, TypeFamilies, MultiParamTypeClasses #-} + +module T10423 where + +class Monad m => Testable m a + +newtype Prop m = MkProp (m Int) + +instance (Monad m, m ~ n) => Testable n (Prop m) diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index 2f257ea..12e2612 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -456,3 +456,4 @@ test('T10009', normal, compile, ['']) test('T10390', normal, compile, ['']) test('T8555', normal, compile, ['']) test('T8799', normal, compile, ['']) +test('T10423', normal, compile, ['']) From git at git.haskell.org Tue Jun 2 10:59:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Jun 2015 10:59:31 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #10451 (8a38348) Message-ID: <20150602105931.694B83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8a3834833d2636134f2e0617e6d85a68e92de551/ghc >--------------------------------------------------------------- commit 8a3834833d2636134f2e0617e6d85a68e92de551 Author: Simon Peyton Jones Date: Tue Jun 2 11:59:29 2015 +0100 Test Trac #10451 >--------------------------------------------------------------- 8a3834833d2636134f2e0617e6d85a68e92de551 testsuite/tests/polykinds/T10451.hs | 10 ++++++++++ testsuite/tests/polykinds/T10451.stderr | 7 +++++++ testsuite/tests/polykinds/all.T | 2 +- 3 files changed, 18 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/polykinds/T10451.hs b/testsuite/tests/polykinds/T10451.hs new file mode 100644 index 0000000..8ba867f --- /dev/null +++ b/testsuite/tests/polykinds/T10451.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE ConstraintKinds #-} + +module T10451 where + +type T a = ( Eq a, Eq a, Eq a, Eq a + , Eq a, Eq a, Eq a, Eq a + , Eq a, Eq a, Eq a, Eq a + , Eq a, Eq a, Eq a, Eq a + , Eq a, Eq a, Eq a, Eq a ) + diff --git a/testsuite/tests/polykinds/T10451.stderr b/testsuite/tests/polykinds/T10451.stderr new file mode 100644 index 0000000..56f037f --- /dev/null +++ b/testsuite/tests/polykinds/T10451.stderr @@ -0,0 +1,7 @@ + +T10451.hs:5:12: error: + Constraint tuple arity too large: 20 (max arity = 16) + Instead, use a nested tuple + In the type ?(Eq a, Eq a, Eq a, Eq a, Eq a, Eq a, Eq a, Eq a, Eq a, + Eq a, Eq a, Eq a, Eq a, Eq a, Eq a, Eq a, Eq a, Eq a, Eq a, Eq a)? + In the type declaration for ?T? diff --git a/testsuite/tests/polykinds/all.T b/testsuite/tests/polykinds/all.T index 7321387..75d2321 100644 --- a/testsuite/tests/polykinds/all.T +++ b/testsuite/tests/polykinds/all.T @@ -115,4 +115,4 @@ test('T9574', normal, compile_fail, ['']) test('T9833', normal, compile, ['']) test('T7908', normal, compile, ['']) test('T10041', normal, compile, ['']) - +test('T10451', normal, compile_fail, ['']) From git at git.haskell.org Tue Jun 2 11:37:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Jun 2015 11:37:34 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #10466 (8e5f8cf) Message-ID: <20150602113734.A2FCF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8e5f8cf4892971f9e1cf143672801eaad7138098/ghc >--------------------------------------------------------------- commit 8e5f8cf4892971f9e1cf143672801eaad7138098 Author: Simon Peyton Jones Date: Tue Jun 2 12:37:27 2015 +0100 Test Trac #10466 >--------------------------------------------------------------- 8e5f8cf4892971f9e1cf143672801eaad7138098 testsuite/tests/ghci/scripts/T10466.script | 3 +++ testsuite/tests/ghci/scripts/all.T | 1 + 2 files changed, 4 insertions(+) diff --git a/testsuite/tests/ghci/scripts/T10466.script b/testsuite/tests/ghci/scripts/T10466.script new file mode 100644 index 0000000..bb89e47 --- /dev/null +++ b/testsuite/tests/ghci/scripts/T10466.script @@ -0,0 +1,3 @@ +:set -XTemplateHaskell +let x = True +let y = [d| x = 'c' |] diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T index 2c48358..212b0e5 100755 --- a/testsuite/tests/ghci/scripts/all.T +++ b/testsuite/tests/ghci/scripts/all.T @@ -217,3 +217,4 @@ test('T10408B', normal, run_command, test('T10248', normal, ghci_script, ['T10248.script']) test('T10110', normal, ghci_script, ['T10110.script']) test('T10322', normal, ghci_script, ['T10322.script']) +test('T10466', normal, ghci_script, ['T10466.script']) From git at git.haskell.org Tue Jun 2 11:43:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Jun 2015 11:43:37 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #10438 (b2b69b2) Message-ID: <20150602114337.541373A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b2b69b2a31e5d41210e851687887377072afd020/ghc >--------------------------------------------------------------- commit b2b69b2a31e5d41210e851687887377072afd020 Author: Simon Peyton Jones Date: Tue Jun 2 12:43:11 2015 +0100 Test Trac #10438 >--------------------------------------------------------------- b2b69b2a31e5d41210e851687887377072afd020 .../tests/partial-sigs/should_compile/T10438.hs | 8 +++++++ .../partial-sigs/should_compile/T10438.stderr | 26 ++++++++++++++++++++++ testsuite/tests/partial-sigs/should_compile/all.T | 1 + 3 files changed, 35 insertions(+) diff --git a/testsuite/tests/partial-sigs/should_compile/T10438.hs b/testsuite/tests/partial-sigs/should_compile/T10438.hs new file mode 100644 index 0000000..583e0dd --- /dev/null +++ b/testsuite/tests/partial-sigs/should_compile/T10438.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE PartialTypeSignatures #-} +{-# LANGUAGE TypeFamilies #-} +module T10438 where + +foo f = g + where g r = x + where x :: _ + x = r diff --git a/testsuite/tests/partial-sigs/should_compile/T10438.stderr b/testsuite/tests/partial-sigs/should_compile/T10438.stderr new file mode 100644 index 0000000..9133a56 --- /dev/null +++ b/testsuite/tests/partial-sigs/should_compile/T10438.stderr @@ -0,0 +1,26 @@ + +T10438.hs:7:22: warning: + Found hole ?_? with type: w_1 + Where: ?w_1? is a rigid type variable bound by + the inferred type of g :: w_1 -> w_1 at T10438.hs:6:9 + Relevant bindings include + r :: w_1 (bound at T10438.hs:6:11) + g :: w_1 -> w_1 (bound at T10438.hs:6:9) + f :: t (bound at T10438.hs:5:5) + foo :: t -> w_ -> w_ (bound at T10438.hs:5:1) + In the type signature for ?x?: _ + In an equation for ?g?: + g r + = x + where + x :: _ + x = r + In an equation for ?foo?: + foo f + = g + where + g r + = x + where + x :: _ + x = r diff --git a/testsuite/tests/partial-sigs/should_compile/all.T b/testsuite/tests/partial-sigs/should_compile/all.T index 91294a5..812ff0a 100644 --- a/testsuite/tests/partial-sigs/should_compile/all.T +++ b/testsuite/tests/partial-sigs/should_compile/all.T @@ -47,3 +47,4 @@ test('Uncurry', normal, compile, ['-ddump-types -fno-warn-partial-type-signature test('UncurryNamed', normal, compile, ['-ddump-types -fno-warn-partial-type-signatures']) test('WarningWildcardInstantiations', normal, compile, ['-ddump-types']) test('T10403', normal, compile, ['']) +test('T10438', normal, compile, ['']) From git at git.haskell.org Tue Jun 2 13:32:10 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Jun 2015 13:32:10 +0000 (UTC) Subject: [commit: ghc] master: compiler: make sure we reject -O + HscInterpreted (091944e) Message-ID: <20150602133210.5ACBD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/091944e3aec736b440a9c1204f152004e382c967/ghc >--------------------------------------------------------------- commit 091944e3aec736b440a9c1204f152004e382c967 Author: Austin Seipp Date: Tue May 19 01:56:48 2015 -0500 compiler: make sure we reject -O + HscInterpreted When using GHCi, we explicitly reject optimization, because the compilers optimization passes can introduce unboxed tuples, which the interpreter is not able to handle. But this goes the other way too: using GHCi on optimized code may cause the optimizer to float out breakpoints that the interpreter introduces. This manifests itself in weird ways, particularly if you as an API client use custom DynFlags to introduce optimization in combination with HscInterpreted. It turns out we weren't checking for consistent DynFlag settings when doing `setSessionDynFlags`, as #10052 showed. While the main driver handled it in `DynFlags` via `parseDynamicFlags`, we didn't check this elsewhere. This does a little refactoring to split out some of the common code, and immunizes the various `DynFlags` utilities in the `GHC` module from this particular bug. We should probably be checking other general invariants too. This fixes #10052, and adds some notes about the behavior in `GHC` and `FloatOut` As a bonus, expose `warningMsg` from `ErrUtils` as a helper since it didn't exist (somehow). Signed-off-by: Austin Seipp Reviewed By: edsko Differential Revision: https://phabricator.haskell.org/D727 GHC Trac Issues: #10052 >--------------------------------------------------------------- 091944e3aec736b440a9c1204f152004e382c967 compiler/main/DynFlags.hs | 12 ++++--- compiler/main/ErrUtils.hs | 6 +++- compiler/main/GHC.hs | 41 ++++++++++++++++++---- compiler/simplCore/FloatOut.hs | 27 ++++++++++++++ testsuite/.gitignore | 1 + testsuite/tests/ghc-api/T10052/Makefile | 12 +++++++ testsuite/tests/ghc-api/T10052/T10052-input.hs | 1 + testsuite/tests/ghc-api/T10052/T10052.hs | 30 ++++++++++++++++ .../T10052/T10052.stderr} | 0 testsuite/tests/ghc-api/T10052/T10052.stdout | 1 + testsuite/tests/ghc-api/T10052/all.T | 2 ++ .../tests/ghci.debugger/scripts/print007.stderr | 5 ++- 12 files changed, 125 insertions(+), 13 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 091944e3aec736b440a9c1204f152004e382c967 From git at git.haskell.org Tue Jun 2 14:31:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Jun 2015 14:31:44 +0000 (UTC) Subject: [commit: ghc] master: build: make haddock a bit less chatty (e796026) Message-ID: <20150602143144.298873A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e796026b45974d71233eef7ffb6feee482c6dd7e/ghc >--------------------------------------------------------------- commit e796026b45974d71233eef7ffb6feee482c6dd7e Author: Austin Seipp Date: Tue Jun 2 09:31:52 2015 -0500 build: make haddock a bit less chatty Summary: Haddock outputs well over a thousand lines of file output just to give its executive summary about coverage. Kill this by default, since we really don't need it in any setting. Signed-off-by: Austin Seipp Test Plan: Crossed my fingers. Reviewers: nomeata, thomie Reviewed By: thomie Subscribers: bgamari, thomie Differential Revision: https://phabricator.haskell.org/D933 >--------------------------------------------------------------- e796026b45974d71233eef7ffb6feee482c6dd7e ghc.mk | 2 +- rules/haddock.mk | 1 + 2 files changed, 2 insertions(+), 1 deletion(-) diff --git a/ghc.mk b/ghc.mk index 5a1845c..3b38372 100644 --- a/ghc.mk +++ b/ghc.mk @@ -1375,7 +1375,7 @@ validate_build_xhtml: cd libraries/xhtml && ./Setup configure --with-ghc="$(BINDIST_PREFIX)/bin/ghc" $(BINDIST_HADDOCK_FLAG) $(BINDIST_LIBRARY_FLAGS) --global --builddir=dist-bindist --prefix="$(BINDIST_PREFIX)" cd libraries/xhtml && ./Setup build --builddir=dist-bindist ifeq "$(HADDOCK_DOCS)" "YES" - cd libraries/xhtml && ./Setup haddock --ghc-options=-optP-P --builddir=dist-bindist + cd libraries/xhtml && ./Setup haddock -v0 --ghc-options=-optP-P --builddir=dist-bindist endif cd libraries/xhtml && ./Setup install --builddir=dist-bindist cd libraries/xhtml && ./Setup clean --builddir=dist-bindist diff --git a/rules/haddock.mk b/rules/haddock.mk index a43df95..5604a50 100644 --- a/rules/haddock.mk +++ b/rules/haddock.mk @@ -48,6 +48,7 @@ ifeq "$$(HSCOLOUR_SRCS)" "YES" "$$(ghc-cabal_INPLACE)" hscolour $1 $2 endif "$$(TOP)/$$(INPLACE_BIN)/haddock" \ + --verbosity=0 \ --odir="$1/$2/doc/html/$$($1_PACKAGE)" \ --no-tmp-comp-dir \ --dump-interface=$$($$($1_PACKAGE)-$$($1_$2_VERSION)_HADDOCK_FILE) \ From git at git.haskell.org Tue Jun 2 16:37:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Jun 2015 16:37:27 +0000 (UTC) Subject: [commit: ghc] master: Improve FFI error reporting (3758050) Message-ID: <20150602163727.5D5B73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3758050f02c1de6af41c50ed122b3df012d400ff/ghc >--------------------------------------------------------------- commit 3758050f02c1de6af41c50ed122b3df012d400ff Author: Simon Peyton Jones Date: Tue Jun 2 17:37:09 2015 +0100 Improve FFI error reporting I refactored TcType FFI functions to return Validity rather than Bool, which turned out to be an easy way to solve Trac #10461. >--------------------------------------------------------------- 3758050f02c1de6af41c50ed122b3df012d400ff compiler/typecheck/TcType.hs | 113 ++++++++++++++------------ testsuite/tests/ffi/should_fail/T10461.hs | 6 ++ testsuite/tests/ffi/should_fail/T10461.stderr | 7 ++ testsuite/tests/ffi/should_fail/all.T | 1 + 4 files changed, 77 insertions(+), 50 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 3758050f02c1de6af41c50ed122b3df012d400ff From git at git.haskell.org Tue Jun 2 19:24:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Jun 2015 19:24:09 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Reduce magic for seqId (cf9f638) Message-ID: <20150602192409.BDF233A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/cf9f638fa2e54e8573e7f042df6bff5d0f059811/ghc >--------------------------------------------------------------- commit cf9f638fa2e54e8573e7f042df6bff5d0f059811 Author: Simon Peyton Jones Date: Fri May 22 14:41:54 2015 +0100 Reduce magic for seqId An upcoming commit means that the RULES for 'seq' get only one value arg, not two. This patch prepares for that by - reducing the arity of seq's built-in rule, to take one value arg - making 'seq' not inline on the LHS of RULES - and removing the horrid un-inlining in DsBinds.decomposeRuleLhs (cherry picked from commit eae703aa60f41fd232be5478e196b661839ec3de) >--------------------------------------------------------------- cf9f638fa2e54e8573e7f042df6bff5d0f059811 compiler/basicTypes/MkId.hs | 34 ++++++++++++++++++++++++---------- compiler/coreSyn/CoreSubst.hs | 15 +++++++++++---- compiler/deSugar/DsBinds.hs | 6 ------ 3 files changed, 35 insertions(+), 20 deletions(-) diff --git a/compiler/basicTypes/MkId.hs b/compiler/basicTypes/MkId.hs index 4d473d5..c6161c5 100644 --- a/compiler/basicTypes/MkId.hs +++ b/compiler/basicTypes/MkId.hs @@ -1086,10 +1086,15 @@ nullAddrId = pcMiscPrelId nullAddrName addrPrimTy info seqId :: Id -- See Note [seqId magic] seqId = pcMiscPrelId seqName ty info where - info = noCafIdInfo `setInlinePragInfo` alwaysInlinePragma + info = noCafIdInfo `setInlinePragInfo` inline_prag `setUnfoldingInfo` mkCompulsoryUnfolding rhs `setSpecInfo` mkSpecInfo [seq_cast_rule] + inline_prag = alwaysInlinePragma `setInlinePragmaActivation` ActiveAfter 0 + -- Make 'seq' not inline-always, so that simpleOptExpr + -- (see CoreSubst.simple_app) won't inline 'seq' on the + -- LHS of rules. That way we can have rules for 'seq'; + -- see Note [seqId magic] ty = mkForAllTys [alphaTyVar,betaTyVar] (mkFunTy alphaTy (mkFunTy betaTy betaTy)) @@ -1099,17 +1104,18 @@ seqId = pcMiscPrelId seqName ty info rhs = mkLams [alphaTyVar,betaTyVar,x,y] (Case (Var x) x betaTy [(DEFAULT, [], Var y)]) -- See Note [Built-in RULES for seq] + -- NB: ru_nargs = 3, not 4, to match the code in + -- Simplify.rebuildCase which tries to apply this rule seq_cast_rule = BuiltinRule { ru_name = fsLit "seq of cast" , ru_fn = seqName - , ru_nargs = 4 - , ru_try = match_seq_of_cast - } + , ru_nargs = 3 + , ru_try = match_seq_of_cast } match_seq_of_cast :: RuleFun -- See Note [Built-in RULES for seq] -match_seq_of_cast _ _ _ [Type _, Type res_ty, Cast scrut co, expr] +match_seq_of_cast _ _ _ [Type _, Type res_ty, Cast scrut co] = Just (Var seqId `mkApps` [Type (pFst (coercionKind co)), Type res_ty, - scrut, expr]) + scrut]) match_seq_of_cast _ _ _ _ = Nothing ------------------------------------------------ @@ -1215,16 +1221,24 @@ transform to Rather than attempt some general analysis to support this, I've added enough support that you can do this using a rewrite rule: - RULE "f/seq" forall n. seq (f n) e = seq n e + RULE "f/seq" forall n. seq (f n) = seq n You write that rule. When GHC sees a case expression that discards its result, it mentally transforms it to a call to 'seq' and looks for a RULE. (This is done in Simplify.rebuildCase.) As usual, the correctness of the rule is up to you. -To make this work, we need to be careful that the magical desugaring -done in Note [seqId magic] item (c) is *not* done on the LHS of a rule. -Or rather, we arrange to un-do it, in DsBinds.decomposeRuleLhs. +VERY IMPORTANT: to make this work, we give the RULE an arity of 1, not 2. +If we wrote + RULE "f/seq" forall n e. seq (f n) e = seq n e +with rule arity 2, then two bad things would happen: + + - The magical desugaring done in Note [seqId magic] item (c) + for saturated application of 'seq' would turn the LHS into + a case expression! + + - The code in Simplify.rebuildCase would need to actually supply + the value argument, which turns out to be awkward. Note [Built-in RULES for seq] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~ diff --git a/compiler/coreSyn/CoreSubst.hs b/compiler/coreSyn/CoreSubst.hs index b381dc8..35dbb50 100644 --- a/compiler/coreSyn/CoreSubst.hs +++ b/compiler/coreSyn/CoreSubst.hs @@ -954,6 +954,7 @@ simple_app subst (Lam b e) (a:as) b2 = add_info subst' b b' simple_app subst (Var v) as | isCompulsoryUnfolding (idUnfolding v) + , isAlwaysActive (idInlineActivation v) -- See Note [Unfold compulsory unfoldings in LHSs] = simple_app subst (unfoldingTemplate (idUnfolding v)) as simple_app subst (Tick t e) as @@ -1108,10 +1109,16 @@ to remain visible until Phase 1 Note [Unfold compulsory unfoldings in LHSs] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -When the user writes `map coerce = coerce` as a rule, the rule will only ever -match if we replace coerce by its unfolding on the LHS, because that is the -core that the rule matching engine will find. So do that for everything that -has a compulsory unfolding. Also see Note [Desugaring coerce as cast] in Desugar +When the user writes `RULES map coerce = coerce` as a rule, the rule +will only ever match if simpleOptExpr replaces coerce by its unfolding +on the LHS, because that is the core that the rule matching engine +will find. So do that for everything that has a compulsory +unfolding. Also see Note [Desugaring coerce as cast] in Desugar. + +However, we don't want to inline 'seq', which happens to also have a +compulsory unfolding, so we only do this unfolding only for things +that are always-active. See Note [User-defined RULES for seq] in MkId. + ************************************************************************ * * diff --git a/compiler/deSugar/DsBinds.hs b/compiler/deSugar/DsBinds.hs index bb10711..b6693aa 100644 --- a/compiler/deSugar/DsBinds.hs +++ b/compiler/deSugar/DsBinds.hs @@ -53,7 +53,6 @@ import MkId(proxyHashId) import Class import DataCon ( dataConWorkId ) import Name -import MkId ( seqId ) import IdInfo ( IdDetails(..) ) import Var import VarSet @@ -638,11 +637,6 @@ decomposeRuleLhs orig_bndrs orig_lhs | not (fn_id `elemVarSet` orig_bndr_set) = Just (fn_id, args) - decompose (Case scrut bndr ty [(DEFAULT, _, body)]) args - | isDeadBinder bndr -- Note [Matching seqId] - , let args' = [Type (idType bndr), Type ty, scrut, body] - = Just (seqId, args' ++ args) - decompose _ _ = Nothing bad_shape_msg = hang (ptext (sLit "RULE left-hand side too complicated to desugar")) From git at git.haskell.org Tue Jun 2 19:24:12 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Jun 2015 19:24:12 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Fix quadratic behaviour in tidyOccName (9b406cc) Message-ID: <20150602192412.850F53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/9b406cc65cdb5db6b294a63301aed52a02bcbaf5/ghc >--------------------------------------------------------------- commit 9b406cc65cdb5db6b294a63301aed52a02bcbaf5 Author: Simon Peyton Jones Date: Fri May 22 14:46:51 2015 +0100 Fix quadratic behaviour in tidyOccName In the test program from comment:3 of Trac #10370, it turned out that 25% of all compile time was going in OccName.tidyOccName! It was all becuase the algorithm for finding an unused OccName had a quadratic case. This patch fixes it. THe effect is pretty big: Before: total time = 34.30 secs (34295 ticks @ 1000 us, 1 processor) total alloc = 15,496,011,168 bytes (excludes profiling overheads) After total time = 25.41 secs (25415 ticks @ 1000 us, 1 processor) total alloc = 11,812,744,816 bytes (excludes profiling overheads) (cherry picked from commit c89bd681d34d3339771ebdde8aa468b1d9ab042b) >--------------------------------------------------------------- 9b406cc65cdb5db6b294a63301aed52a02bcbaf5 compiler/basicTypes/OccName.hs | 57 +++++++++++++++++----- compiler/typecheck/TcMType.hs | 2 - compiler/types/TypeRep.hs | 2 + .../tests/ghci.debugger/scripts/print027.stdout | 6 +-- testsuite/tests/parser/should_fail/T7848.stderr | 2 +- .../tests/simplCore/should_compile/T7360.stderr | 16 +++--- 6 files changed, 58 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 9b406cc65cdb5db6b294a63301aed52a02bcbaf5 From git at git.haskell.org Tue Jun 2 19:24:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Jun 2015 19:24:15 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Fix a huge space leak in the mighty Simplifier (8af219a) Message-ID: <20150602192415.54FB33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/8af219adb914b292d0f8c737fe0a1e3f7fb19cf3/ghc >--------------------------------------------------------------- commit 8af219adb914b292d0f8c737fe0a1e3f7fb19cf3 Author: Simon Peyton Jones Date: Fri May 22 15:04:47 2015 +0100 Fix a huge space leak in the mighty Simplifier This long-standing, terrible, adn somewhat subtle bug was exposed by Trac #10370, thanks to Reid Barton's brilliant test case (comment:3). The effect is large on the Trac #10370 test. Here is what the profile report says: Before: total time = 24.35 secs (24353 ticks @ 1000 us, 1 processor) total alloc = 11,864,360,816 bytes (excludes profiling overheads) After: total time = 21.16 secs (21160 ticks @ 1000 us, 1 processor) total alloc = 7,947,141,136 bytes (excludes profiling overheads) The /combined/ effect of the tidyOccName fix, plus this one, is dramtic for Trac #10370. Here is what +RTS -s says: Before: 15,490,210,952 bytes allocated in the heap 1,783,919,456 bytes maximum residency (20 sample(s)) MUT time 30.117s ( 31.383s elapsed) GC time 90.103s ( 90.107s elapsed) Total time 120.843s (122.065s elapsed) After: 7,928,671,936 bytes allocated in the heap 52,914,832 bytes maximum residency (25 sample(s)) MUT time 13.912s ( 15.110s elapsed) GC time 6.809s ( 6.808s elapsed) Total time 20.789s ( 21.954s elapsed) - Heap allocation halved - Residency cut by a factor of more than 30. - ELapsed time cut by a factor of 6 Not bad! The details ~~~~~~~~~~~ The culprit was SimplEnv.mkCoreSubst, which used mapVarEnv to do some impedence-matching from the substitituion used by the simplifier to the one used by CoreSubst. But the impedence-mactching was recursive! mk_subst tv_env cv_env id_env = CoreSubst.mkSubst in_scope tv_env cv_env (mapVarEnv fiddle id_env) fiddle (DoneEx e) = e fiddle (DoneId v) = Var v fiddle (ContEx tv cv id e) = CoreSubst.substExpr (mk_subst tv cv id) e Inside fiddle, in the ContEx case, we may do another whole level of fiddle. And so on. Moreover, UniqFM (which is built on Data.IntMap) is strict, so the fiddling is done eagerly. I didn't wok through all the details but the result is a gargatuan blow-up of entirely unnecessary work. Laziness would make this go away, I think, but I don't want to mess with IntMap. And in any case, the impedence matching is a royal pain. In the end I simply ceased trying to use CoreSubst.substExpr in the simplifier, and instead just use simplExpr. That does mean bit of duplication; e.g. new code for simplRules. But it's not a big deal and it's far more direct and easy to reason about. A bit of knock-on refactoring: * Data type ArgSummary moves to CoreUnfold. * interestingArg moves from CoreUnfold to SimplUtils, and gets a SimplEnv argument which can be used when we encounter a variable. * simplLamBndrs, addBndrRules move from SimplEnv to Simplify (because they now calls simplUnfolding, simplRules resp) * SimplUtils.substExpr, substUnfolding, mkCoreSubst die completely * In Simplify some several functions that were previously pure substitution-based functions are now monadic: - addBndrRules, simplRule - addCoerce, add_coerce in simplCast * In case 2c of Simplify.rebuildCase, there was a pretty disgusting expression-substitution taking place for 'rhs'; and we really don't want to make that monadic becuase 'rhs' can be big. Solution: reduce the arity of the rules for seq. See Note [User-defined RULES for seq] in MkId. (cherry picked from commit 45d9a15c4b85a2ed89579106bdafd84accf2cb39) >--------------------------------------------------------------- 8af219adb914b292d0f8c737fe0a1e3f7fb19cf3 compiler/coreSyn/CoreUnfold.hs | 88 +----- compiler/simplCore/SimplCore.hs | 19 +- compiler/simplCore/SimplEnv.hs | 94 +----- compiler/simplCore/SimplUtils.hs | 217 +++++++++----- compiler/simplCore/Simplify.hs | 323 +++++++++++++-------- testsuite/tests/perf/compiler/all.T | 5 +- .../tests/simplCore/should_compile/T7785.stderr | 2 + .../tests/simplCore/should_compile/rule2.stderr | 3 +- testsuite/tests/simplCore/should_run/SeqRule.hs | 2 +- 9 files changed, 397 insertions(+), 356 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 8af219adb914b292d0f8c737fe0a1e3f7fb19cf3 From git at git.haskell.org Tue Jun 2 19:24:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Jun 2015 19:24:18 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: testsuite: commit missing T4945 stdout (452e336) Message-ID: <20150602192418.6F8A13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/452e3367e5977370fa29118dd3e3cc2971fb16f9/ghc >--------------------------------------------------------------- commit 452e3367e5977370fa29118dd3e3cc2971fb16f9 Author: Austin Seipp Date: Sat May 23 07:24:50 2015 -0500 testsuite: commit missing T4945 stdout Simon apparently forgot this it seems. Signed-off-by: Austin Seipp (cherry picked from commit 7d519dabd2006c9742e82fce02df55704da15482) >--------------------------------------------------------------- 452e3367e5977370fa29118dd3e3cc2971fb16f9 testsuite/tests/simplCore/should_compile/T4945.stdout | 9 +++++++++ 1 file changed, 9 insertions(+) diff --git a/testsuite/tests/simplCore/should_compile/T4945.stdout b/testsuite/tests/simplCore/should_compile/T4945.stdout new file mode 100644 index 0000000..4e53cfd --- /dev/null +++ b/testsuite/tests/simplCore/should_compile/T4945.stdout @@ -0,0 +1,9 @@ + -> STUArray RealWorld Int Int -> (# State# RealWorld, () #) + (ipv3 [OS=OneShot] :: STUArray RealWorld Int Int) -> + case ipv3 of _ [Occ=Dead] { STUArray ds5 ds6 dt ds7 -> + (Data.Array.Base.STUArray + (Data.Array.Base.STUArray + (Data.Array.Base.STUArray + (Data.Array.Base.STUArray + (Data.Array.Base.STUArray + (Data.Array.Base.STUArray From git at git.haskell.org Tue Jun 2 19:24:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Jun 2015 19:24:21 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: compiler: kill a stray pprTrace in OccName (91324d4) Message-ID: <20150602192421.34DC73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/91324d46496e9f5623b06060d067332296914d88/ghc >--------------------------------------------------------------- commit 91324d46496e9f5623b06060d067332296914d88 Author: Austin Seipp Date: Sat May 23 07:26:55 2015 -0500 compiler: kill a stray pprTrace in OccName Left in by c89bd681d34d, and otherwise rather annoying during the build! Signed-off-by: Austin Seipp (cherry picked from commit 4d6c0ee11ff2c439fcd06677d55c57b8644ed7a7) >--------------------------------------------------------------- 91324d46496e9f5623b06060d067332296914d88 compiler/basicTypes/OccName.hs | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/compiler/basicTypes/OccName.hs b/compiler/basicTypes/OccName.hs index 7ea3faf..a0b5758 100644 --- a/compiler/basicTypes/OccName.hs +++ b/compiler/basicTypes/OccName.hs @@ -848,9 +848,7 @@ tidyOccName env occ@(OccName occ_sp fs) -- 1, add 1, add 2, add 3, etc which -- moves at quadratic speed through a dense patch - Nothing -> (if k>5 then pprTrace "tidyOccName" (ppr k $$ ppr occ $$ ppr new_fs) - else \x -> x) - (new_env, OccName occ_sp new_fs) + Nothing -> (new_env, OccName occ_sp new_fs) where new_fs = mkFastString (base ++ show n) new_env = addToUFM (addToUFM env new_fs 1) base1 (n+1) From git at git.haskell.org Tue Jun 2 19:24:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Jun 2015 19:24:23 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: testsuite: fix some failures from merge problems (07282c7) Message-ID: <20150602192423.DC4F83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/07282c7222d718e6d3df8d8f843d95d534dd7062/ghc >--------------------------------------------------------------- commit 07282c7222d718e6d3df8d8f843d95d534dd7062 Author: Austin Seipp Date: Tue Jun 2 14:07:35 2015 -0500 testsuite: fix some failures from merge problems Signed-off-by: Austin Seipp >--------------------------------------------------------------- 07282c7222d718e6d3df8d8f843d95d534dd7062 testsuite/tests/driver/T2507.stderr | 4 ++-- testsuite/tests/ghci/prog013/prog013.stderr | 12 ++++++------ testsuite/tests/simplCore/should_compile/T4945.stdout | 8 +++----- 3 files changed, 11 insertions(+), 13 deletions(-) diff --git a/testsuite/tests/driver/T2507.stderr b/testsuite/tests/driver/T2507.stderr index 925a870..e4365a3 100644 --- a/testsuite/tests/driver/T2507.stderr +++ b/testsuite/tests/driver/T2507.stderr @@ -1,5 +1,5 @@ T2507.hs:5:7: - Couldn't match expected type `Int' with actual type `()' + Couldn't match expected type ?Int? with actual type ?()? In the expression: () - In an equation for `foo': foo = () + In an equation for ?foo?: foo = () diff --git a/testsuite/tests/ghci/prog013/prog013.stderr b/testsuite/tests/ghci/prog013/prog013.stderr index ce8827f..f701de4 100644 --- a/testsuite/tests/ghci/prog013/prog013.stderr +++ b/testsuite/tests/ghci/prog013/prog013.stderr @@ -1,17 +1,17 @@ -Bad.hs:3:8: error: +Bad.hs:3:8: lexical error in string/character literal at character '\n' -Bad.hs:3:8: error: +Bad.hs:3:8: lexical error in string/character literal at character '\n' -Bad.hs:3:8: error: +Bad.hs:3:8: lexical error in string/character literal at character '\n' -:10:1: error: parse error on input ?+? +:10:1: parse error on input ?+? -Bad.hs:3:8: error: +Bad.hs:3:8: lexical error in string/character literal at character '\n' -Bad.hs:3:8: error: +Bad.hs:3:8: lexical error in string/character literal at character '\n' diff --git a/testsuite/tests/simplCore/should_compile/T4945.stdout b/testsuite/tests/simplCore/should_compile/T4945.stdout index 4e53cfd..2467d21 100644 --- a/testsuite/tests/simplCore/should_compile/T4945.stdout +++ b/testsuite/tests/simplCore/should_compile/T4945.stdout @@ -1,9 +1,7 @@ - -> STUArray RealWorld Int Int -> (# State# RealWorld, () #) + -> STUArray RealWorld Int Int (ipv3 [OS=OneShot] :: STUArray RealWorld Int Int) -> case ipv3 of _ [Occ=Dead] { STUArray ds5 ds6 dt ds7 -> (Data.Array.Base.STUArray - (Data.Array.Base.STUArray - (Data.Array.Base.STUArray (Data.Array.Base.STUArray - (Data.Array.Base.STUArray - (Data.Array.Base.STUArray + (Data.Array.Base.STUArray + (Data.Array.Base.STUArray From git at git.haskell.org Tue Jun 2 19:24:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Jun 2015 19:24:27 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Rename new T9858c to T9858d to avoid test name clash (b980228) Message-ID: <20150602192427.254673A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/b980228a7f79ad54d509bb531e76da42fc72df09/ghc >--------------------------------------------------------------- commit b980228a7f79ad54d509bb531e76da42fc72df09 Author: Joachim Breitner Date: Wed Apr 22 16:18:27 2015 +0200 Rename new T9858c to T9858d to avoid test name clash (cherry picked from commit 43d7137399e6edcf950b3ed43b752b06ad550d2e) >--------------------------------------------------------------- b980228a7f79ad54d509bb531e76da42fc72df09 testsuite/tests/typecheck/should_fail/{T9858c.hs => T9858d.hs} | 2 +- testsuite/tests/typecheck/should_fail/{T9858c.stderr => T9858d.stderr} | 1 - testsuite/tests/typecheck/should_fail/all.T | 2 +- 3 files changed, 2 insertions(+), 3 deletions(-) diff --git a/testsuite/tests/typecheck/should_fail/T9858c.hs b/testsuite/tests/typecheck/should_fail/T9858d.hs similarity index 90% rename from testsuite/tests/typecheck/should_fail/T9858c.hs rename to testsuite/tests/typecheck/should_fail/T9858d.hs index 116a50b..dedd71c 100644 --- a/testsuite/tests/typecheck/should_fail/T9858c.hs +++ b/testsuite/tests/typecheck/should_fail/T9858d.hs @@ -1,6 +1,6 @@ {-# LANGUAGE ImpredicativeTypes, FlexibleContexts #-} -module T9858b where +module T9858d where import Data.Typeable i :: (Typeable a, Typeable b) => Proxy (a b) -> TypeRep diff --git a/testsuite/tests/typecheck/should_fail/T9858c.stderr b/testsuite/tests/typecheck/should_fail/T9858d.stderr similarity index 99% rename from testsuite/tests/typecheck/should_fail/T9858c.stderr rename to testsuite/tests/typecheck/should_fail/T9858d.stderr index 2f235005..6936ed2 100644 --- a/testsuite/tests/typecheck/should_fail/T9858c.stderr +++ b/testsuite/tests/typecheck/should_fail/T9858d.stderr @@ -1,4 +1,3 @@ - T9858c.hs:9:8: Couldn't match type ?Eq Int => Int? with ?a0 b0? Expected type: Proxy (a0 b0) diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index 6402dc4..745c2f2 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -361,4 +361,4 @@ test('T10285', multimod_compile_fail, ['T10285', '-v0']) test('T9858a', normal, compile_fail, ['']) test('T9858b', normal, compile_fail, ['']) -test('T9858c', normal, compile_fail, ['']) +test('T9858d', normal, compile_fail, ['']) From git at git.haskell.org Tue Jun 2 19:24:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Jun 2015 19:24:30 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Rename new T9858d to T9858e to avoid test name clash (28943a8) Message-ID: <20150602192430.670C43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/28943a8925427a5aafa7013e3ad47ff4511985da/ghc >--------------------------------------------------------------- commit 28943a8925427a5aafa7013e3ad47ff4511985da Author: Joachim Breitner Date: Wed Apr 22 18:50:00 2015 +0200 Rename new T9858d to T9858e to avoid test name clash (Next time, when fixing someone else?s mistake, I really shouldn?t do the precise same thing.) (cherry picked from commit a55bfabbed21f17064f863450f9d94d45db9c478) >--------------------------------------------------------------- 28943a8925427a5aafa7013e3ad47ff4511985da testsuite/tests/typecheck/should_fail/{T9858d.hs => T9858e.hs} | 2 +- testsuite/tests/typecheck/should_fail/{T9858d.stderr => T9858e.stderr} | 2 +- testsuite/tests/typecheck/should_fail/all.T | 2 +- 3 files changed, 3 insertions(+), 3 deletions(-) diff --git a/testsuite/tests/typecheck/should_fail/T9858d.hs b/testsuite/tests/typecheck/should_fail/T9858e.hs similarity index 90% rename from testsuite/tests/typecheck/should_fail/T9858d.hs rename to testsuite/tests/typecheck/should_fail/T9858e.hs index dedd71c..0ec39a6 100644 --- a/testsuite/tests/typecheck/should_fail/T9858d.hs +++ b/testsuite/tests/typecheck/should_fail/T9858e.hs @@ -1,6 +1,6 @@ {-# LANGUAGE ImpredicativeTypes, FlexibleContexts #-} -module T9858d where +module T9858e where import Data.Typeable i :: (Typeable a, Typeable b) => Proxy (a b) -> TypeRep diff --git a/testsuite/tests/typecheck/should_fail/T9858d.stderr b/testsuite/tests/typecheck/should_fail/T9858e.stderr similarity index 94% rename from testsuite/tests/typecheck/should_fail/T9858d.stderr rename to testsuite/tests/typecheck/should_fail/T9858e.stderr index 6936ed2..10d65b9 100644 --- a/testsuite/tests/typecheck/should_fail/T9858d.stderr +++ b/testsuite/tests/typecheck/should_fail/T9858e.stderr @@ -1,4 +1,4 @@ -T9858c.hs:9:8: +T9858e.hs:9:8: error: Couldn't match type ?Eq Int => Int? with ?a0 b0? Expected type: Proxy (a0 b0) Actual type: Proxy (Eq Int => Int) diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index 745c2f2..ad036b3 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -361,4 +361,4 @@ test('T10285', multimod_compile_fail, ['T10285', '-v0']) test('T9858a', normal, compile_fail, ['']) test('T9858b', normal, compile_fail, ['']) -test('T9858d', normal, compile_fail, ['']) +test('T9858e', normal, compile_fail, ['']) From git at git.haskell.org Tue Jun 2 19:24:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Jun 2015 19:24:33 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Rename tests so that they have a unique name. (763936c) Message-ID: <20150602192433.237313A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/763936c204a633d4e2e092de22fc36c6b04242e1/ghc >--------------------------------------------------------------- commit 763936c204a633d4e2e092de22fc36c6b04242e1 Author: Iavor S. Diatchki Date: Thu Apr 16 14:29:07 2015 -0700 Rename tests so that they have a unique name. (cherry picked from commit 3b90d8c8cfb4f56cec3eb5e1ede12c22a9e28d79) >--------------------------------------------------------------- 763936c204a633d4e2e092de22fc36c6b04242e1 testsuite/tests/typecheck/should_run/{T9858b.hs => T9858d.hs} | 0 testsuite/tests/typecheck/should_run/{T9858b.stdout => T9858d.stdout} | 0 testsuite/tests/typecheck/should_run/all.T | 2 +- 3 files changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/typecheck/should_run/T9858b.hs b/testsuite/tests/typecheck/should_run/T9858d.hs similarity index 100% rename from testsuite/tests/typecheck/should_run/T9858b.hs rename to testsuite/tests/typecheck/should_run/T9858d.hs diff --git a/testsuite/tests/typecheck/should_run/T9858b.stdout b/testsuite/tests/typecheck/should_run/T9858d.stdout similarity index 100% rename from testsuite/tests/typecheck/should_run/T9858b.stdout rename to testsuite/tests/typecheck/should_run/T9858d.stdout diff --git a/testsuite/tests/typecheck/should_run/all.T b/testsuite/tests/typecheck/should_run/all.T index 990688f..55b88cf 100755 --- a/testsuite/tests/typecheck/should_run/all.T +++ b/testsuite/tests/typecheck/should_run/all.T @@ -115,5 +115,5 @@ test('T8739', normal, compile_and_run, ['']) test('T9497a-run', [exit_code(1)], compile_and_run, ['-fdefer-typed-holes']) test('T9497b-run', [exit_code(1)], compile_and_run, ['-fdefer-typed-holes -fno-warn-typed-holes']) test('T9497c-run', [exit_code(1)], compile_and_run, ['-fdefer-type-errors -fno-warn-typed-holes']) -test('T9858b', normal, compile_and_run, ['']) test('T9858c', normal, compile_and_run, ['']) +test('T9858d', normal, compile_and_run, ['']) From git at git.haskell.org Tue Jun 2 19:24:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Jun 2015 19:24:37 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: compiler: make sure we reject -O + HscInterpreted (20d33af) Message-ID: <20150602192437.031093A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/20d33af1ff4375a735845081be41fbd8a1472d28/ghc >--------------------------------------------------------------- commit 20d33af1ff4375a735845081be41fbd8a1472d28 Author: Austin Seipp Date: Tue May 19 01:56:48 2015 -0500 compiler: make sure we reject -O + HscInterpreted When using GHCi, we explicitly reject optimization, because the compilers optimization passes can introduce unboxed tuples, which the interpreter is not able to handle. But this goes the other way too: using GHCi on optimized code may cause the optimizer to float out breakpoints that the interpreter introduces. This manifests itself in weird ways, particularly if you as an API client use custom DynFlags to introduce optimization in combination with HscInterpreted. It turns out we weren't checking for consistent DynFlag settings when doing `setSessionDynFlags`, as #10052 showed. While the main driver handled it in `DynFlags` via `parseDynamicFlags`, we didn't check this elsewhere. This does a little refactoring to split out some of the common code, and immunizes the various `DynFlags` utilities in the `GHC` module from this particular bug. We should probably be checking other general invariants too. This fixes #10052, and adds some notes about the behavior in `GHC` and `FloatOut` As a bonus, expose `warningMsg` from `ErrUtils` as a helper since it didn't exist (somehow). Signed-off-by: Austin Seipp Reviewed By: edsko Differential Revision: https://phabricator.haskell.org/D727 GHC Trac Issues: #10052 (cherry picked from commit 091944e3aec736b440a9c1204f152004e382c967) >--------------------------------------------------------------- 20d33af1ff4375a735845081be41fbd8a1472d28 compiler/main/DynFlags.hs | 12 ++++--- compiler/main/ErrUtils.hs | 6 +++- compiler/main/GHC.hs | 41 ++++++++++++++++++---- compiler/simplCore/FloatOut.hs | 27 ++++++++++++++ testsuite/.gitignore | 1 + testsuite/tests/ghc-api/T10052/Makefile | 12 +++++++ testsuite/tests/ghc-api/T10052/T10052-input.hs | 1 + testsuite/tests/ghc-api/T10052/T10052.hs | 30 ++++++++++++++++ .../T10052/T10052.stderr} | 0 testsuite/tests/ghc-api/T10052/T10052.stdout | 1 + testsuite/tests/ghc-api/T10052/all.T | 2 ++ .../tests/ghci.debugger/scripts/print007.stderr | 5 ++- 12 files changed, 125 insertions(+), 13 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 20d33af1ff4375a735845081be41fbd8a1472d28 From git at git.haskell.org Tue Jun 2 20:01:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Jun 2015 20:01:51 +0000 (UTC) Subject: [commit: ghc] master: Detabify a programlisting in the User's Guide (#10425) (5688053) Message-ID: <20150602200151.110F83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5688053a5c0a188c8bc94cd2c41d178b5c716535/ghc >--------------------------------------------------------------- commit 5688053a5c0a188c8bc94cd2c41d178b5c716535 Author: Reid Barton Date: Tue Jun 2 16:00:10 2015 -0400 Detabify a programlisting in the User's Guide (#10425) >--------------------------------------------------------------- 5688053a5c0a188c8bc94cd2c41d178b5c716535 docs/users_guide/bugs.xml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/docs/users_guide/bugs.xml b/docs/users_guide/bugs.xml index 1e948e6..cb32775 100644 --- a/docs/users_guide/bugs.xml +++ b/docs/users_guide/bugs.xml @@ -71,7 +71,7 @@ main = do args <- getArgs - if null args then return [] else do + if null args then return [] else do ps <- mapM process args mapM print ps From git at git.haskell.org Tue Jun 2 21:05:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Jun 2015 21:05:03 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: ApiAnnotations : rationalise tests (b57348f) Message-ID: <20150602210503.D5F7A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/b57348fda1e5bab4ad6c5a13e2152af7e62f8ffb/ghc >--------------------------------------------------------------- commit b57348fda1e5bab4ad6c5a13e2152af7e62f8ffb Author: Alan Zimmerman Date: Mon Jun 1 11:51:27 2015 +0200 ApiAnnotations : rationalise tests Summary: At the moment the API Annotations tests have a driver that has been copy/pasted multiple times. Compile it once, and run it for each test case. Test Plan: ./validate Reviewers: hvr, austin Reviewed By: austin Subscribers: bgamari, thomie Differential Revision: https://phabricator.haskell.org/D913 GHC Trac Issues: #10452 (cherry picked from commit e00910b0f83eaafd91dcb59cec0779b3ea9f0d30) >--------------------------------------------------------------- b57348fda1e5bab4ad6c5a13e2152af7e62f8ffb testsuite/tests/ghc-api/annotations/.gitignore | 14 +- .../annotations/{t10278.hs => CheckUtils.hs} | 15 +- testsuite/tests/ghc-api/annotations/Makefile | 173 ++++++++++++--------- testsuite/tests/ghc-api/annotations/T10255.stderr | 3 - testsuite/tests/ghc-api/annotations/T10255.stdout | 2 + testsuite/tests/ghc-api/annotations/T10268.stdout | 2 + testsuite/tests/ghc-api/annotations/T10269.stdout | 2 + testsuite/tests/ghc-api/annotations/T10280.stdout | 2 + testsuite/tests/ghc-api/annotations/T10307.stdout | 2 + testsuite/tests/ghc-api/annotations/T10309.stdout | 2 + testsuite/tests/ghc-api/annotations/T10312.stdout | 2 + testsuite/tests/ghc-api/annotations/T10358.stderr | 12 -- testsuite/tests/ghc-api/annotations/T10358.stdout | 2 +- testsuite/tests/ghc-api/annotations/T10399.stderr | 12 +- testsuite/tests/ghc-api/annotations/T10399.stdout | 146 ++++++++--------- testsuite/tests/ghc-api/annotations/Test10255.hs | 2 +- testsuite/tests/ghc-api/annotations/Test10278.hs | 2 +- testsuite/tests/ghc-api/annotations/Test10358.hs | 2 +- testsuite/tests/ghc-api/annotations/Test10399.hs | 3 + testsuite/tests/ghc-api/annotations/all.T | 14 +- testsuite/tests/ghc-api/annotations/boolFormula.hs | 106 +------------ .../tests/ghc-api/annotations/boolFormula.stdout | 2 + testsuite/tests/ghc-api/annotations/exampleTest.hs | 111 +------------ .../tests/ghc-api/annotations/exampleTest.stdout | 2 + testsuite/tests/ghc-api/annotations/t10255.hs | 105 +------------ testsuite/tests/ghc-api/annotations/t10268.hs | 106 +------------ testsuite/tests/ghc-api/annotations/t10269.hs | 106 +------------ testsuite/tests/ghc-api/annotations/t10278.hs | 117 +------------- testsuite/tests/ghc-api/annotations/t10280.hs | 106 +------------ testsuite/tests/ghc-api/annotations/t10307.hs | 105 +------------ testsuite/tests/ghc-api/annotations/t10309.hs | 105 +------------ testsuite/tests/ghc-api/annotations/t10312.hs | 105 +------------ testsuite/tests/ghc-api/annotations/t10354.hs | 117 +------------- testsuite/tests/ghc-api/annotations/t10357.hs | 117 +------------- testsuite/tests/ghc-api/annotations/t10358.hs | 117 +------------- testsuite/tests/ghc-api/annotations/t10396.hs | 117 +------------- testsuite/tests/ghc-api/annotations/t10399.hs | 117 +------------- 37 files changed, 269 insertions(+), 1806 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b57348fda1e5bab4ad6c5a13e2152af7e62f8ffb From git at git.haskell.org Tue Jun 2 21:15:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Jun 2015 21:15:31 +0000 (UTC) Subject: [commit: ghc] master: testsuite: mark test T9938 (#9938) as passing again (942a074) Message-ID: <20150602211531.1DB1A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/942a074ccb441320daae74fadf37b44e636dc102/ghc >--------------------------------------------------------------- commit 942a074ccb441320daae74fadf37b44e636dc102 Author: Austin Seipp Date: Tue Jun 2 16:07:30 2015 -0500 testsuite: mark test T9938 (#9938) as passing again Signed-off-by: Austin Seipp >--------------------------------------------------------------- 942a074ccb441320daae74fadf37b44e636dc102 testsuite/tests/driver/all.T | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/driver/all.T b/testsuite/tests/driver/all.T index 48ec649..8d4fcf5 100644 --- a/testsuite/tests/driver/all.T +++ b/testsuite/tests/driver/all.T @@ -411,7 +411,7 @@ test('write_interface_make', normal, run_command, ['$MAKE -s --no-print-director test('T9776', normal, compile_fail, ['-frule-check']) test('T9938', - [ extra_clean(['T9938.hi', 'T9938.o', 'T9938']), expect_broken(9938) ], + [ extra_clean(['T9938.hi', 'T9938.o', 'T9938']), normal ], run_command, ['$MAKE -s --no-print-directory T9938']) From git at git.haskell.org Tue Jun 2 21:15:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Jun 2015 21:15:33 +0000 (UTC) Subject: [commit: ghc] master: newTempName: Do not include pid in basename (7a82b77) Message-ID: <20150602211533.CCAC93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7a82b77691fb90c4af6863673f10e454a449739e/ghc >--------------------------------------------------------------- commit 7a82b77691fb90c4af6863673f10e454a449739e Author: Joachim Breitner Date: Tue Jun 2 16:12:43 2015 -0500 newTempName: Do not include pid in basename The filename of temporary files, especially the basename of C files, can end up in the output in some form, e.g. as part of linker debug information. In the interest of bit-wise exactly reproducible compilation (#4012), the basename of the temporary file no longer contains random information (it used to ontain the process id). This is ok, as the temporary directory used contains the pid (see getTempDir). This patch has been applied to the Debian package (version 7.10.1-5) and allowed a fully bit-wise reproducible build: https://reproducible.debian.net/rb-pkg/experimental/amd64/ghc.html Reviewed By: austin, rwbarton Differential Revision: https://phabricator.haskell.org/D910 GHC Trac Issues: #4012 >--------------------------------------------------------------- 7a82b77691fb90c4af6863673f10e454a449739e compiler/main/SysTools.hs | 19 ++++++++++++++----- 1 file changed, 14 insertions(+), 5 deletions(-) diff --git a/compiler/main/SysTools.hs b/compiler/main/SysTools.hs index d47925e..0b9537f 100644 --- a/compiler/main/SysTools.hs +++ b/compiler/main/SysTools.hs @@ -1083,8 +1083,7 @@ newTempSuffix dflags = atomicModifyIORef' (nextTempSuffix dflags) $ \n -> (n+1,n newTempName :: DynFlags -> Suffix -> IO FilePath newTempName dflags extn = do d <- getTempDir dflags - x <- getProcessID - findTempName (d "ghc" ++ show x ++ "_") + findTempName (d "ghc_") -- See Note [Deterministic base name] where findTempName :: FilePath -> IO FilePath findTempName prefix @@ -1099,12 +1098,11 @@ newTempName dflags extn newTempLibName :: DynFlags -> Suffix -> IO (FilePath, FilePath, String) newTempLibName dflags extn = do d <- getTempDir dflags - x <- getProcessID - findTempName d ("ghc" ++ show x ++ "_") + findTempName d ("ghc_") where findTempName :: FilePath -> String -> IO (FilePath, FilePath, String) findTempName dir prefix - = do n <- newTempSuffix dflags + = do n <- newTempSuffix dflags -- See Note [Deterministic base name] let libname = prefix ++ show n filename = dir "lib" ++ libname <.> extn b <- doesFileExist filename @@ -1157,6 +1155,17 @@ getTempDir dflags = do `catchIO` \e -> if isAlreadyExistsError e then mkTempDir prefix else ioError e +-- Note [Deterministic base name] +-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +-- +-- The filename of temporary files, especially the basename of C files, can end +-- up in the output in some form, e.g. as part of linker debug information. In the +-- interest of bit-wise exactly reproducible compilation (#4012), the basename of +-- the temporary file no longer contains random information (it used to contain +-- the process id). +-- +-- This is ok, as the temporary directory used contains the pid (see getTempDir). + addFilesToClean :: DynFlags -> [FilePath] -> IO () -- May include wildcards [used by DriverPipeline.run_phase SplitMangle] addFilesToClean dflags new_files From git at git.haskell.org Tue Jun 2 21:16:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Jun 2015 21:16:13 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: newTempName: Do not include pid in basename (1ff03e4) Message-ID: <20150602211613.B99093A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/1ff03e466c9edb46aa9e148ef1dc45933796083c/ghc >--------------------------------------------------------------- commit 1ff03e466c9edb46aa9e148ef1dc45933796083c Author: Joachim Breitner Date: Tue Jun 2 16:12:43 2015 -0500 newTempName: Do not include pid in basename The filename of temporary files, especially the basename of C files, can end up in the output in some form, e.g. as part of linker debug information. In the interest of bit-wise exactly reproducible compilation (#4012), the basename of the temporary file no longer contains random information (it used to ontain the process id). This is ok, as the temporary directory used contains the pid (see getTempDir). This patch has been applied to the Debian package (version 7.10.1-5) and allowed a fully bit-wise reproducible build: https://reproducible.debian.net/rb-pkg/experimental/amd64/ghc.html Reviewed By: austin, rwbarton Differential Revision: https://phabricator.haskell.org/D910 GHC Trac Issues: #4012 (cherry picked from commit 7a82b77691fb90c4af6863673f10e454a449739e) >--------------------------------------------------------------- 1ff03e466c9edb46aa9e148ef1dc45933796083c compiler/main/SysTools.hs | 19 ++++++++++++++----- 1 file changed, 14 insertions(+), 5 deletions(-) diff --git a/compiler/main/SysTools.hs b/compiler/main/SysTools.hs index 540d7c4..811b930 100644 --- a/compiler/main/SysTools.hs +++ b/compiler/main/SysTools.hs @@ -1083,8 +1083,7 @@ newTempSuffix dflags = atomicModifyIORef (nextTempSuffix dflags) $ \n -> (n+1,n) newTempName :: DynFlags -> Suffix -> IO FilePath newTempName dflags extn = do d <- getTempDir dflags - x <- getProcessID - findTempName (d "ghc" ++ show x ++ "_") + findTempName (d "ghc_") -- See Note [Deterministic base name] where findTempName :: FilePath -> IO FilePath findTempName prefix @@ -1099,12 +1098,11 @@ newTempName dflags extn newTempLibName :: DynFlags -> Suffix -> IO (FilePath, FilePath, String) newTempLibName dflags extn = do d <- getTempDir dflags - x <- getProcessID - findTempName d ("ghc" ++ show x ++ "_") + findTempName d ("ghc_") where findTempName :: FilePath -> String -> IO (FilePath, FilePath, String) findTempName dir prefix - = do n <- newTempSuffix dflags + = do n <- newTempSuffix dflags -- See Note [Deterministic base name] let libname = prefix ++ show n filename = dir "lib" ++ libname <.> extn b <- doesFileExist filename @@ -1157,6 +1155,17 @@ getTempDir dflags = do `catchIO` \e -> if isAlreadyExistsError e then mkTempDir prefix else ioError e +-- Note [Deterministic base name] +-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +-- +-- The filename of temporary files, especially the basename of C files, can end +-- up in the output in some form, e.g. as part of linker debug information. In the +-- interest of bit-wise exactly reproducible compilation (#4012), the basename of +-- the temporary file no longer contains random information (it used to contain +-- the process id). +-- +-- This is ok, as the temporary directory used contains the pid (see getTempDir). + addFilesToClean :: DynFlags -> [FilePath] -> IO () -- May include wildcards [used by DriverPipeline.run_phase SplitMangle] addFilesToClean dflags new_files From git at git.haskell.org Tue Jun 2 21:20:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Jun 2015 21:20:47 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Detabify a programlisting in the User's Guide (#10425) (77b55b8) Message-ID: <20150602212047.269363A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/77b55b8a34fba9c9cbfd5ea523930b93fc715efb/ghc >--------------------------------------------------------------- commit 77b55b8a34fba9c9cbfd5ea523930b93fc715efb Author: Reid Barton Date: Tue Jun 2 16:00:10 2015 -0400 Detabify a programlisting in the User's Guide (#10425) (cherry picked from commit 5688053a5c0a188c8bc94cd2c41d178b5c716535) >--------------------------------------------------------------- 77b55b8a34fba9c9cbfd5ea523930b93fc715efb docs/users_guide/bugs.xml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/docs/users_guide/bugs.xml b/docs/users_guide/bugs.xml index a23c75c..1d7903a 100644 --- a/docs/users_guide/bugs.xml +++ b/docs/users_guide/bugs.xml @@ -71,7 +71,7 @@ main = do args <- getArgs - if null args then return [] else do + if null args then return [] else do ps <- mapM process args mapM print ps From git at git.haskell.org Tue Jun 2 22:08:24 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Jun 2015 22:08:24 +0000 (UTC) Subject: [commit: ghc] master: Typofixes (2c4c627) Message-ID: <20150602220824.868313A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2c4c6271a3a175ae9d14062518e34892947c3e7b/ghc >--------------------------------------------------------------- commit 2c4c6271a3a175ae9d14062518e34892947c3e7b Author: Gabor Greif Date: Tue Jun 2 23:59:24 2015 +0200 Typofixes >--------------------------------------------------------------- 2c4c6271a3a175ae9d14062518e34892947c3e7b compiler/hsSyn/HsBinds.hs | 2 +- compiler/typecheck/TcBinds.hs | 12 ++++++------ compiler/typecheck/TcInstDcls.hs | 2 +- compiler/typecheck/TcPat.hs | 2 +- compiler/typecheck/TcRnDriver.hs | 4 ++-- 5 files changed, 11 insertions(+), 11 deletions(-) diff --git a/compiler/hsSyn/HsBinds.hs b/compiler/hsSyn/HsBinds.hs index 89ec1b7..d934418 100644 --- a/compiler/hsSyn/HsBinds.hs +++ b/compiler/hsSyn/HsBinds.hs @@ -333,7 +333,7 @@ This ultimately desugars to something like this: (fm::a->a,gm:Any->Any) -> fm ...similarly for g... -The abe_wrap field deals with impedence-matching between +The abe_wrap field deals with impedance-matching between (/\a b. case tup a b of { (f,g) -> f }) and the thing we really want, which may have fewer type variables. The action happens in TcBinds.mkExport. diff --git a/compiler/typecheck/TcBinds.hs b/compiler/typecheck/TcBinds.hs index 3096f2b..ac36908 100644 --- a/compiler/typecheck/TcBinds.hs +++ b/compiler/typecheck/TcBinds.hs @@ -651,7 +651,7 @@ mkExport prag_fn qtvs inferred_theta (poly_name, mb_sig, mono_id) ; traceTc "mkExport: check sig" (vcat [ ppr poly_name, ppr sel_poly_ty, ppr (idType poly_id) ]) - -- Perform the impedence-matching and ambiguity check + -- Perform the impedance-matching and ambiguity check -- right away. If it fails, we want to fail now (and recover -- in tcPolyBinds). If we delay checking, we get an error cascade. -- Remember we are in the tcPolyInfer case, so the type envt is @@ -786,9 +786,9 @@ Examples that might fail: - an inferred type that includes unboxed tuples However we don't do the ambiguity check (checkValidType omits it for -InfSigCtxt) because the impedence-matching stage, which follows +InfSigCtxt) because the impedance-matching stage, which follows immediately, will do it and we don't want two error messages. -Moreover, because of the impedence matching stage, the ambiguity-check +Moreover, because of the impedance matching stage, the ambiguity-check suggestion of -XAllowAmbiguiousTypes will not work. @@ -812,7 +812,7 @@ The types we really want for f and g are f :: forall a. (Eq a, Num a) => a -> Bool -> Bool g :: forall b. [b] -> Bool -> Bool -We can get these by "impedence matching": +We can get these by "impedance matching": tuple :: forall a b. (Eq a, Num a) => (a -> Bool -> Bool, [b] -> Bool -> Bool) tuple a b d1 d1 = let ...bind f_mono, g_mono in (f_mono, g_mono) @@ -822,9 +822,9 @@ We can get these by "impedence matching": Suppose the shared quantified tyvars are qtvs and constraints theta. Then we want to check that f's polytype is more polymorphic than forall qtvs. theta => f_mono_ty -and the proof is the impedence matcher. +and the proof is the impedance matcher. -Notice that the impedence matcher may do defaulting. See Trac #7173. +Notice that the impedance matcher may do defaulting. See Trac #7173. It also cleverly does an ambiguity check; for example, rejecting f :: F a -> a diff --git a/compiler/typecheck/TcInstDcls.hs b/compiler/typecheck/TcInstDcls.hs index f2607a4..9ce2d2f 100644 --- a/compiler/typecheck/TcInstDcls.hs +++ b/compiler/typecheck/TcInstDcls.hs @@ -1498,7 +1498,7 @@ that the type variables bound in the signature will scope over the body. What about the check that the instance method signature is more polymorphic than the instantiated class method type? We just do a tcSubType call in mkMethIds, and use the HsWrapper thus generated in -the method AbsBind. It's very like the tcSubType impedence-matching +the method AbsBind. It's very like the tcSubType impedance-matching call in mkExport. We have to pass the HsWrapper into tcMethodBody. -} diff --git a/compiler/typecheck/TcPat.hs b/compiler/typecheck/TcPat.hs index df2ad18..7e5b4e3 100644 --- a/compiler/typecheck/TcPat.hs +++ b/compiler/typecheck/TcPat.hs @@ -397,7 +397,7 @@ Two cases, dealt with by the LetPat case of tcPatBndr we want to bind a cloned, local version of the variable, with the type given by the pattern context, *not* by the signature (even if there is one; see Trac #7268). The mkExport part of the - generalisation step will do the checking and impedence matching + generalisation step will do the checking and impedance matching against the signature. * If for some some reason we are not generalising (plan = NoGen), the diff --git a/compiler/typecheck/TcRnDriver.hs b/compiler/typecheck/TcRnDriver.hs index b0d02f0..99309b0 100644 --- a/compiler/typecheck/TcRnDriver.hs +++ b/compiler/typecheck/TcRnDriver.hs @@ -734,7 +734,7 @@ checkHiBootIface' :: [ClsInst] -> TypeEnv -> [AvailInfo] -- Variant which doesn't require a full TcGblEnv; you could get the -- local components from another ModDetails. -- --- We return a list of "impedence-matching" bindings for the dfuns +-- We return a list of "impedance-matching" bindings for the dfuns -- defined in the hs-boot file, such as -- $fxEqT = $fEqT -- We need these because the module and hi-boot file might differ in @@ -759,7 +759,7 @@ checkHiBootIface' -- instances? We can't easily equate tycons... -- Check instance declarations - -- and generate an impedence-matching binding + -- and generate an impedance-matching binding ; mb_dfun_prs <- mapM check_inst boot_insts ; failIfErrsM From git at git.haskell.org Tue Jun 2 22:20:56 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Jun 2015 22:20:56 +0000 (UTC) Subject: [commit: ghc] master: Suggest -H to improve GC productivity, fixes #10474. (6adfb88) Message-ID: <20150602222056.BC5FA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6adfb88a4eb1988d5c674513545280fc66bf1627/ghc >--------------------------------------------------------------- commit 6adfb88a4eb1988d5c674513545280fc66bf1627 Author: Edward Z. Yang Date: Tue Jun 2 11:07:04 2015 -0700 Suggest -H to improve GC productivity, fixes #10474. Signed-off-by: Edward Z. Yang Test Plan: none Reviewers: rwbarton, austin Subscribers: bgamari, thomie Differential Revision: https://phabricator.haskell.org/D937 GHC Trac Issues: #10474 >--------------------------------------------------------------- 6adfb88a4eb1988d5c674513545280fc66bf1627 docs/users_guide/sooner.xml | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/docs/users_guide/sooner.xml b/docs/users_guide/sooner.xml index 68bcc61..41d04dd 100644 --- a/docs/users_guide/sooner.xml +++ b/docs/users_guide/sooner.xml @@ -459,11 +459,15 @@ f (Wibble x y) # ugly, and proud of it option RTS option) indicate that it's doing lots of garbage-collection (say, more than 20% of execution time), more memory might help—with the - -M<size> + -H<size> RTS option or -A<size> RTS option RTS options (see ). + linkend="rts-options-gc"/>). As a rule of thumb, try + setting to the amount of memory + you're willing to let your process consume, or perhaps try passing + without any argument to let GHC calculate + a value based on the amount of live data. From git at git.haskell.org Tue Jun 2 22:20:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 2 Jun 2015 22:20:59 +0000 (UTC) Subject: [commit: ghc] master: Remove outdated uBackpack docs. (7b6800c) Message-ID: <20150602222059.7DFFD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7b6800c5ab62cb10b3c1b7a85e40c77897cc366f/ghc >--------------------------------------------------------------- commit 7b6800c5ab62cb10b3c1b7a85e40c77897cc366f Author: Edward Z. Yang Date: Tue Jun 2 15:19:21 2015 -0700 Remove outdated uBackpack docs. Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- 7b6800c5ab62cb10b3c1b7a85e40c77897cc366f docs/backpack/ubackpack.pdf | Bin 200784 -> 0 bytes docs/backpack/ubackpack.tex | 381 -------------------------------------------- 2 files changed, 381 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 7b6800c5ab62cb10b3c1b7a85e40c77897cc366f From git at git.haskell.org Wed Jun 3 10:27:52 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 3 Jun 2015 10:27:52 +0000 (UTC) Subject: [commit: ghc] branch 'wip/aarch64-regd' created Message-ID: <20150603102752.571E43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/aarch64-regd Referencing: 6d3f174d56f04a583fc8429ca82df185d1786487 From git at git.haskell.org Wed Jun 3 10:27:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 3 Jun 2015 10:27:55 +0000 (UTC) Subject: [commit: ghc] wip/aarch64-regd: rts: Fix clobbered regs list for aarch64 StgRun (6d3f174) Message-ID: <20150603102755.0A8243A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/aarch64-regd Link : http://ghc.haskell.org/trac/ghc/changeset/6d3f174d56f04a583fc8429ca82df185d1786487/ghc >--------------------------------------------------------------- commit 6d3f174d56f04a583fc8429ca82df185d1786487 Author: Erik de Castro Lopo Date: Wed Jun 3 05:54:23 2015 +0000 rts: Fix clobbered regs list for aarch64 StgRun >--------------------------------------------------------------- 6d3f174d56f04a583fc8429ca82df185d1786487 rts/StgCRun.c | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/rts/StgCRun.c b/rts/StgCRun.c index 02ec532..419e65a 100644 --- a/rts/StgCRun.c +++ b/rts/StgCRun.c @@ -820,8 +820,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 Wed Jun 3 10:46:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 3 Jun 2015 10:46:16 +0000 (UTC) Subject: [commit: ghc] master: Refactor RdrName.Provenance, to fix #7672 (7ea156a) Message-ID: <20150603104616.7F7B53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7ea156ae3e1c66e59935f0eb877ea1a3f3bfd5b9/ghc >--------------------------------------------------------------- commit 7ea156ae3e1c66e59935f0eb877ea1a3f3bfd5b9 Author: Simon Peyton Jones Date: Wed Jun 3 11:43:53 2015 +0100 Refactor RdrName.Provenance, to fix #7672 Trac #7672 has a data type T in module A that is in scope *both* locally-bound *and* imported (with a qualified) name. The Provenance of a GlobalRdrElt simply couldn't express that before. Now you can. In doing so, I flattened out Provenance into GlobalRdrElt, so quite a lot of modules are touched in a not-very-interesting way. >--------------------------------------------------------------- 7ea156ae3e1c66e59935f0eb877ea1a3f3bfd5b9 compiler/basicTypes/RdrName.hs | 283 +++++++++++++++---------- compiler/deSugar/DsMonad.hs | 2 +- compiler/iface/IfaceEnv.hs | 8 +- compiler/main/DynamicLoading.hs | 6 +- compiler/main/HscTypes.hs | 5 +- compiler/main/InteractiveEval.hs | 20 +- compiler/rename/RnEnv.hs | 146 ++++++------- compiler/rename/RnNames.hs | 43 ++-- compiler/rename/RnPat.hs | 2 +- compiler/typecheck/TcCanonical.hs | 10 +- compiler/typecheck/TcDeriv.hs | 8 +- compiler/typecheck/TcRnDriver.hs | 11 +- testsuite/tests/rename/should_compile/T7672.hs | 4 +- testsuite/tests/rename/should_compile/all.T | 2 +- 14 files changed, 285 insertions(+), 265 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 7ea156ae3e1c66e59935f0eb877ea1a3f3bfd5b9 From git at git.haskell.org Wed Jun 3 16:56:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 3 Jun 2015 16:56:32 +0000 (UTC) Subject: [commit: ghc] master: Allow Any return in foreign prim, fixes #10460. (cd9c5c6) Message-ID: <20150603165632.839F03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cd9c5c6678e206ffcda955f66c26c7a4d89519c9/ghc >--------------------------------------------------------------- commit cd9c5c6678e206ffcda955f66c26c7a4d89519c9 Author: Edward Z. Yang Date: Mon Jun 1 11:30:17 2015 -0700 Allow Any return in foreign prim, fixes #10460. Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: simonpj, goldfire, austin Subscribers: bgamari, thomie Differential Revision: https://phabricator.haskell.org/D935 GHC Trac Issues: #10460 >--------------------------------------------------------------- cd9c5c6678e206ffcda955f66c26c7a4d89519c9 compiler/typecheck/TcType.hs | 6 ++++-- docs/users_guide/ffi-chap.xml | 3 ++- testsuite/tests/ffi/should_compile/T10460.hs | 5 +++++ testsuite/tests/ffi/should_compile/all.T | 1 + 4 files changed, 12 insertions(+), 3 deletions(-) diff --git a/compiler/typecheck/TcType.hs b/compiler/typecheck/TcType.hs index a131a05..485c1ba 100644 --- a/compiler/typecheck/TcType.hs +++ b/compiler/typecheck/TcType.hs @@ -1658,9 +1658,11 @@ isFFIPrimArgumentTy dflags ty isFFIPrimResultTy :: DynFlags -> Type -> Validity -- Checks for valid result type for a 'foreign import prim' --- Currently it must be an unlifted type, including unboxed tuples. +-- Currently it must be an unlifted type, including unboxed tuples, +-- or the well-known type Any. isFFIPrimResultTy dflags ty - = checkRepTyCon (legalFIPrimResultTyCon dflags) ty + | isAnyTy ty = IsValid + | otherwise = checkRepTyCon (legalFIPrimResultTyCon dflags) ty isFunPtrTy :: Type -> Bool isFunPtrTy ty diff --git a/docs/users_guide/ffi-chap.xml b/docs/users_guide/ffi-chap.xml index a5ab9e7..38db2bf 100644 --- a/docs/users_guide/ffi-chap.xml +++ b/docs/users_guide/ffi-chap.xml @@ -76,7 +76,8 @@ OK: internal GHC calling convention. The arguments and results must be unboxed types, except that an argument may be of type Any (by way of unsafeCoerce#) - and the result type is allowed to be an unboxed tuple. + and the result type is allowed to be an unboxed tuple or the + type Any. This feature is not intended for diff --git a/testsuite/tests/ffi/should_compile/T10460.hs b/testsuite/tests/ffi/should_compile/T10460.hs new file mode 100644 index 0000000..7481453 --- /dev/null +++ b/testsuite/tests/ffi/should_compile/T10460.hs @@ -0,0 +1,5 @@ +{-# LANGUAGE GHCForeignImportPrim #-} +module T10460 where +import GHC.Exts +-- don't link me! +foreign import prim "f" f :: Any -> Any diff --git a/testsuite/tests/ffi/should_compile/all.T b/testsuite/tests/ffi/should_compile/all.T index 84c7e86..ec6326b 100644 --- a/testsuite/tests/ffi/should_compile/all.T +++ b/testsuite/tests/ffi/should_compile/all.T @@ -29,3 +29,4 @@ test('T3624', normal, compile, ['']) test('T3742', normal, compile, ['']) test('cc015', normal, compile, ['']) test('cc016', normal, compile, ['']) +test('T10460', normal, compile, ['']) From git at git.haskell.org Wed Jun 3 17:39:08 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 3 Jun 2015 17:39:08 +0000 (UTC) Subject: [commit: ghc] master: Move liftData and use it as a default definition for Lift. (08558a3) Message-ID: <20150603173908.B94FC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/08558a30c17572453e0f8bcbb483a8cb7f00eafa/ghc >--------------------------------------------------------------- commit 08558a30c17572453e0f8bcbb483a8cb7f00eafa Author: Edward Z. Yang Date: Thu May 28 19:04:37 2015 -0700 Move liftData and use it as a default definition for Lift. Summary: This should make it a lot easier to define Lift instances. See https://mail.haskell.org/pipermail/libraries/2015-May/025728.html for motivating discussion. I needed to muck out some code from Quote into Syntax to get the definition in the right place; but I would argue that code never really belonged in Quote to begin with. Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: austin, ekmett, goldfire Subscribers: bgamari, thomie Differential Revision: https://phabricator.haskell.org/D923 >--------------------------------------------------------------- 08558a30c17572453e0f8bcbb483a8cb7f00eafa docs/users_guide/7.12.1-notes.xml | 12 +++ .../template-haskell/Language/Haskell/TH/Quote.hs | 77 +--------------- .../template-haskell/Language/Haskell/TH/Syntax.hs | 100 ++++++++++++++++++++- 3 files changed, 113 insertions(+), 76 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 08558a30c17572453e0f8bcbb483a8cb7f00eafa From git at git.haskell.org Wed Jun 3 20:40:02 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 3 Jun 2015 20:40:02 +0000 (UTC) Subject: [commit: ghc] master: typo: 'Ture' / 'True' (942cfa4) Message-ID: <20150603204002.909EE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/942cfa4e3257347dfc4644ce1a8a28db1fb0aee0/ghc >--------------------------------------------------------------- commit 942cfa4e3257347dfc4644ce1a8a28db1fb0aee0 Author: Sergei Trofimovich Date: Wed Jun 3 21:39:10 2015 +0100 typo: 'Ture' / 'True' Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- 942cfa4e3257347dfc4644ce1a8a28db1fb0aee0 compiler/basicTypes/RdrName.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/basicTypes/RdrName.hs b/compiler/basicTypes/RdrName.hs index b4deeca..b6ae072 100644 --- a/compiler/basicTypes/RdrName.hs +++ b/compiler/basicTypes/RdrName.hs @@ -449,7 +449,7 @@ i.e. how the Name came to be in scope. It can be in scope two ways: - gre_imp: a list of all the imports that brought it into scope It's an INVARIANT that you have one or the other; that is, either -gre_lcl is Ture, or gre_imp is non-empty. +gre_lcl is True, or gre_imp is non-empty. It is just possible to have *both* if there is a module loop: a Name is defined locally in A, and also brought into scope by importing a From git at git.haskell.org Thu Jun 4 13:25:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 4 Jun 2015 13:25:27 +0000 (UTC) Subject: [commit: ghc] master: Travis: Send notifications to author and commiter (21d7c85) Message-ID: <20150604132527.0E9753A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/21d7c85d4baa0fdf7bab89e5c356c1f638d0d607/ghc >--------------------------------------------------------------- commit 21d7c85d4baa0fdf7bab89e5c356c1f638d0d607 Author: Joachim Breitner Date: Thu Jun 4 15:22:47 2015 +0200 Travis: Send notifications to author and commiter This is the Travis default. It should only spam people who have an GitHub account and are a member of the ghc organization on GitHub, as noted by thomie on https://phabricator.haskell.org/D939#25497. Let's see how that works out. >--------------------------------------------------------------- 21d7c85d4baa0fdf7bab89e5c356c1f638d0d607 .travis.yml | 5 ----- 1 file changed, 5 deletions(-) diff --git a/.travis.yml b/.travis.yml index c740515..d2e961d 100644 --- a/.travis.yml +++ b/.travis.yml @@ -1,11 +1,6 @@ git: submodules: false -notifications: - email: - - mail at joachim-breitner.de - - ghc-builds at haskell.org - env: - DEBUG_STAGE2=YES - DEBUG_STAGE2=NO From git at git.haskell.org Thu Jun 4 19:45:53 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 4 Jun 2015 19:45:53 +0000 (UTC) Subject: [commit: ghc] master: ghc-pkg support query by package-key, fixes #9507 (c69b69d) Message-ID: <20150604194553.EA9793A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c69b69d2cda890e6f3f6aa1fd4092421e6053b89/ghc >--------------------------------------------------------------- commit c69b69d2cda890e6f3f6aa1fd4092421e6053b89 Author: Edward Z. Yang Date: Wed Jun 3 10:55:58 2015 -0700 ghc-pkg support query by package-key, fixes #9507 Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: austin Subscribers: bgamari, thomie Differential Revision: https://phabricator.haskell.org/D946 GHC Trac Issues: #9507 >--------------------------------------------------------------- c69b69d2cda890e6f3f6aa1fd4092421e6053b89 utils/ghc-pkg/Main.hs | 42 ++++++++++++++++++++++++++++++------------ 1 file changed, 30 insertions(+), 12 deletions(-) diff --git a/utils/ghc-pkg/Main.hs b/utils/ghc-pkg/Main.hs index 1389723..b7e617e 100644 --- a/utils/ghc-pkg/Main.hs +++ b/utils/ghc-pkg/Main.hs @@ -137,6 +137,7 @@ data Flag | FlagNoUserDb | FlagVerbosity (Maybe String) | FlagIPId + | FlagPackageKey deriving Eq flags :: [OptDescr Flag] @@ -181,6 +182,8 @@ flags = [ "ignore case for substring matching", Option [] ["ipid"] (NoArg FlagIPId) "interpret package arguments as installed package IDs", + Option [] ["package-key"] (NoArg FlagPackageKey) + "interpret package arguments as installed package keys", Option ['v'] ["verbose"] (OptArg FlagVerbosity "Verbosity") "verbosity level (0-2, default 1)" ] @@ -317,6 +320,12 @@ substProg prog (c:xs) = c : substProg prog xs data Force = NoForce | ForceFiles | ForceAll | CannotForce deriving (Eq,Ord) +-- | Enum flag representing argument type +data AsPackageArg + = AsIpid + | AsPackageKey + | AsDefault + -- | Represents how a package may be specified by a user on the command line. data PackageArg -- | A package identifier foo-0.1; the version might be a glob. @@ -324,6 +333,9 @@ data PackageArg -- | An installed package ID foo-0.1-HASH. This is guaranteed to uniquely -- match a single entry in the package database. | IPId InstalledPackageId + -- | A package key foo_HASH. This is also guaranteed to uniquely match + -- a single entry in the package database + | PkgKey PackageKey -- | A glob against the package name. The first string is the literal -- glob, the second is a function which returns @True@ if the argument -- matches. @@ -338,7 +350,9 @@ runit verbosity cli nonopts = do | FlagForce `elem` cli = ForceAll | FlagForceFiles `elem` cli = ForceFiles | otherwise = NoForce - as_ipid = FlagIPId `elem` cli + as_arg | FlagIPId `elem` cli = AsIpid + | FlagPackageKey `elem` cli = AsPackageKey + | otherwise = AsDefault multi_instance = FlagMultiInstance `elem` cli expand_env_vars= FlagExpandEnvVars `elem` cli mexpand_pkgroot= foldl' accumExpandPkgroot Nothing cli @@ -415,25 +429,25 @@ runit verbosity cli nonopts = do multi_instance expand_env_vars True force ["unregister", pkgarg_str] -> do - pkgarg <- readPackageArg as_ipid pkgarg_str + pkgarg <- readPackageArg as_arg pkgarg_str unregisterPackage pkgarg verbosity cli force ["expose", pkgarg_str] -> do - pkgarg <- readPackageArg as_ipid pkgarg_str + pkgarg <- readPackageArg as_arg pkgarg_str exposePackage pkgarg verbosity cli force ["hide", pkgarg_str] -> do - pkgarg <- readPackageArg as_ipid pkgarg_str + pkgarg <- readPackageArg as_arg pkgarg_str hidePackage pkgarg verbosity cli force ["trust", pkgarg_str] -> do - pkgarg <- readPackageArg as_ipid pkgarg_str + pkgarg <- readPackageArg as_arg pkgarg_str trustPackage pkgarg verbosity cli force ["distrust", pkgarg_str] -> do - pkgarg <- readPackageArg as_ipid pkgarg_str + pkgarg <- readPackageArg as_arg pkgarg_str distrustPackage pkgarg verbosity cli force ["list"] -> do listPackages verbosity cli Nothing Nothing ["list", pkgarg_str] -> case substringCheck pkgarg_str of - Nothing -> do pkgarg <- readPackageArg as_ipid pkgarg_str + Nothing -> do pkgarg <- readPackageArg as_arg pkgarg_str listPackages verbosity cli (Just pkgarg) Nothing Just m -> listPackages verbosity cli (Just (Substring pkgarg_str m)) Nothing @@ -447,13 +461,13 @@ runit verbosity cli nonopts = do latestPackage verbosity cli pkgid ["describe", pkgid_str] -> do pkgarg <- case substringCheck pkgid_str of - Nothing -> readPackageArg as_ipid pkgid_str + Nothing -> readPackageArg as_arg pkgid_str Just m -> return (Substring pkgid_str m) describePackage verbosity cli pkgarg (fromMaybe False mexpand_pkgroot) ["field", pkgid_str, fields] -> do pkgarg <- case substringCheck pkgid_str of - Nothing -> readPackageArg as_ipid pkgid_str + Nothing -> readPackageArg as_arg pkgid_str Just m -> return (Substring pkgid_str m) describeField verbosity cli pkgarg (splitFields fields) (fromMaybe True mexpand_pkgroot) @@ -489,10 +503,12 @@ parseGlobPackageId = _ <- string "-*" return (PackageIdentifier{ pkgName = n, pkgVersion = globVersion })) -readPackageArg :: Bool -> String -> IO PackageArg -readPackageArg True str = +readPackageArg :: AsPackageArg -> String -> IO PackageArg +readPackageArg AsIpid str = parseCheck (IPId `fmap` parse) str "installed package id" -readPackageArg False str = Id `fmap` readGlobPkgId str +readPackageArg AsPackageKey str = + parseCheck (PkgKey `fmap` parse) str "package key" +readPackageArg AsDefault str = Id `fmap` readGlobPkgId str -- globVersion means "all versions" globVersion :: Version @@ -1384,6 +1400,7 @@ findPackagesByDB db_stack pkgarg ps -> return ps where pkg_msg (Id pkgid) = display pkgid + pkg_msg (PkgKey pk) = display pk pkg_msg (IPId ipid) = display ipid pkg_msg (Substring pkgpat _) = "matching " ++ pkgpat @@ -1398,6 +1415,7 @@ realVersion pkgid = versionBranch (pkgVersion pkgid) /= [] matchesPkg :: PackageArg -> InstalledPackageInfo -> Bool (Id pid) `matchesPkg` pkg = pid `matches` sourcePackageId pkg +(PkgKey pk) `matchesPkg` pkg = pk == packageKey pkg (IPId ipid) `matchesPkg` pkg = ipid == installedPackageId pkg (Substring _ m) `matchesPkg` pkg = m (display (sourcePackageId pkg)) From git at git.haskell.org Thu Jun 4 19:55:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 4 Jun 2015 19:55:27 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Give a hint when a TH splice has a bad package key, partially fixes #10279 (e59fe3e) Message-ID: <20150604195527.4F2DC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/e59fe3ee5a302a0975c1d4912f799844e9f22e50/ghc >--------------------------------------------------------------- commit e59fe3ee5a302a0975c1d4912f799844e9f22e50 Author: Edward Z. Yang Date: Mon Apr 20 14:02:36 2015 -0700 Give a hint when a TH splice has a bad package key, partially fixes #10279 Previously, if we got a package key in our splice, we'd give a very unhelpful error message saying we couldn't find a package 'base-4.7.0.1', despite there being a package with that source package ID. Really, we couldn't find a package with that *key*, so clarify, and also tell the user what the real package key is. Signed-off-by: Edward Z. Yang (cherry picked from commit bf4f3e653407d02593a69618fb199b2e2d529c92) >--------------------------------------------------------------- e59fe3ee5a302a0975c1d4912f799844e9f22e50 compiler/main/Finder.hs | 16 ++++++++++++++-- testsuite/tests/th/T10279.hs | 10 ++++++++++ testsuite/tests/th/T10279.stderr | 8 ++++++++ testsuite/tests/th/all.T | 1 + 4 files changed, 33 insertions(+), 2 deletions(-) diff --git a/compiler/main/Finder.hs b/compiler/main/Finder.hs index 71b4e97..09bf830 100644 --- a/compiler/main/Finder.hs +++ b/compiler/main/Finder.hs @@ -590,8 +590,8 @@ cantFindErr cannot_find _ dflags mod_name find_result more_info = case find_result of NoPackage pkg - -> ptext (sLit "no package matching") <+> quotes (ppr pkg) <+> - ptext (sLit "was found") + -> ptext (sLit "no package key matching") <+> quotes (ppr pkg) <+> + ptext (sLit "was found") $$ looks_like_srcpkgid pkg NotFound { fr_paths = files, fr_pkg = mb_pkg , fr_mods_hidden = mod_hiddens, fr_pkgs_hidden = pkg_hiddens @@ -652,6 +652,18 @@ cantFindErr cannot_find _ dflags mod_name find_result ptext (sLit "to the build-depends in your .cabal file.") | otherwise = Outputable.empty + looks_like_srcpkgid :: PackageKey -> SDoc + looks_like_srcpkgid pk + -- Unsafely coerce a package key FastString into a source package ID + -- FastString and see if it means anything. + | (pkg:pkgs) <- searchPackageId dflags (SourcePackageId (packageKeyFS pk)) + = parens (text "This package key looks like the source package ID;" $$ + text "the real package key is" <+> quotes (ftext (packageKeyFS (packageKey pkg))) $$ + (if null pkgs then Outputable.empty + else text "and" <+> int (length pkgs) <+> text "other candidates")) + -- Todo: also check if it looks like a package name! + | otherwise = Outputable.empty + mod_hidden pkg = ptext (sLit "it is a hidden module in the package") <+> quotes (ppr pkg) diff --git a/testsuite/tests/th/T10279.hs b/testsuite/tests/th/T10279.hs new file mode 100644 index 0000000..fbc2dbb --- /dev/null +++ b/testsuite/tests/th/T10279.hs @@ -0,0 +1,10 @@ +module T10279 where +import Language.Haskell.TH +import Language.Haskell.TH.Syntax + +-- NB: rts-1.0 is used here because it doesn't change. +-- You do need to pick the right version number, otherwise the +-- error message doesn't recognize it as a source package ID, +-- (This is OK, since it will look obviously wrong when they +-- try to find the package in their package database.) +blah = $(conE (Name (mkOccName "Foo") (NameG VarName (mkPkgName "rts-1.0") (mkModName "A")))) diff --git a/testsuite/tests/th/T10279.stderr b/testsuite/tests/th/T10279.stderr new file mode 100644 index 0000000..9c72bf9 --- /dev/null +++ b/testsuite/tests/th/T10279.stderr @@ -0,0 +1,8 @@ + +T10279.hs:10:10: + Failed to load interface for ?A? + no package key matching ?rts-1.0? was found + (This package key looks like the source package ID; + the real package key is ?rts?) + In the expression: (rts-1.0:A.Foo) + In an equation for ?blah?: blah = (rts-1.0:A.Foo) diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 335363b..bc6ca5d 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -359,3 +359,4 @@ test('T8031', normal, compile, ['-v0']) test('T8624', normal, run_command, ['$MAKE -s --no-print-directory T8624']) test('TH_Lift', normal, compile, ['-v0']) test('T10019', normal, ghci_script, ['T10019.script']) +test('T10279', normal, compile_fail, ['-v0']) From git at git.haskell.org Thu Jun 4 20:00:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 4 Jun 2015 20:00:26 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: ghc-pkg support query by package-key, fixes #9507 (36c3a51) Message-ID: <20150604200026.37A3D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/36c3a51413baa531f40ccb7e039cb2077d56f121/ghc >--------------------------------------------------------------- commit 36c3a51413baa531f40ccb7e039cb2077d56f121 Author: Edward Z. Yang Date: Wed Jun 3 10:55:58 2015 -0700 ghc-pkg support query by package-key, fixes #9507 Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: austin Subscribers: bgamari, thomie Differential Revision: https://phabricator.haskell.org/D946 GHC Trac Issues: #9507 (cherry picked from commit c69b69d2cda890e6f3f6aa1fd4092421e6053b89) >--------------------------------------------------------------- 36c3a51413baa531f40ccb7e039cb2077d56f121 utils/ghc-pkg/Main.hs | 42 ++++++++++++++++++++++++++++++------------ 1 file changed, 30 insertions(+), 12 deletions(-) diff --git a/utils/ghc-pkg/Main.hs b/utils/ghc-pkg/Main.hs index 0493866..8a6d712 100644 --- a/utils/ghc-pkg/Main.hs +++ b/utils/ghc-pkg/Main.hs @@ -131,6 +131,7 @@ data Flag | FlagNoUserDb | FlagVerbosity (Maybe String) | FlagIPId + | FlagPackageKey deriving Eq flags :: [OptDescr Flag] @@ -177,6 +178,8 @@ flags = [ "ignore case for substring matching", Option [] ["ipid"] (NoArg FlagIPId) "interpret package arguments as installed package IDs", + Option [] ["package-key"] (NoArg FlagPackageKey) + "interpret package arguments as installed package keys", Option ['v'] ["verbose"] (OptArg FlagVerbosity "Verbosity") "verbosity level (0-2, default 1)" ] @@ -313,6 +316,12 @@ substProg prog (c:xs) = c : substProg prog xs data Force = NoForce | ForceFiles | ForceAll | CannotForce deriving (Eq,Ord) +-- | Enum flag representing argument type +data AsPackageArg + = AsIpid + | AsPackageKey + | AsDefault + -- | Represents how a package may be specified by a user on the command line. data PackageArg -- | A package identifier foo-0.1; the version might be a glob. @@ -320,6 +329,9 @@ data PackageArg -- | An installed package ID foo-0.1-HASH. This is guaranteed to uniquely -- match a single entry in the package database. | IPId InstalledPackageId + -- | A package key foo_HASH. This is also guaranteed to uniquely match + -- a single entry in the package database + | PkgKey PackageKey -- | A glob against the package name. The first string is the literal -- glob, the second is a function which returns @True@ if the the argument -- matches. @@ -334,7 +346,9 @@ runit verbosity cli nonopts = do | FlagForce `elem` cli = ForceAll | FlagForceFiles `elem` cli = ForceFiles | otherwise = NoForce - as_ipid = FlagIPId `elem` cli + as_arg | FlagIPId `elem` cli = AsIpid + | FlagPackageKey `elem` cli = AsPackageKey + | otherwise = AsDefault auto_ghci_libs = FlagAutoGHCiLibs `elem` cli multi_instance = FlagMultiInstance `elem` cli expand_env_vars= FlagExpandEnvVars `elem` cli @@ -412,25 +426,25 @@ runit verbosity cli nonopts = do auto_ghci_libs multi_instance expand_env_vars True force ["unregister", pkgarg_str] -> do - pkgarg <- readPackageArg as_ipid pkgarg_str + pkgarg <- readPackageArg as_arg pkgarg_str unregisterPackage pkgarg verbosity cli force ["expose", pkgarg_str] -> do - pkgarg <- readPackageArg as_ipid pkgarg_str + pkgarg <- readPackageArg as_arg pkgarg_str exposePackage pkgarg verbosity cli force ["hide", pkgarg_str] -> do - pkgarg <- readPackageArg as_ipid pkgarg_str + pkgarg <- readPackageArg as_arg pkgarg_str hidePackage pkgarg verbosity cli force ["trust", pkgarg_str] -> do - pkgarg <- readPackageArg as_ipid pkgarg_str + pkgarg <- readPackageArg as_arg pkgarg_str trustPackage pkgarg verbosity cli force ["distrust", pkgarg_str] -> do - pkgarg <- readPackageArg as_ipid pkgarg_str + pkgarg <- readPackageArg as_arg pkgarg_str distrustPackage pkgarg verbosity cli force ["list"] -> do listPackages verbosity cli Nothing Nothing ["list", pkgarg_str] -> case substringCheck pkgarg_str of - Nothing -> do pkgarg <- readPackageArg as_ipid pkgarg_str + Nothing -> do pkgarg <- readPackageArg as_arg pkgarg_str listPackages verbosity cli (Just pkgarg) Nothing Just m -> listPackages verbosity cli (Just (Substring pkgarg_str m)) Nothing @@ -444,13 +458,13 @@ runit verbosity cli nonopts = do latestPackage verbosity cli pkgid ["describe", pkgid_str] -> do pkgarg <- case substringCheck pkgid_str of - Nothing -> readPackageArg as_ipid pkgid_str + Nothing -> readPackageArg as_arg pkgid_str Just m -> return (Substring pkgid_str m) describePackage verbosity cli pkgarg (fromMaybe False mexpand_pkgroot) ["field", pkgid_str, fields] -> do pkgarg <- case substringCheck pkgid_str of - Nothing -> readPackageArg as_ipid pkgid_str + Nothing -> readPackageArg as_arg pkgid_str Just m -> return (Substring pkgid_str m) describeField verbosity cli pkgarg (splitFields fields) (fromMaybe True mexpand_pkgroot) @@ -486,10 +500,12 @@ parseGlobPackageId = _ <- string "-*" return (PackageIdentifier{ pkgName = n, pkgVersion = globVersion })) -readPackageArg :: Bool -> String -> IO PackageArg -readPackageArg True str = +readPackageArg :: AsPackageArg -> String -> IO PackageArg +readPackageArg AsIpid str = parseCheck (IPId `fmap` parse) str "installed package id" -readPackageArg False str = Id `fmap` readGlobPkgId str +readPackageArg AsPackageKey str = + parseCheck (PkgKey `fmap` parse) str "package key" +readPackageArg AsDefault str = Id `fmap` readGlobPkgId str -- globVersion means "all versions" globVersion :: Version @@ -1310,6 +1326,7 @@ findPackagesByDB db_stack pkgarg ps -> return ps where pkg_msg (Id pkgid) = display pkgid + pkg_msg (PkgKey pk) = display pk pkg_msg (IPId ipid) = display ipid pkg_msg (Substring pkgpat _) = "matching " ++ pkgpat @@ -1324,6 +1341,7 @@ realVersion pkgid = versionBranch (pkgVersion pkgid) /= [] matchesPkg :: PackageArg -> InstalledPackageInfo -> Bool (Id pid) `matchesPkg` pkg = pid `matches` sourcePackageId pkg +(PkgKey pk) `matchesPkg` pkg = pk == packageKey pkg (IPId ipid) `matchesPkg` pkg = ipid == installedPackageId pkg (Substring _ m) `matchesPkg` pkg = m (display (sourcePackageId pkg)) From git at git.haskell.org Thu Jun 4 22:00:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 4 Jun 2015 22:00:57 +0000 (UTC) Subject: [commit: ghc] master: Re-center perf numbers for haddock.compiler (d8f66f1) Message-ID: <20150604220057.B5F3C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d8f66f1b5fcd79a42141b98dd49d3aef202af78c/ghc >--------------------------------------------------------------- commit d8f66f1b5fcd79a42141b98dd49d3aef202af78c Author: Thomas Miedema Date: Thu Jun 4 01:42:29 2015 +0200 Re-center perf numbers for haddock.compiler Summary: Phabricator/Harbormaster measured the following allocation numbers for haddock.compiler: Expected: 33562468736 June 2nd [1]: 36740649320 Upper bound: 36918715610 June 3rd [2]: 36956620504 So although this test didn't start failing until June 2nd/3rd, the biggest increase in allocation must have occured sometime before that. [1] 2f0011aca137055f139bed484302679c10238d55 [2] 942cfa4e3257347dfc4644ce1a8a28db1fb0aee0 Test Plan: validate Reviewers: austin Subscribers: bgamari, thomie Differential Revision: https://phabricator.haskell.org/D948 >--------------------------------------------------------------- d8f66f1b5fcd79a42141b98dd49d3aef202af78c 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 5d1e6a0..aaa7c55 100644 --- a/testsuite/tests/perf/haddock/all.T +++ b/testsuite/tests/perf/haddock/all.T @@ -86,7 +86,7 @@ test('haddock.Cabal', test('haddock.compiler', [unless(in_tree_compiler(), skip), req_haddock ,stats_num_field('bytes allocated', - [(wordsize(64), 33562468736, 10) + [(wordsize(64), 36740649320, 10) # 2012P-08-14: 26070600504 (amd64/Linux) # 2012-08-29: 26353100288 (amd64/Linux, new CG) # 2012-09-18: 26882813032 (amd64/Linux) @@ -95,6 +95,7 @@ test('haddock.compiler', # 2012-11-27: 28708374824 (amd64/Linux) # 2014-09-10: 30353349160 (amd64/Linux) post-AMP cleanup # 2014-11-22: 33562468736 (amd64/Linux) + # 2015-06-02: 36740649320 (amd64/Linux) unknown cause ,(platform('i386-unknown-mingw32'), 902576468, 10) # 2012-10-30: 13773051312 (x86/Windows) From git at git.haskell.org Thu Jun 4 22:01:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 4 Jun 2015 22:01:00 +0000 (UTC) Subject: [commit: ghc] master: ghc-cabal: don't warn about missing cabal fields (14652b5) Message-ID: <20150604220100.9CF4A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/14652b519eca12411e92c28cd06de32612b0973a/ghc >--------------------------------------------------------------- commit 14652b519eca12411e92c28cd06de32612b0973a Author: Thomas Miedema Date: Mon Jun 1 19:58:43 2015 +0200 ghc-cabal: don't warn about missing cabal fields Only print and exit on errors. Warnings of the type 'PackageDistSuspicious' are not very useful. The following show up in the build logs currently: * The 'license' field is missing. * No 'maintainer' field * No 'category' field * 'ghc-options: -O2' is rarely needed. Check that it is giving a real benefit and not just imposing longer compile times on your users. Differential Revision: https://phabricator.haskell.org/D944 >--------------------------------------------------------------- 14652b519eca12411e92c28cd06de32612b0973a utils/ghc-cabal/Main.hs | 8 +++----- 1 file changed, 3 insertions(+), 5 deletions(-) diff --git a/utils/ghc-cabal/Main.hs b/utils/ghc-cabal/Main.hs index f066251..4ae85ec 100644 --- a/utils/ghc-cabal/Main.hs +++ b/utils/ghc-cabal/Main.hs @@ -114,11 +114,9 @@ doCheck directory $ do let verbosity = normal gpdFile <- defaultPackageDesc verbosity gpd <- readPackageDescription verbosity gpdFile - case partition isFailure $ checkPackage gpd Nothing of - ([], []) -> return () - ([], warnings) -> mapM_ print warnings - (errs, _) -> do mapM_ print errs - exitWith (ExitFailure 1) + case filter isFailure $ checkPackage gpd Nothing of + [] -> return () + errs -> mapM_ print errs >> exitWith (ExitFailure 1) where isFailure (PackageDistSuspicious {}) = False isFailure _ = True From git at git.haskell.org Thu Jun 4 22:01:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 4 Jun 2015 22:01:03 +0000 (UTC) Subject: [commit: ghc] master: Build: make configure and ghc-pkg a bit less chatty (75c6e06) Message-ID: <20150604220103.9CDCF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/75c6e0684dda585c37b4ac254cd7a13537a59a91/ghc >--------------------------------------------------------------- commit 75c6e0684dda585c37b4ac254cd7a13537a59a91 Author: Thomas Miedema Date: Mon Jun 1 14:16:27 2015 +0200 Build: make configure and ghc-pkg a bit less chatty Only when V=0. Differential Revision: https://phabricator.haskell.org/D943 >--------------------------------------------------------------- 75c6e0684dda585c37b4ac254cd7a13537a59a91 rules/build-package-data.mk | 11 +++++++++++ 1 file changed, 11 insertions(+) diff --git a/rules/build-package-data.mk b/rules/build-package-data.mk index 817bf8d..edf3216 100644 --- a/rules/build-package-data.mk +++ b/rules/build-package-data.mk @@ -18,6 +18,17 @@ $(call profStart, build-package-data($1,$2,$3)) # $2 = distdir # $3 = GHC stage to use (0 == bootstrapping compiler) +ifeq "$(V)" "0" +$1_$2_CONFIGURE_OPTS += -v0 --configure-option=--quiet + +# Cabal always passes --with-compiler and --with-gcc to library configure +# scripts, resulting in the following useless (for us) warning in the logs: +# "configure: WARNING: unrecognized options: --with-compiler, --with-gcc" +$1_$2_CONFIGURE_OPTS += --configure-option=--disable-option-checking + +$1_$2_GHC_PKG_OPTS += -v0 +endif + $1_$2_CONFIGURE_OPTS += --disable-library-for-ghci ifeq "$$(filter v,$$($1_$2_WAYS))" "v" $1_$2_CONFIGURE_OPTS += --enable-library-vanilla From git at git.haskell.org Thu Jun 4 22:01:06 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 4 Jun 2015 22:01:06 +0000 (UTC) Subject: [commit: ghc] master: Build: ./boot && ./configure && make sdist (#8723) (092082e) Message-ID: <20150604220106.F1EA13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/092082e7583c8170ae41ef8d01a554db34f91bb3/ghc >--------------------------------------------------------------- commit 092082e7583c8170ae41ef8d01a554db34f91bb3 Author: Thomas Miedema Date: Wed May 27 20:54:36 2015 +0200 Build: ./boot && ./configure && make sdist (#8723) Make it possible to run `make sdist` right after configure, without completing a complete build first. Test Plan: I compared the contents of the created `.tar.bz2` files in the `sdistprep` directory, after running `make sdist` both before and after completing a full build, using `diff -r`. There weren't any differences (after applying the patches from D914). Note that the `.tar.bz2` files were not exactly the same size, but they aren't either when tarring and bzipping the same directory twice. It seems tarring and bzipping is not deterministic (on my system). Differential Revision: https://phabricator.haskell.org/D917 >--------------------------------------------------------------- 092082e7583c8170ae41ef8d01a554db34f91bb3 Makefile | 30 ++++++++++++++++++++++++- ghc.mk | 47 ++++++++++++++++++++-------------------- libraries/integer-gmp/gmp/ghc.mk | 5 ++++- rules/sdist-ghc-file.mk | 46 +++++++++++++++++++++++++++++++++++++++ 4 files changed, 102 insertions(+), 26 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 092082e7583c8170ae41ef8d01a554db34f91bb3 From git at git.haskell.org Thu Jun 4 22:01:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 4 Jun 2015 22:01:09 +0000 (UTC) Subject: [commit: ghc] master: Testsuite: add/fix cleanup for certain tests (e340f6e) Message-ID: <20150604220109.D764D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e340f6eccc9d6d8f0a11c56c312570060c245946/ghc >--------------------------------------------------------------- commit e340f6eccc9d6d8f0a11c56c312570060c245946 Author: Thomas Miedema Date: Thu May 28 22:00:00 2015 +0200 Testsuite: add/fix cleanup for certain tests * extra_clean argument should be a list Add an assert to prevent regressions. * properly clean package conf direcories They are directories now, which was causing problems. * properly clean write_interface_* tests We were getting these errors: [Errno 21] Is a directory: './driver/write_interface_oneshot' [Errno 39] Directory not empty: './driver/write_interface_oneshot' [Errno 21] Is a directory: './driver/write_interface_make' [Errno 39] Directory not empty: './driver/write_interface_make' * outputdir() is better than -outputdir, as it knows how to (pre)clean itself. >--------------------------------------------------------------- e340f6eccc9d6d8f0a11c56c312570060c245946 testsuite/driver/testlib.py | 6 ++++++ testsuite/tests/driver/Makefile | 8 ++++---- testsuite/tests/driver/all.T | 11 +++++++++-- testsuite/tests/generics/T5462No1.stderr | 4 ++-- testsuite/tests/generics/all.T | 12 ++++++------ testsuite/tests/ghci/linking/all.T | 11 +++++++---- testsuite/tests/ghci/scripts/all.T | 4 ++-- testsuite/tests/parser/unicode/all.T | 2 +- 8 files changed, 37 insertions(+), 21 deletions(-) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index fe9125b..dbae8d7 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -264,6 +264,7 @@ def _extra_hc_opts( name, opts, v ): # ----- def extra_clean( files ): + assert not isinstance(files, str), files return lambda name, opts, v=files: _extra_clean(name, opts, v); def _extra_clean( name, opts, v ): @@ -751,6 +752,11 @@ def test_common_work (name, opts, func, args): def clean(strs): for str in strs: + if (str.endswith('.package.conf') or + str.startswith('package.conf.') and not str.endswith('/*')): + # Package confs are directories now. + str += '/*' + for name in glob.glob(in_testdir(str)): clean_full_path(name) diff --git a/testsuite/tests/driver/Makefile b/testsuite/tests/driver/Makefile index dafb76e..d463ebf 100644 --- a/testsuite/tests/driver/Makefile +++ b/testsuite/tests/driver/Makefile @@ -578,14 +578,14 @@ T2182: .PHONY: write_interface_oneshot write_interface_oneshot: $(RM) -rf write_interface_oneshot/A011.hi - "$(TEST_HC)" $(TEST_HC_OPTS) -hidir write_interface_oneshot -fno-code -fwrite-interface -c A011.hs - test -f write_interface_oneshot/A011.hi + "$(TEST_HC)" $(TEST_HC_OPTS) -hidir write_interface_oneshot_hidir -fno-code -fwrite-interface -c A011.hs + test -f write_interface_oneshot_hidir/A011.hi .PHONY: write_interface_make write_interface_make: $(RM) -rf write_interface_make/A011.hi - "$(TEST_HC)" $(TEST_HC_OPTS) -hidir write_interface_make -fno-code -fwrite-interface --make A011.hs - test -f write_interface_make/A011.hi + "$(TEST_HC)" $(TEST_HC_OPTS) -hidir write_interface_make_hidir -fno-code -fwrite-interface --make A011.hs + test -f write_interface_make_hidir/A011.hi .PHONY: T9938 T9938: diff --git a/testsuite/tests/driver/all.T b/testsuite/tests/driver/all.T index 8d4fcf5..5d936d7 100644 --- a/testsuite/tests/driver/all.T +++ b/testsuite/tests/driver/all.T @@ -405,8 +405,15 @@ def build_T9050(name, way): return simple_build(name + '.cmm', way, '-outputdir=. ', 0, '', 0, 0, 0) test('T9050', normal, build_T9050, []) -test('write_interface_oneshot', normal, run_command, ['$MAKE -s --no-print-directory write_interface_oneshot']) -test('write_interface_make', normal, run_command, ['$MAKE -s --no-print-directory write_interface_make']) +test('write_interface_oneshot', + extra_clean(['write_interface_oneshot_hidir/*']), + run_command, + ['$MAKE -s --no-print-directory write_interface_oneshot']) + +test('write_interface_make', + extra_clean(['write_interface_make_hidir/*']), + run_command, + ['$MAKE -s --no-print-directory write_interface_make']) test('T9776', normal, compile_fail, ['-frule-check']) diff --git a/testsuite/tests/generics/T5462No1.stderr b/testsuite/tests/generics/T5462No1.stderr index 9a4418a..87ef888 100644 --- a/testsuite/tests/generics/T5462No1.stderr +++ b/testsuite/tests/generics/T5462No1.stderr @@ -1,5 +1,5 @@ -[1 of 2] Compiling GFunctor ( GFunctor/GFunctor.hs, T5462No1/GFunctor.o ) -[2 of 2] Compiling T5462No1 ( T5462No1.hs, T5462No1/T5462No1.o ) +[1 of 2] Compiling GFunctor ( GFunctor/GFunctor.hs, out_T5462No1/GFunctor.o ) +[2 of 2] Compiling T5462No1 ( T5462No1.hs, out_T5462No1/T5462No1.o ) T5462No1.hs:24:42: Can't make a derived instance of ?GFunctor F?: diff --git a/testsuite/tests/generics/all.T b/testsuite/tests/generics/all.T index 98116ec..9a2103f 100644 --- a/testsuite/tests/generics/all.T +++ b/testsuite/tests/generics/all.T @@ -19,12 +19,12 @@ test('GenCannotDoRep1_6', normal, compile_fail, ['']) test('GenCannotDoRep1_7', normal, compile_fail, ['']) test('GenCannotDoRep1_8', normal, compile_fail, ['']) -test('T5462Yes1', extra_clean(['T5462Yes1/GFunctor.hi']) - , multimod_compile_and_run, ['T5462Yes1', '-iGEq -iGEnum -iGFunctor -outputdir=out_T5462Yes1']) -test('T5462Yes2', extra_clean(['T5462Yes2/GFunctor.hi']) - , multimod_compile_and_run, ['T5462Yes2', '-iGFunctor -outputdir=out_T5462Yes2']) -test('T5462No1', extra_clean(['T5462No1/GFunctor.hi']) - , multimod_compile_fail, ['T5462No1', '-iGFunctor -outputdir=T5462No1']) +test('T5462Yes1', outputdir('out_T5462Yes1') + , multimod_compile_and_run, ['T5462Yes1', '-iGEq -iGEnum -iGFunctor']) +test('T5462Yes2', outputdir('out_T5462Yes2') + , multimod_compile_and_run, ['T5462Yes2', '-iGFunctor']) +test('T5462No1', outputdir('out_T5462No1') + , multimod_compile_fail, ['T5462No1', '-iGFunctor']) test('T5884', extra_clean(['T5884Other.o', 'T5884Other.hi']) , multimod_compile, ['T5884Other', '-v0']) diff --git a/testsuite/tests/ghci/linking/all.T b/testsuite/tests/ghci/linking/all.T index 6675a53..c7ce1c3 100644 --- a/testsuite/tests/ghci/linking/all.T +++ b/testsuite/tests/ghci/linking/all.T @@ -22,12 +22,15 @@ test('ghcilink003', test('ghcilink004', [unless(doing_ghci, skip), - extra_clean(['dir004/*','dir004'])], + extra_clean(['dir004/local.package.conf/*', 'dir004/*', 'dir004']) + ], run_command, ['$MAKE -s --no-print-directory ghcilink004']) test('ghcilink005', - [unless(doing_ghci, skip), extra_clean(['dir005/*','dir005'])], + [unless(doing_ghci, skip), + extra_clean(['dir005/ghcilink005.package.conf/*', 'dir005/*','dir005']) + ], run_command, ['$MAKE -s --no-print-directory ghcilink005']) @@ -36,13 +39,13 @@ test('ghcilink006', # still cannot load libstdc++ on Windows. See also #4468. when(opsys('mingw32'), expect_broken(5289)), unless(doing_ghci, skip), - extra_clean(['dir006/*','dir006']) + extra_clean(['dir006/ghcilink006.package.conf/*', 'dir006/*','dir006']) ], run_command, ['$MAKE -s --no-print-directory ghcilink006']) test('T3333', - [extra_clean('T3333.o'), + [extra_clean(['T3333.o']), unless(doing_ghci, skip), unless(opsys('linux') or ghci_dynamic(), expect_broken(3333))], run_command, diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T index 212b0e5..a366c1f 100755 --- a/testsuite/tests/ghci/scripts/all.T +++ b/testsuite/tests/ghci/scripts/all.T @@ -130,11 +130,11 @@ test('T5979', ghci_script, ['T5979.script']) test('T5975a', [pre_cmd('touch f??b?r1.hs'), - clean_cmd('rm f??b?r1.hs')], + clean_cmd('rm -f f??b?r1.hs')], ghci_script, ['T5975a.script']) test('T5975b', [pre_cmd('touch f??b?r2.hs'), - clean_cmd('rm f??b?r2.hs'), + clean_cmd('rm -f f??b?r2.hs'), extra_hc_opts('f??b?r2.hs')], ghci_script, ['T5975b.script']) test('T6027ghci', normal, ghci_script, ['T6027ghci.script']) diff --git a/testsuite/tests/parser/unicode/all.T b/testsuite/tests/parser/unicode/all.T index 2ff7edf..ec08ae5 100644 --- a/testsuite/tests/parser/unicode/all.T +++ b/testsuite/tests/parser/unicode/all.T @@ -20,5 +20,5 @@ test('T1744', normal, compile_and_run, ['']) test('T1103', normal, compile, ['']) test('T2302', only_ways(['normal']), compile_fail, ['']) test('T4373', normal, compile, ['']) -test('T6016', extra_clean('T6016-twoBOMs'), compile_and_run, ['-package ghc']) +test('T6016', extra_clean(['T6016-twoBOMs']), compile_and_run, ['-package ghc']) test('T7671', normal, compile, ['']) From git at git.haskell.org Thu Jun 4 22:01:12 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 4 Jun 2015 22:01:12 +0000 (UTC) Subject: [commit: ghc] master: Build: remove more unnecessary CLEANING/=YES checks (5dd0286) Message-ID: <20150604220112.A62443A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5dd02864a844bcf6fe0018755ff261affdef3fea/ghc >--------------------------------------------------------------- commit 5dd02864a844bcf6fe0018755ff261affdef3fea Author: Thomas Miedema Date: Thu May 28 12:38:21 2015 +0200 Build: remove more unnecessary CLEANING/=YES checks All these checks that CLEANING/=YES are no longer needed, because nowadays $1_$2_PROGNAME is always set explicitly, and $1_$2_PROG isn't. They were once introduce to allow `make clean` before `./configure`. I checked, and it still works. Remove the checks to make the build system a tiny bit shorter, and to no longer wonder why they are there. Differential Revision: https://phabricator.haskell.org/D941 >--------------------------------------------------------------- 5dd02864a844bcf6fe0018755ff261affdef3fea rules/build-perl.mk | 2 -- rules/build-prog.mk | 4 ---- 2 files changed, 6 deletions(-) diff --git a/rules/build-perl.mk b/rules/build-perl.mk index a6725ba..46cf053 100644 --- a/rules/build-perl.mk +++ b/rules/build-perl.mk @@ -24,13 +24,11 @@ $(call profStart, build-perl($1,$2)) # $1 = dir # $2 = distdir -ifneq "$$(CLEANING)" "YES" ifeq "$$($1_$2_PROGNAME)" "" $$(error $1_$2_PROGNAME is not set) endif ifneq "$$($1_$2_PROG)" "" $$(error $1_$2_PROG is set) -endif $1_$2_PROG = $$($1_$2_PROGNAME) ifneq "$$($$($1_$2_PROG)_INPLACE)" "" diff --git a/rules/build-prog.mk b/rules/build-prog.mk index 3e9bc89..f2f6ad2 100644 --- a/rules/build-prog.mk +++ b/rules/build-prog.mk @@ -22,14 +22,12 @@ $(call profStart, build-prog($1,$2,$3)) # $2 = distdir # $3 = GHC stage to use (0 == bootstrapping compiler) -ifneq "$$(CLEANING)" "YES" ifeq "$$($1_$2_PROGNAME)" "" $$(error $1_$2_PROGNAME is not set) endif ifneq "$$($1_$2_PROG)" "" $$(error $1_$2_PROG is set) endif -endif $1_$2_PROG = $$($1_$2_PROGNAME)$$(exeext$3) ifeq "$$(findstring $3,0 1 2)" "" @@ -91,11 +89,9 @@ else $1_$2_INPLACE = endif else -ifneq "$$(CLEANING)" "YES" ifneq "$$($$($1_$2_PROGNAME)_INPLACE)" "" $$(error $$($1_$2_PROGNAME)_INPLACE defined twice) endif -endif ifeq "$$($1_$2_TOPDIR)" "YES" $$($1_$2_PROGNAME)_INPLACE = $$(INPLACE_TOPDIR)/$$($1_$2_PROG) else From git at git.haskell.org Thu Jun 4 22:01:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 4 Jun 2015 22:01:15 +0000 (UTC) Subject: [commit: ghc] master: Build: remove unnecessary CLEANING/=YES check (cac68d0) Message-ID: <20150604220115.78C883A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cac68d0d340f93738db79ad867fe3f0eec515075/ghc >--------------------------------------------------------------- commit cac68d0d340f93738db79ad867fe3f0eec515075 Author: Thomas Miedema Date: Tue May 26 21:00:04 2015 +0200 Build: remove unnecessary CLEANING/=YES check The comment "INPLACE_BIN might be empty if we're distcleaning" is no longer true, and the check that CLEANING isn't YES isn't necessary. It was introduced in cd12c32de77ac18a69ed1733a558095567ec5ba8, to "make repeated 'make distclean' not fail", and and later revised in 39253008705e3ca590afdfa1b87bfbb5a16da7e7. It was needed because INPLACE_BIN was defined in config.mk. Commit 6793a033e1ce41f77316675e8f7aa83196a9b211 however, two days later, introduced a better solution to this problem: "Move the fixed paths out of config.mk, so cleaning works without configuring" So here we remove the original comment and check. One less thing to worry about when trying to understand the build system. Differential Revision: https://phabricator.haskell.org/D940 >--------------------------------------------------------------- cac68d0d340f93738db79ad867fe3f0eec515075 rules/build-perl.mk | 4 ---- rules/build-prog.mk | 3 --- 2 files changed, 7 deletions(-) diff --git a/rules/build-perl.mk b/rules/build-perl.mk index 51e92f7..a6725ba 100644 --- a/rules/build-perl.mk +++ b/rules/build-perl.mk @@ -51,8 +51,6 @@ $(call clean-target,$1,$2,$1/$2 $$($1_$2_INPLACE)) .PHONY: clean_$1 clean_$1 : clean_$1_$2 -# INPLACE_BIN etc. might be empty if we're cleaning -ifneq "$$(CLEANING)" "YES" ifneq "$$(BINDIST)" "YES" $1/$2/$$($1_$2_PROG).prl: $1/$$($1_PERL_SRC) $$$$(unlit_INPLACE) | $$$$(dir $$$$@)/. "$$(unlit_INPLACE)" $$(UNLIT_OPTS) $$< $$@ @@ -67,8 +65,6 @@ $1/$2/$$($1_$2_PROG): $1/$2/$$($1_$2_PROG).prl $$($1_$2_INPLACE): $1/$2/$$($1_$2_PROG) | $$$$(dir $$$$@)/. "$$(CP)" $$< $$@ $$(EXECUTABLE_FILE) $$@ - -endif endif ifeq "$$($1_$2_INSTALL)" "YES" diff --git a/rules/build-prog.mk b/rules/build-prog.mk index 10d31c5..3e9bc89 100644 --- a/rules/build-prog.mk +++ b/rules/build-prog.mk @@ -287,13 +287,10 @@ endif endif endif -# INPLACE_BIN might be empty if we're distcleaning -ifneq "$$(CLEANING)" "YES" ifeq "$$($1_$2_INSTALL_INPLACE)" "YES" $$($1_$2_INPLACE) : $1/$2/build/tmp/$$($1_$2_PROG_INPLACE) | $$$$(dir $$$$@)/. $$(INSTALL) -m 755 $$< $$@ endif -endif endif # BINDIST=YES From git at git.haskell.org Thu Jun 4 22:01:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 4 Jun 2015 22:01:18 +0000 (UTC) Subject: [commit: ghc] master: Make validate more quiet (d0063e8) Message-ID: <20150604220118.6E0A03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d0063e8975672714a6ae33f7e8175421c6b5d5c5/ghc >--------------------------------------------------------------- commit d0063e8975672714a6ae33f7e8175421c6b5d5c5 Author: Thomas Miedema Date: Fri May 29 13:35:13 2015 +0200 Make validate more quiet * By default use V=0, and call the testsuite with VERBOSE=2, which we did before only with validate --quiet. This disables printing the test commands it runs. * When --quiet is used, call the testsuite with VERBOSE=1. This disables printing the '====> Scanning' lines, and doesn't print which test is being run. So it only prints something when a test accidentally prints to stdout or when it fails. Don't set this option on Travis, as Travis will cancel a build if it doesn't see any output for more than 10 minutes. * When --quiet is used, set the new test option NO_PRINT_SUMMARY, which skips printing the test summary. Only the list of unexpected failures is printed, if there are any. Note that the full summary can still be found in testsuite_summary.txt * When --quiet is used, don't pass the `-v` flag to `ghc-pkg check` * When --quiet is used, don't print the Oops! header. It shoud be clear from the list of failing tests that something is wrong. This is all done to get the most out of 30 lines of logfile. These changes can be disabled later by simply not passing the --quiet flag to validate. Differential Revision: https://phabricator.haskell.org/D942 >--------------------------------------------------------------- d0063e8975672714a6ae33f7e8175421c6b5d5c5 .travis.yml | 5 ++-- Makefile | 4 +-- testsuite/driver/runtests.py | 16 +++++++----- testsuite/driver/testglobals.py | 11 +++++++- testsuite/driver/testlib.py | 7 ++++- testsuite/mk/test.mk | 8 ++++-- validate | 58 +++++++++++++++++++++-------------------- 7 files changed, 67 insertions(+), 42 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d0063e8975672714a6ae33f7e8175421c6b5d5c5 From git at git.haskell.org Thu Jun 4 22:01:21 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 4 Jun 2015 22:01:21 +0000 (UTC) Subject: [commit: ghc] master: Travis: allow user forks (7beb477) Message-ID: <20150604220121.314E83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7beb4771a7adb470a98ea1cde43e9f00887ac980/ghc >--------------------------------------------------------------- commit 7beb4771a7adb470a98ea1cde43e9f00887ac980 Author: Thomas Miedema Date: Sun May 31 14:54:30 2015 +0200 Travis: allow user forks Check for each submodule repository url if the user made its own fork. If so, use that. Otherwise, fall back on the one from github.com/ghc. As suggested by Richard in this mailinglist discussion: https://mail.haskell.org/pipermail/ghc-devs/2014-November/007300.html Documentation is at [wiki:TestingPatches#Travis]. Differential Revision: https://phabricator.haskell.org/D939 >--------------------------------------------------------------- 7beb4771a7adb470a98ea1cde43e9f00887ac980 .travis.yml | 21 +++++++++++++++------ 1 file changed, 15 insertions(+), 6 deletions(-) diff --git a/.travis.yml b/.travis.yml index dd5a648..836e62a 100644 --- a/.travis.yml +++ b/.travis.yml @@ -14,12 +14,21 @@ before_install: - travis_retry sudo apt-get install cabal-install-1.18 ghc-7.6.3 alex-3.1.3 happy-1.19.4 - travis_retry sudo apt-get install llvm-3.6 - export PATH=/opt/ghc/7.6.3/bin:/opt/cabal/1.18/bin:/opt/alex/3.1.3/bin:/opt/happy/1.19.4/bin:/usr/lib/llvm-3.6/bin:$PATH - - git config --global url."git://github.com/ghc/packages-".insteadOf git://github.com/ghc/packages/ - - git config --global url."http://github.com/ghc/packages-".insteadOf http://github.com/ghc/packages/ - - git config --global url."https://github.com/ghc/packages-".insteadOf https://github.com/ghc/packages/ - - git config --global url."ssh://git at github.com/ghc/packages-".insteadOf ssh://git at github.com/ghc/packages/ - - git config --global url."git at github.com:/ghc/packages-".insteadOf git at github.com:/ghc/packages/ - - git submodule update --init --recursive + +# Be explicit about which protocol to use, such that we don't have to repeat the rewrite command for each. + - git config remote.origin.url git://github.com/${TRAVIS_REPO_SLUG}.git + - git config --global url."git://github.com/${TRAVIS_REPO_SLUG%/*}/packages-".insteadOf "git://github.com/${TRAVIS_REPO_SLUG%/*}/packages/" + - git submodule --quiet init # Be quiet about these urls, as we may override them later. + +# Check if submodule repositories exist. + - git config --get-regexp submodule.*.url | while read entry url; do git ls-remote "$url" dummyref 2>/dev/null && echo "$entry = $url" || git config --unset-all "$entry" ; done + +# Use github.com/ghc for those submodule repositories we couldn't connect to. + - git config remote.origin.url git://github.com/ghc/ghc.git + - git config --global url."git://github.com/ghc/packages-".insteadOf git://github.com/ghc/packages/ + - git submodule init # Don't be quiet, we want to show these urls. + - git submodule --quiet update --recursive # Now we can be quiet again. + install: # - sudo apt-get update # - sudo apt-get install haskell-platform autoconf libtool make ncurses-dev g++ dblatex docbook-xsl docbook-utils From git at git.haskell.org Thu Jun 4 22:01:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 4 Jun 2015 22:01:23 +0000 (UTC) Subject: [commit: ghc] master: Testsuite: don't show compile/link info for some tests (0686d76) Message-ID: <20150604220123.E0AAA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0686d76fc445e5338425f27743d9498b2a32d785/ghc >--------------------------------------------------------------- commit 0686d76fc445e5338425f27743d9498b2a32d785 Author: Thomas Miedema Date: Fri May 29 17:06:58 2015 +0200 Testsuite: don't show compile/link info for some tests This info is not needed in the testlogs, and was actually making these tests fail on my machine because of some bug with the timeout program: ... [1 of 1] Compiling Main ( OutOfHeap.hs, tmp_T9579_outofheap_rtssome/Main.o ) Linking T9579_outofheap_rtsnone ... ... >--------------------------------------------------------------- 0686d76fc445e5338425f27743d9498b2a32d785 testsuite/tests/ghci/scripts/Makefile | 2 +- testsuite/tests/rts/T9579/Makefile | 16 ++++++++-------- 2 files changed, 9 insertions(+), 9 deletions(-) diff --git a/testsuite/tests/ghci/scripts/Makefile b/testsuite/tests/ghci/scripts/Makefile index f70c062..1c1dadb 100644 --- a/testsuite/tests/ghci/scripts/Makefile +++ b/testsuite/tests/ghci/scripts/Makefile @@ -46,7 +46,7 @@ T9367: .PHONY: T9762_prep T9762_prep: - '$(TEST_HC)' $(TEST_HC_OPTS) -O -fhpc -dynamic T9762B.hs + '$(TEST_HC)' $(TEST_HC_OPTS) -v0 -O -fhpc -dynamic T9762B.hs .PHONY: T10408A T10408A: diff --git a/testsuite/tests/rts/T9579/Makefile b/testsuite/tests/rts/T9579/Makefile index b05f0c4..23177ee 100644 --- a/testsuite/tests/rts/T9579/Makefile +++ b/testsuite/tests/rts/T9579/Makefile @@ -3,43 +3,43 @@ include $(TOP)/mk/boilerplate.mk include $(TOP)/mk/test.mk T9579_stackoverflow_rtsnone: - '$(TEST_HC)' $(TEST_HC_OPTS) -rtsopts=none -fforce-recomp -with-rtsopts -K1m \ + '$(TEST_HC)' $(TEST_HC_OPTS) -v0 -rtsopts=none -fforce-recomp -with-rtsopts -K1m \ -outputdir tmp_T9579_stackoverflow_rtsnone \ StackOverflow.hs -o T9579_stackoverflow_rtsnone T9579_stackoverflow_rtssome: - '$(TEST_HC)' $(TEST_HC_OPTS) -rtsopts=some -fforce-recomp -with-rtsopts -K1m \ + '$(TEST_HC)' $(TEST_HC_OPTS) -v0 -rtsopts=some -fforce-recomp -with-rtsopts -K1m \ -outputdir tmp_T9579_stackoverflow_rtssome \ StackOverflow.hs -o T9579_stackoverflow_rtssome T9579_stackoverflow_rtsall: - '$(TEST_HC)' $(TEST_HC_OPTS) -rtsopts=all -fforce-recomp -with-rtsopts -K1m \ + '$(TEST_HC)' $(TEST_HC_OPTS) -v0 -rtsopts=all -fforce-recomp -with-rtsopts -K1m \ -outputdir tmp_T9579_stackoverflow_rtsall \ StackOverflow.hs -o T9579_stackoverflow_rtsall T9579_stackoverflow_rtsall_no_suggestions: - '$(TEST_HC)' $(TEST_HC_OPTS) -rtsopts=all -fforce-recomp -with-rtsopts -K1m \ + '$(TEST_HC)' $(TEST_HC_OPTS) -v0 -rtsopts=all -fforce-recomp -with-rtsopts -K1m \ -no-rtsopts-suggestions \ -outputdir tmp_T9579_stackoverflow_rtsall_no_suggestions \ StackOverflow.hs -o T9579_stackoverflow_rtsall_no_suggestions T9579_outofheap_rtsnone: - '$(TEST_HC)' $(TEST_HC_OPTS) -rtsopts=none -fforce-recomp -with-rtsopts -M1m \ + '$(TEST_HC)' $(TEST_HC_OPTS) -v0 -rtsopts=none -fforce-recomp -with-rtsopts -M1m \ -outputdir tmp_T9579_outofheap_rtsnone \ OutOfHeap.hs -o T9579_outofheap_rtsnone T9579_outofheap_rtssome: - '$(TEST_HC)' $(TEST_HC_OPTS) -rtsopts=some -fforce-recomp -with-rtsopts -M1m \ + '$(TEST_HC)' $(TEST_HC_OPTS) -v0 -rtsopts=some -fforce-recomp -with-rtsopts -M1m \ -outputdir tmp_T9579_outofheap_rtssome \ OutOfHeap.hs -o T9579_outofheap_rtssome T9579_outofheap_rtsall: - '$(TEST_HC)' $(TEST_HC_OPTS) -rtsopts=all -fforce-recomp -with-rtsopts -M1m \ + '$(TEST_HC)' $(TEST_HC_OPTS) -v0 -rtsopts=all -fforce-recomp -with-rtsopts -M1m \ -outputdir tmp_T9579_outofheap_rtsall \ OutOfHeap.hs -o T9579_outofheap_rtsall T9579_outofheap_rtsall_no_suggestions: - '$(TEST_HC)' $(TEST_HC_OPTS) -rtsopts=all -fforce-recomp -with-rtsopts -M1m \ + '$(TEST_HC)' $(TEST_HC_OPTS) -v0 -rtsopts=all -fforce-recomp -with-rtsopts -M1m \ -no-rtsopts-suggestions \ -outputdir tmp_T9579_outofheap_rtsall_no_suggestions \ OutOfHeap.hs -o T9579_outofheap_rtsall_no_suggestions From git at git.haskell.org Thu Jun 4 22:01:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 4 Jun 2015 22:01:26 +0000 (UTC) Subject: [commit: ghc] master: Testsuite: ignore `stdcall attribute ignored` (#1288) (07feab1) Message-ID: <20150604220126.9BB463A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/07feab194aff4a2ae39514480736ce23a3b679b1/ghc >--------------------------------------------------------------- commit 07feab194aff4a2ae39514480736ce23a3b679b1 Author: Thomas Miedema Date: Fri May 29 21:13:39 2015 +0200 Testsuite: ignore `stdcall attribute ignored` (#1288) That warning is only shown on some platforms, and is I believe harmless. >--------------------------------------------------------------- 07feab194aff4a2ae39514480736ce23a3b679b1 testsuite/tests/ffi/should_run/Makefile | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/ffi/should_run/Makefile b/testsuite/tests/ffi/should_run/Makefile index 98d26fe..a4a716a 100644 --- a/testsuite/tests/ffi/should_run/Makefile +++ b/testsuite/tests/ffi/should_run/Makefile @@ -6,10 +6,12 @@ ffi018_ghci_setup : '$(TEST_HC)' $(TEST_HC_OPTS) -c ffi018_ghci_c.c T1288_ghci_setup : - '$(TEST_HC)' $(TEST_HC_OPTS) $(ghciWayFlags) -c T1288_ghci_c.c + # Don't show gcc warning: 'stdcall' attribute ignored [-Wattributes] + '$(TEST_HC)' $(TEST_HC_OPTS) $(ghciWayFlags) -c -optc=-Wno-attributes T1288_ghci_c.c T2276_ghci_setup : - '$(TEST_HC)' $(TEST_HC_OPTS) $(ghciWayFlags) -c T2276_ghci_c.c + # Don't show gcc warning: 'stdcall' attribute ignored [-Wattributes] + '$(TEST_HC)' $(TEST_HC_OPTS) $(ghciWayFlags) -c -optc=-Wno-attributes T2276_ghci_c.c ffi002_setup : '$(TEST_HC)' $(TEST_HC_OPTS) -c ffi002.hs From git at git.haskell.org Fri Jun 5 15:09:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 5 Jun 2015 15:09:16 +0000 (UTC) Subject: [commit: ghc] master: Fix #10488 by unwrapping type synonyms. (761fb7c) Message-ID: <20150605150916.04FFA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/761fb7c4869a081da7320e4307dcb947b5ed95d1/ghc >--------------------------------------------------------------- commit 761fb7c4869a081da7320e4307dcb947b5ed95d1 Author: Richard Eisenberg Date: Thu Jun 4 17:05:02 2015 -0400 Fix #10488 by unwrapping type synonyms. Summary: Previously, I had forgotten to unwrap vanilla type synonyms in the "flattener" that is used around the closed-type-family apartness check. Test Plan: validate Reviewers: austin Subscribers: bgamari, thomie Differential Revision: https://phabricator.haskell.org/D955 GHC Trac Issues: #10488 >--------------------------------------------------------------- 761fb7c4869a081da7320e4307dcb947b5ed95d1 compiler/types/FamInstEnv.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/compiler/types/FamInstEnv.hs b/compiler/types/FamInstEnv.hs index 930d059..9c53138 100644 --- a/compiler/types/FamInstEnv.hs +++ b/compiler/types/FamInstEnv.hs @@ -1034,6 +1034,8 @@ coreFlattenTys in_scope = go [] coreFlattenTy :: InScopeSet -> FlattenMap -> Type -> (FlattenMap, Type) coreFlattenTy in_scope = go where + go m ty | Just ty' <- coreView ty = go m ty' + go m ty@(TyVarTy {}) = (m, ty) go m (AppTy ty1 ty2) = let (m1, ty1') = go m ty1 (m2, ty2') = go m1 ty2 in From git at git.haskell.org Fri Jun 5 15:09:19 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 5 Jun 2015 15:09:19 +0000 (UTC) Subject: [commit: ghc] master: Fix #10489 (61b96a8) Message-ID: <20150605150919.42F503A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/61b96a86c5342fb1c850361177d60fe855d948f6/ghc >--------------------------------------------------------------- commit 61b96a86c5342fb1c850361177d60fe855d948f6 Author: Richard Eisenberg Date: Fri Jun 5 09:56:21 2015 -0400 Fix #10489 Dang, roles are annoying. Test case: typecheck/should_compile/T10489 >--------------------------------------------------------------- 61b96a86c5342fb1c850361177d60fe855d948f6 compiler/hsSyn/HsUtils.hs | 3 ++- testsuite/tests/typecheck/should_compile/T10489.hs | 3 +++ testsuite/tests/typecheck/should_compile/all.T | 1 + 3 files changed, 6 insertions(+), 1 deletion(-) diff --git a/compiler/hsSyn/HsUtils.hs b/compiler/hsSyn/HsUtils.hs index f4737e7..fd3d5ef 100644 --- a/compiler/hsSyn/HsUtils.hs +++ b/compiler/hsSyn/HsUtils.hs @@ -504,9 +504,10 @@ mkHsWrapPat :: HsWrapper -> Pat id -> Type -> Pat id mkHsWrapPat co_fn p ty | isIdHsWrapper co_fn = p | otherwise = CoPat co_fn p ty +-- input coercion is Nominal mkHsWrapPatCo :: TcCoercion -> Pat id -> Type -> Pat id mkHsWrapPatCo co pat ty | isTcReflCo co = pat - | otherwise = CoPat (mkWpCast co) pat ty + | otherwise = CoPat (mkWpCast (mkTcSubCo co)) pat ty mkHsDictLet :: TcEvBinds -> LHsExpr Id -> LHsExpr Id mkHsDictLet ev_binds expr = mkLHsWrap (mkWpLet ev_binds) expr diff --git a/testsuite/tests/typecheck/should_compile/T10489.hs b/testsuite/tests/typecheck/should_compile/T10489.hs new file mode 100644 index 0000000..892965e --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T10489.hs @@ -0,0 +1,3 @@ +module T10489 where + +convert d = let d' = case d of '0' -> '!' in d' diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index 12e2612..dbd6328 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -457,3 +457,4 @@ test('T10390', normal, compile, ['']) test('T8555', normal, compile, ['']) test('T8799', normal, compile, ['']) test('T10423', normal, compile, ['']) +test('T10489', normal, compile, ['']) From git at git.haskell.org Fri Jun 5 15:09:22 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 5 Jun 2015 15:09:22 +0000 (UTC) Subject: [commit: ghc] master: Minor code cleanup (53c1374) Message-ID: <20150605150922.3E2A23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/53c13744210402151e58baf0d703d23927f5188d/ghc >--------------------------------------------------------------- commit 53c13744210402151e58baf0d703d23927f5188d Author: Richard Eisenberg Date: Fri Jun 5 09:50:00 2015 -0400 Minor code cleanup >--------------------------------------------------------------- 53c13744210402151e58baf0d703d23927f5188d compiler/typecheck/TcCanonical.hs | 10 ++-------- 1 file changed, 2 insertions(+), 8 deletions(-) diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index 1223194..5bbab21 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -432,7 +432,7 @@ can_eq_nc' flat _rdr_env _envs ev eq_rel ty1 ps_ty1 ty2 ps_ty2 | Just ty2' <- tcView ty2 = can_eq_nc flat ev eq_rel ty1 ps_ty1 ty2' ps_ty2 -- need to check for reflexivity in the ReprEq case. --- See Note [AppTy reflexivity check] and Note [Eager reflexivity check] +-- See Note [Eager reflexivity check] can_eq_nc' _flat _rdr_env _envs ev ReprEq ty1 _ ty2 _ | ty1 `eqType` ty2 = canEqReflexive ev ReprEq ty1 @@ -509,11 +509,6 @@ can_eq_nc' True _rdr_env _envs ev NomEq ty1 _ (AppTy t2 s2) _ | Just (t1, s1) <- tcSplitAppTy_maybe ty1 = can_eq_app ev t1 s1 t2 s2 --- See Note [AppTy reflexivity check] -can_eq_nc' _flat _rdr_env _envs ev ReprEq ty1@(AppTy {}) _ ty2@(AppTy {}) _ - | ty1 `eqType` ty2 - = canEqReflexive ev ReprEq ty1 - -- No similarity in type structure detected. Flatten and try again! can_eq_nc' False rdr_env envs ev eq_rel _ ps_ty1 _ ps_ty2 = do { (xi1, co1) <- flatten FM_FlattenAll ev ps_ty1 @@ -571,8 +566,7 @@ equality because the flattener technology deals with the similar case Note that this check does not catch all cases, but it will catch the cases we're most worried about, types like X above that are actually inhabited. -Note [AppTy reflexivity check] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Here's another place where this reflexivity check is key: Consider trying to prove (f a) ~R (f a). The AppTys in there can't be decomposed, because representational equality isn't congruent with respect to AppTy. So, when canonicalising the equality above, we get stuck and From git at git.haskell.org Sat Jun 6 13:26:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 Jun 2015 13:26:17 +0000 (UTC) Subject: [commit: ghc] master: docs: Fix #10416 (dcaaa98) Message-ID: <20150606132617.3D5543A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/dcaaa980dc59202744bb3888d9662f9a7558cdf6/ghc >--------------------------------------------------------------- commit dcaaa980dc59202744bb3888d9662f9a7558cdf6 Author: Austin Seipp Date: Fri Jun 5 15:43:25 2015 -0500 docs: Fix #10416 Summary: Apparently this was broken by b30c6012c7552c874281050d40e5a59012b2c5e7, but I can't reproduce the issue described there at all. Signed-off-by: Austin Seipp Test Plan: Use my eyes to read the resulting user manual. Reviewers: hvr, thomie Reviewed By: thomie Subscribers: bgamari, thomie Differential Revision: https://phabricator.haskell.org/D958 GHC Trac Issues: #10416 >--------------------------------------------------------------- dcaaa980dc59202744bb3888d9662f9a7558cdf6 docs/users_guide/profiling.xml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/docs/users_guide/profiling.xml b/docs/users_guide/profiling.xml index 4971a7d..84f96b1 100644 --- a/docs/users_guide/profiling.xml +++ b/docs/users_guide/profiling.xml @@ -625,7 +625,7 @@ MAIN MAIN 102 0 0.0 0.0 100.0 1 other than making the PS file generation work, rather than falling over. The result seems to be broken PS on the page with the image. --> - You might also want to take a look From git at git.haskell.org Sat Jun 6 13:26:19 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 Jun 2015 13:26:19 +0000 (UTC) Subject: [commit: ghc] master: Testsuite: only show output diff when test is expected to pass (ae83a81) Message-ID: <20150606132619.E999F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ae83a81ad6b6185f5b754c1819cb78399da86d84/ghc >--------------------------------------------------------------- commit ae83a81ad6b6185f5b754c1819cb78399da86d84 Author: Thomas Miedema Date: Fri May 29 15:44:21 2015 +0200 Testsuite: only show output diff when test is expected to pass Don't let the output of tests that either have missing libraries or are expected to be broken obscure real failures. This makes it easier to analyse the testlogs. The only consequence is that when a test fails because a certain library isn't installed, you have to check the all.T file in which the test is defined to actually find out _which_ library that is. Before it would print something like Compile failed (status 256) errors were: stm052.hs:10:8: error: Could not find module ?System.Random? Use -v to see a list of the files searched for. And now it doesn't. I think this is an acceptable tradeoff. Differential Revision: https://phabricator.haskell.org/D945 >--------------------------------------------------------------- ae83a81ad6b6185f5b754c1819cb78399da86d84 testsuite/driver/testlib.py | 28 +++++++++++++++++----------- 1 file changed, 17 insertions(+), 11 deletions(-) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index dbae8d7..63b42e8 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -168,6 +168,11 @@ def record_broken(name, opts, bug): if not me in brokens: brokens.append(me) +def _expect_pass(way): + # Helper function. Not intended for use in .T files. + opts = getTestOpts() + return opts.expect == 'pass' and way not in opts.expect_fail_for + # ----- def omit_ways( ways ): @@ -817,8 +822,7 @@ def do_test(name, way, func, args): passFail = 'No passFail found' if passFail == 'pass': - if getTestOpts().expect == 'pass' \ - and way not in getTestOpts().expect_fail_for: + if _expect_pass(way): t.n_expected_passes = t.n_expected_passes + 1 if name in t.expected_passes: t.expected_passes[name].append(way) @@ -829,8 +833,7 @@ def do_test(name, way, func, args): t.n_unexpected_passes = t.n_unexpected_passes + 1 addPassingTestInfo(t.unexpected_passes, getTestOpts().testdir, name, way) elif passFail == 'fail': - if getTestOpts().expect == 'pass' \ - and way not in getTestOpts().expect_fail_for: + if _expect_pass(way): reason = result['reason'] tag = result.get('tag') if tag == 'stat': @@ -1248,8 +1251,9 @@ def simple_build( name, way, extra_hc_opts, should_fail, top_mod, link, addsuf, if result != 0 and not should_fail: actual_stderr = qualify(name, 'comp.stderr') - if_verbose(1,'Compile failed (status ' + repr(result) + ') errors were:') - if_verbose_dump(1,actual_stderr) + if config.verbose >= 1 and _expect_pass(way): + print('Compile failed (status ' + repr(result) + ') errors were:') + if_verbose_dump(1, actual_stderr) # ToDo: if the sub-shell was killed by ^C, then exit @@ -1332,9 +1336,10 @@ def simple_run( name, way, prog, args ): # check the exit code if exit_code != opts.exit_code: - print('Wrong exit code (expected', opts.exit_code, ', actual', exit_code, ')') - dump_stdout(name) - dump_stderr(name) + if config.verbose >= 1 and _expect_pass(way): + print('Wrong exit code (expected', opts.exit_code, ', actual', exit_code, ')') + dump_stdout(name) + dump_stderr(name) return failBecause('bad exit code') check_hp = my_rts_flags.find("-h") != -1 @@ -1643,7 +1648,8 @@ def compare_outputs(way, kind, normaliser, expected_file, actual_file): if expected_str == actual_str: return 1 else: - if_verbose(1, 'Actual ' + kind + ' output differs from expected:') + if config.verbose >= 1 and _expect_pass(way): + print('Actual ' + kind + ' output differs from expected:') if expected_file_for_diff == '/dev/null': expected_normalised_file = '/dev/null' @@ -1662,7 +1668,7 @@ def compare_outputs(way, kind, normaliser, expected_file, actual_file): # (including newlines) so the diff would be hard to read. # This does mean that the diff might contain changes that # would be normalised away. - if (config.verbose >= 1): + if config.verbose >= 1 and _expect_pass(way): r = os.system( 'diff -uw ' + expected_file_for_diff + \ ' ' + actual_file ) From git at git.haskell.org Sat Jun 6 13:26:22 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 Jun 2015 13:26:22 +0000 (UTC) Subject: [commit: ghc] master: Fix the sdist build (328c212) Message-ID: <20150606132622.A998D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/328c212b1db4d439fc693216495515bce162ef6e/ghc >--------------------------------------------------------------- commit 328c212b1db4d439fc693216495515bce162ef6e Author: Thomas Miedema Date: Fri Jun 5 22:12:34 2015 +0200 Fix the sdist build Since commit 824e34e30338b4b1de0ab5467ffd29da4c7c805a, building ghc from a source distribution doesn't work. The error is: make[3]: *** No rule to make target 'utils/genprimopcode/dist/build/Lexer.hs', needed by 'utils/genprimopcode/dist/build/Lexer.o'. Stop. This commit fixes that. See note [Implicit rule search algorithm]. Differential Revision: https://phabricator.haskell.org/D959 >--------------------------------------------------------------- 328c212b1db4d439fc693216495515bce162ef6e rules/hs-suffix-way-rules.mk | 82 ++++++++++++++++++++++++++++++++++++++++++-- 1 file changed, 80 insertions(+), 2 deletions(-) diff --git a/rules/hs-suffix-way-rules.mk b/rules/hs-suffix-way-rules.mk index f9ecf6e..4735182 100644 --- a/rules/hs-suffix-way-rules.mk +++ b/rules/hs-suffix-way-rules.mk @@ -29,6 +29,86 @@ $1/$2/build/%.$$(dyn_osuf)-boot: $1/$2/build/%.$$(v_hisuf)-boot fi else +# Note [Implicit rule search algorithm] +# +# The order in which implicit rules are defined can influence a build. +# +# Case study: genprimpos/Lexer.hs +# +# We have two implicit rules for creating .o files, which after instantiating +# with a specific directory ($1=utils/genprimops) and distdir ($2=dist) look +# like this: +# +# utils/genprimops/dist/build/%.o : utils/genprimops/dist/build/%.hs +# +# utils/genprimops/dist/build/%.o : utils/genprimops/./%.hs +# +# +# The first rule is defined in hs-suffix-way-rules.mk (this file), the other +# in hs-suffix-way-rules-srcdir.mk. +# +# Assume for rest of this story that %=Lexer. +# +# In a normal repository checkout, neither Lexer.hs exists, but we have a rule +# to generate the one in the build directory by running alex on Lexer.x (the +# rule for that operation is defined in hs-suffix-rules-srcdir.mk). Since make +# needs to make a choice which of the above two implicit rules to follow (it +# never runs 2 recipes for the same target, unless double colon rules are +# used, which we don't), logically it will choose the first rule: Lexer.o will +# depend on Lexer.hs in the build directory, that file will be build, and then +# Lexer.o can be build. +# +# In an sdist however, Lexer.hs is present in the source directory. It was +# copied there during the creation of the sdist by a rule in +# sdist-ghc-file.mk. And this time we *don't* know how to generate the +# Lexer.hs in the build directory, because 1) alex is not installed when +# building from sdist and 2) the sdist creation process renamed Lexer.x to +# Lexer.x.source. So normally make would now choose the second rule: Lexer.o +# will depend on Lexer.hs in the source directory, for which nothing needs to +# be done, and then Lexer.o can be build. +# +# There is however another actor in play, a rule in sdist-ghc-file.mk, which +# after after instantiating with the same directory ($1=utils/genprimops) and +# distdir ($2=dist) looks like this: +# +# sdist_utils/genprimops_dist_Lexer : utils/genprimops/dist/build/Lexer.hs +# +# Note that this is not an implicit rule, there aren't any %'s. This rule +# *explicitly* depends on Lexer.hs in the build directory. What follows is the +# following: +# +# * make thinks Lexer.hs in the build directory "ought to exist" [1], +# because it is an explicit dependency of /some/ target. +# +# * this puts our two implicit rules on equal footing: one depends on a +# file that exists, the other on a file that ought to exist. Make's +# implicit rule search algorithm doesn't distinguish between these two +# cases [1]. +# +# * to break the tie, make chooses the rule that is defined first. Lexer.o +# will depend on Lexer.hs in the build directory, which doesn't exist, +# and which make doesn't know how to build, causing a build failure. +# +# To prevent this from happening we define rules for haskell source files in +# the source directory before those in the distdir. +# +# Alternative solutions: +# +# * Don't include the explicit rule above when not creating an sdist, as +# that is the only time when it is needed. +# +# * Merge the two implicit rules, with help from $1_$2_HS_SRCS from +# hs-sources.mk, which is sdist aware. +# +# * Require alex and happy to be installed when building from an sdist, +# simplifying all this drastically. +# +# [1] https://www.gnu.org/software/make/manual/make.html#Implicit-Rule-Search + +$$(foreach dir,$$($1_$2_HS_SRC_DIRS),\ + $$(eval $$(call hs-suffix-way-rules-srcdir,$1,$2,$3,$$(dir)))) + + ifneq "$$(BINDIST)" "YES" $1/$2/build/%.$$($3_hcsuf) : $1/$2/build/%.hs $$(LAX_DEPS_FOLLOW) $$$$($1_$2_HC_DEP) @@ -45,8 +125,6 @@ $1/$2/build/%.$$($3_osuf) : $1/$2/build/autogen/%.hs $$(LAX_DEPS_FOLLOW) $$$$($1 endif -$$(foreach dir,$$($1_$2_HS_SRC_DIRS),\ - $$(eval $$(call hs-suffix-way-rules-srcdir,$1,$2,$3,$$(dir)))) endif From git at git.haskell.org Sat Jun 6 17:53:08 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 6 Jun 2015 17:53:08 +0000 (UTC) Subject: [commit: ghc] master: Fix the build when SplitObjs=YES (89223ce) Message-ID: <20150606175308.D7B263A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/89223ce1340654455a9f3aa9cbf25f30884227fd/ghc >--------------------------------------------------------------- commit 89223ce1340654455a9f3aa9cbf25f30884227fd Author: Thomas Miedema Date: Sat Jun 6 18:47:05 2015 +0200 Fix the build when SplitObjs=YES The default (perf) build, which sets SplitObjs=YES, was broken with commit 5dd02864a844bcf6fe0018755ff261affdef3fea. I accidently removed the wrong `endif`. This should fix it. >--------------------------------------------------------------- 89223ce1340654455a9f3aa9cbf25f30884227fd rules/build-perl.mk | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/rules/build-perl.mk b/rules/build-perl.mk index 46cf053..b943e16 100644 --- a/rules/build-perl.mk +++ b/rules/build-perl.mk @@ -29,6 +29,7 @@ $$(error $1_$2_PROGNAME is not set) endif ifneq "$$($1_$2_PROG)" "" $$(error $1_$2_PROG is set) +endif $1_$2_PROG = $$($1_$2_PROGNAME) ifneq "$$($$($1_$2_PROG)_INPLACE)" "" @@ -39,7 +40,6 @@ $$($1_$2_PROG)_INPLACE = $$(INPLACE_TOPDIR)/$$($1_$2_PROG) else $$($1_$2_PROG)_INPLACE = $$(INPLACE_BIN)/$$($1_$2_PROG) endif -endif $1_$2_INPLACE = $$($$($1_$2_PROG)_INPLACE) From git at git.haskell.org Mon Jun 8 08:16:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 8 Jun 2015 08:16:16 +0000 (UTC) Subject: [commit: ghc] wip/spj-improvement: Checkpoint on improving improvement (4a9bb76) Message-ID: <20150608081616.A4A233A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/spj-improvement Link : http://ghc.haskell.org/trac/ghc/changeset/4a9bb76f932a06eb94dc14ad50f34fd14e1ddaf2/ghc >--------------------------------------------------------------- commit 4a9bb76f932a06eb94dc14ad50f34fd14e1ddaf2 Author: Simon Peyton Jones Date: Thu May 7 09:07:51 2015 +0100 Checkpoint on improving improvement This patch allows unification variables to unify with fmvs, So that from, say alpha ~ fmv we get alpha := fmv But it iterates forever on F alpha ~ alpha because we flatten to F alpha ~ fmv alpha ~ fmv then unify to F fmv ~ fmv The unflatten F beta ~ beta and we are back to where we started. Dimitrios and I have new idas about saturation; I just wanted to commit this to a branch. >--------------------------------------------------------------- 4a9bb76f932a06eb94dc14ad50f34fd14e1ddaf2 compiler/typecheck/TcCanonical.hs | 6 +++-- compiler/typecheck/TcFlatten.hs | 20 ++++++++++++----- compiler/typecheck/TcInteract.hs | 28 +++++++++++++++--------- compiler/typecheck/TcSMonad.hs | 46 ++++++++++++++++++++++++--------------- compiler/typecheck/TcSimplify.hs | 16 +++++++------- compiler/typecheck/TcType.hs | 9 ++++---- 6 files changed, 77 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 4a9bb76f932a06eb94dc14ad50f34fd14e1ddaf2 From git at git.haskell.org Mon Jun 8 08:16:19 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 8 Jun 2015 08:16:19 +0000 (UTC) Subject: [commit: ghc] wip/spj-improvement: New checkpoint on improvign improvement (59a6749) Message-ID: <20150608081619.6898D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/spj-improvement Link : http://ghc.haskell.org/trac/ghc/changeset/59a6749d82f95924e235bbc009b282d2f2c63910/ghc >--------------------------------------------------------------- commit 59a6749d82f95924e235bbc009b282d2f2c63910 Author: Simon Peyton Jones Date: Fri Jun 5 17:42:56 2015 +0100 New checkpoint on improvign improvement >--------------------------------------------------------------- 59a6749d82f95924e235bbc009b282d2f2c63910 compiler/typecheck/TcCanonical.hs | 11 +- compiler/typecheck/TcFlatten.hs | 103 +++--- compiler/typecheck/TcInteract.hs | 284 +++++++++------- compiler/typecheck/TcRnTypes.hs | 14 + compiler/typecheck/TcSMonad.hs | 365 ++++++++++++++------- .../tests/typecheck/should_fail/tcfail122.stderr | 4 +- testsuite/tests/typecheck/should_fail/tcfail138.hs | 2 +- .../tests/typecheck/should_fail/tcfail201.stderr | 2 +- 8 files changed, 486 insertions(+), 299 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 59a6749d82f95924e235bbc009b282d2f2c63910 From git at git.haskell.org Mon Jun 8 08:16:22 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 8 Jun 2015 08:16:22 +0000 (UTC) Subject: [commit: ghc] wip/spj-improvement's head updated: New checkpoint on improvign improvement (59a6749) Message-ID: <20150608081622.7374E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/spj-improvement' now includes: 4efa421 Permit empty closed type families 63a10bb arm: Force non-executable stack (#10369) f7dfcef Fix safeHaskell test for llvm backend bf4f3e6 Give a hint when a TH splice has a bad package key, partially fixes #10279 cdba973 Documentation for Language.Haskell.TH.Quote. 1a4374c arm: Force non-executable stack (part 2) 341a766 Doc: checkCrossStageLifting, RnSplice/TcExpr is untyped/typed brackets (#10384) f7daf5a Normalise type families in the type of an expression 458a97b Fix typo: identifer -> identifier 03c4893 Retain ic_monad and ic_int_print from external packages after load 477f514 rts: add "-no-rtsopts-suggestions" option fa0474d base: Fix confusing docs typo fb54b2c API Annotations : add Locations in hsSyn were layout occurs caeae1a Correct parsing of lifted empty list constructor 15aafc7 ApiAnnotations : quoted type variables missing leading quote 81030ed ApiAnnotations : Nested forall loses forall annotation f34c072 Revert "ApiAnnotations : Nested forall loses forall annotation" 97d320f Revert "API Annotations : add Locations in hsSyn were layout occurs" d1295da Comments only 931d014 A bit of refactoring RnSplice c3e6b3a Regression test for Trac #10390 5bde9f7 ApiAnnotations : RdrHsSyn.isFunLhs discards parentheses cc9b788 Backpack docs: meditate on AvailTC with four examples. 225df19 ApiAnnotations : AnnComma missing in TupleSection 7136126 ApiAnnotations: misplaced AnnComma for squals production 2601a43 Backpack docs: AvailInfo plan, and why selectors are hard. 28257ca Support stage 1 Template Haskell (non-quasi) quotes, fixes #10382. 21c72e7 Split off quotes/ from th/ for tests that can be done on stage1 compiler. eb0ed40 RnSplice's staging test should be applied for quotes in stage1. 9a43b2c Always do polymorphic typed quote check, c.f. #10384 3c70ae0 Quick fix: drop base bound on template-haskell. 5c459ee Revert stage 1 template-haskell. This is a combination of 5 commits. 811b72a Api Annotations: RdrHsSyn.mkAtDefault causes annotations to be disconnected. e4032b1 ApiAnnotations : mkGadtDecl discards annotations for HsFunTy 27aa733 IdInfo comment update 2666ba3 haddock: update submodule to fix #10206 cf7573b More accurate allocation stats for :set +s 9736c04 compiler: make sure we reject -O + HscInterpreted 24707d7 ApiAnnotations : BooleanFormula construction discards original f35d621 Fix build breakage from 9736c042 fe38195 ApiAnnotations : pquals production adds AnnVbar in the wrong place ecc3d6b ApiAnnotations : PatBind gives wrong SrcSpan for the pattern. f16ddce Support stage 1 Template Haskell (non-quasi) quotes, fixes #10382. b0784cc Backpack docs: more carefully describe unification versus unioning. b4f6c16 Ignore out and toc files. 53409a7 Backpack docs: proper discourse on ModIface and ModDetails. eecef17 Fix safe haskell bug: instances in safe-inferred 4fffbc3 New handling of overlapping inst in Safe Haskell ef7ed16 Make template-haskell build with GHC 7.6, fixes bootstrap build. c119a80 Use fmap instead of <$> (Fixes #10407) ca7c855 We need an empty boolFormula.stderr f5188f3 Fix weird behavior of -ignore-dot-ghci and -ghci-scipt 6ee4b6f Turn off warnings when compiling boolFormula 1b47692 Backpack docs: Consistently italicize metavariables. 4432863 Update some tests for recent Safe Haskell change. a171cc1 Update Safe Haskell documentation. 4b8b4ce Fix fragile T9579 tests 8764a7e Revert D727 8da785d Delete commented-out line 130e93a Refactor tuple constraints 5910a1b Change in capitalisation of error msg a154944 Two wibbles to fix the build a8493e0 Fix imports in HscMain (stage2) 6e1174d Separate transCloVarSet from fixVarSet 51cbad1 Update haddock submodule ca173aa Add a case to checkValidTyCon eb6ca85 Make the "matchable-given" check happen first c0aae6f Test Trac #10248 a9ccd37 Test Trac #10403 04a484e Test Trac #10359 3cf8ecd Revert multiple commits 3ef7fce Do not check dir perms when .ghci doesn't exist 5972037 Backpack docs: Rewrite type checking section to have a more concrete plan. ab45de1 Failing test for #10420 using plugins. c256357 Speed up elimCommonBlocks by grouping blocks also by outgoing labels 8e4dc8f Greatly speed up nativeCodeGen/seqBlocks 73f836f CmmCommonBlockElim: Improve hash function 3f42de5 Test Trac #10359 f1f265d Test Trac #10403 fa0bdd3 Test Trac #10248 76024fd Delete commented-out line ffc2150 Refactor tuple constraints 228ddb9 Make the "matchable-given" check happen first eaaa38b includes/stg/SMP.h: implement simple load_/store_load_barrier on armv6 and older 85bf9e4 Add regression test for #10110. 5cbac88 user guide: correct documentation for -Wall (fixes #10386) 578d2ba Remove unneeded compatibility with LLVM < 3.6 b03f074 ghci: Allow :back and :forward to take counts b0b11ad In ghci linker, link against all previous temp sos (#10322) b199536 compiler: make sure we reject -O + HscInterpreted 470a949 Revert "In ghci linker, link against all previous temp sos (#10322)" 753b156 Add a TODO FIXME w.r.t. D894 fc8c5e7 Test Trac #8799, #8555 edb8dc5 Revert "compiler: make sure we reject -O + HscInterpreted" (again) 25d1a71 Fix error messages from open(Binary)TempFileWithDefaultPermissions c934914 Backpack docs: Clarifications from today's Skype call. 9f968e9 Fix binary instance for IfaceLitTy c553e98 ApiAnnotations : AST version of nested forall loses forall annotation 0df14b5 ApiAnnotations : parens around a context with wildcard loses annotations c488da8 ApiAnnotatons : AnnDcolon in wrong place for PatBind 369dd0c White space layout only eae703a Reduce magic for seqId c89bd68 Fix quadratic behaviour in tidyOccName 45d9a15 Fix a huge space leak in the mighty Simplifier 7d519da testsuite: commit missing T4945 stdout 4d6c0ee compiler: kill a stray pprTrace in OccName 6694ccf testsuite: handle missing stats files gracefully (#10305) c00f051 Update .mailmap c04571d rts: Fix typo in comment 326989e Add missing name for FFI import (fixes #9950) 70f1ca4 Fix ghci-way tests of -XStaticPointers. 71d1f01 Omit the static form error for variables not in scope. 388448b Build system: don't install haddock .t files (#10410) c591147 ApiAnnotations tweaks ef90466 Testdriver: don't use os.popen in config/ghc ce166a3 Testdriver: do not interfer with MinGW path magic (#10449) 640fe14 Remove unnecessary loadInterface for TH quoted name. e28462d base: fix #10298 & #7695 b0d8ba3 Add liftData function. a138fa1 Testsuite: accept new output for T2507 and T8959a 5ead7d1 Build system: make more targets PHONY 4c7d177 Build system: remove toplevel target `fast` a065a3a Build system: use `mkdir -p` instead of `-mkdir` 51aacde Build system: allow missing config.mk for target clean_% 4de8028 Build system: check $CLEANING instead of $MAKECMDGOALS 47e00ec Build system: don't set CLEANING=NO b0885e4 Build system: whitespace and comments only cd0e2f5 Build system: prevent "--version: Command not found" 0bfd05e Build system: prevent "./Setup: Command not found" a49070e Build system: time's config files have moved 48ed2f1 Build system: always allow me to clean haddock 577d315 Build system: always use `make -r` 0d20d76 Build system: make clean in utils/ghc-pkg should not delete inplace/lib/bin 0a159e3 Build system: don't use supposedly local variable inside macro 018fec0 Build system: also clean the inplace wrapper 508a3a3 Build system: don't build runghc if GhcWithInterpreter=NO (#10261) 7db2dec linker_unload working on Windows, fixes #8292. 5a65da4 Don't run T9330fail on Windows, no clobber occurs. #9930 94fff17 Travis: use validate --quiet to prevent hitting log file limits 4756438 Catch canonicalizePath exceptions, fix #10101 a52f144 In ghci linker, link against all previous temp sos (#10322) f5b43ce compiler/specialise: shut match_co up a bit f6ca695 rts: Fix aarch64 implementation of xchg e00910b ApiAnnotations : rationalise tests 7dd0ea7 Update binary submodule to 0.7.5.0 release e6191d1 ApiAnnotations : strings in warnings do not return SourceText e8a7254 Add constraint creation functions to TcPluginM API 1c38325 Fix dropped event registrations 928f536 Use seq rather than (==) to force the size 5eee6a1 Move seqExpr, seqIdInfo etc to CoreUtils 20d8621 Add some missing seqs to Coercion.seqCo d245787 Use named fields in SimplCont.Select constructor 403cfc9 Comments only 931268a Replace tabs with spaces. 98b0b2e Add information about allowed foreign prim args, see #10460. e5be846 Typofix: missing period. (#10460) a27fb46 Add (failing) test case for #7672. f82e866 Newline after type of allocate(). dfdc50d Don't call DEAD_WEAK finalizer again on shutdown (#7170) 34dcf8a Re-center perf numbers for T5631 2f0011a White space only 11d8f84 Treat pattern-synonym binders more consistently 9b73cb1 Refactor the GlobalRdrEnv, fixing #7672 90fde52 Mark sigof02 tests as expect_broken 1189196 Re-do superclass solving (again); fixes #10423 b095c97 Improve constraint tuples (Trac #10451) dbcdfe2 Set 32-bit perf figure d6c01fa Remove redundant import b1b2b44 Test Trac #10423 8a38348 Test Trac #10451 8e5f8cf Test Trac #10466 b2b69b2 Test Trac #10438 091944e compiler: make sure we reject -O + HscInterpreted e796026 build: make haddock a bit less chatty 3758050 Improve FFI error reporting 5688053 Detabify a programlisting in the User's Guide (#10425) 942a074 testsuite: mark test T9938 (#9938) as passing again 7a82b77 newTempName: Do not include pid in basename 2c4c627 Typofixes 6adfb88 Suggest -H to improve GC productivity, fixes #10474. 7b6800c Remove outdated uBackpack docs. 7ea156a Refactor RdrName.Provenance, to fix #7672 4a9bb76 Checkpoint on improving improvement 59a6749 New checkpoint on improvign improvement From git at git.haskell.org Mon Jun 8 10:59:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 8 Jun 2015 10:59:35 +0000 (UTC) Subject: [commit: ghc] master: Fix for CAF retention when dynamically loading & unloading code (19ec6a8) Message-ID: <20150608105935.25ACD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/19ec6a84d6344c2808d0d41da11956689a0e4ae9/ghc >--------------------------------------------------------------- commit 19ec6a84d6344c2808d0d41da11956689a0e4ae9 Author: Simon Marlow Date: Mon Jun 8 11:54:51 2015 +0100 Fix for CAF retention when dynamically loading & unloading code In a situaion where we have some statically-linked code and we want to load and unload a series of objects, we need the CAFs in the statically-linked code to be retained indefinitely, while the CAFs in the dynamically-linked code should be GC'd as normal, so that we can detect when the code is unloadable. This was wrong before - we GC'd CAFs in the static code, leading to a crash in the rare case where we use a CAF, GC it, and then load a new object that uses it again. I also did some tidy up: RtsConfig now has a field keep_cafs to indicate whether we want CAFs to be retained in static code. >--------------------------------------------------------------- 19ec6a84d6344c2808d0d41da11956689a0e4ae9 includes/RtsAPI.h | 3 +++ includes/rts/storage/GC.h | 6 ++++-- rts/Linker.c | 6 +++--- rts/RtsFlags.c | 1 + rts/RtsStartup.c | 6 +++++- rts/sm/Storage.c | 41 ++++++++++++++++++++++++++++++++++------- 6 files changed, 50 insertions(+), 13 deletions(-) diff --git a/includes/RtsAPI.h b/includes/RtsAPI.h index 3b6de0f..4748060 100644 --- a/includes/RtsAPI.h +++ b/includes/RtsAPI.h @@ -73,6 +73,9 @@ typedef struct { // True if GHC was not passed -no-hs-main HsBool rts_hs_main; + // Whether to retain CAFs (default: false) + HsBool keep_cafs; + // Called before processing command-line flags, so that default // settings for RtsFlags can be provided. void (* defaultsHook) (void); diff --git a/includes/rts/storage/GC.h b/includes/rts/storage/GC.h index 444ef88..f7da838 100644 --- a/includes/rts/storage/GC.h +++ b/includes/rts/storage/GC.h @@ -200,11 +200,13 @@ void performMajorGC(void); The CAF table - used to let us revert CAFs in GHCi -------------------------------------------------------------------------- */ -StgInd *newCAF (StgRegTable *reg, StgIndStatic *caf); -StgInd *newDynCAF (StgRegTable *reg, StgIndStatic *caf); +StgInd *newCAF (StgRegTable *reg, StgIndStatic *caf); +StgInd *newRetainedCAF (StgRegTable *reg, StgIndStatic *caf); +StgInd *newGCdCAF (StgRegTable *reg, StgIndStatic *caf); void revertCAFs (void); // Request that all CAFs are retained indefinitely. +// (preferably use RtsConfig.keep_cafs instead) void setKeepCAFs (void); /* ----------------------------------------------------------------------------- diff --git a/rts/Linker.c b/rts/Linker.c index 9d3ca12..bbf75bf 100644 --- a/rts/Linker.c +++ b/rts/Linker.c @@ -1512,7 +1512,7 @@ RTS_LIBFFI_SYMBOLS #define SymE_NeedsDataProto(vvv) SymE_HasDataProto(vvv) // SymI_HasProto_redirect allows us to redirect references to one symbol to -// another symbol. See newCAF/newDynCAF for an example. +// another symbol. See newCAF/newRetainedCAF/newGCdCAF for an example. #define SymI_HasProto_redirect(vvv,xxx) \ { MAYBE_LEADING_UNDERSCORE_STR(#vvv), \ (void*)(&(xxx)) }, @@ -1692,10 +1692,10 @@ initLinker_ (int retain_cafs) barf("ghciInsertSymbolTable failed"); } - // Redurect newCAF to newDynCAF if retain_cafs is true. + // Redurect newCAF to newRetainedCAF if retain_cafs is true. if (! ghciInsertSymbolTable(WSTR("(GHCi built-in symbols)"), symhash, MAYBE_LEADING_UNDERSCORE_STR("newCAF"), - retain_cafs ? newDynCAF : newCAF, + retain_cafs ? newRetainedCAF : newGCdCAF, HS_BOOL_FALSE, NULL)) { barf("ghciInsertSymbolTable failed"); } diff --git a/rts/RtsFlags.c b/rts/RtsFlags.c index 94a6c0e..4e23eb8 100644 --- a/rts/RtsFlags.c +++ b/rts/RtsFlags.c @@ -62,6 +62,7 @@ const RtsConfig defaultRtsConfig = { .rts_opts_suggestions = rtsTrue, .rts_opts = NULL, .rts_hs_main = rtsFalse, + .keep_cafs = rtsFalse, .defaultsHook = FlagDefaultsHook, .onExitHook = OnExitHook, .stackOverflowHook = StackOverflowHook, diff --git a/rts/RtsStartup.c b/rts/RtsStartup.c index c50bb07..f6544b6 100644 --- a/rts/RtsStartup.c +++ b/rts/RtsStartup.c @@ -138,12 +138,16 @@ hs_init_ghc(int *argc, char **argv[], RtsConfig rts_config) stat_startInit(); /* Set the RTS flags to default values. */ - initRtsFlagsDefaults(); /* Call the user hook to reset defaults, if present */ rts_config.defaultsHook(); + /* Whether to GC CAFs */ + if (rts_config.keep_cafs) { + setKeepCAFs(); + } + /* Parse the flags, separating the RTS flags from the programs args */ if (argc == NULL || argv == NULL) { // Use a default for argc & argv if either is not supplied diff --git a/rts/sm/Storage.c b/rts/sm/Storage.c index 85884fa..7779601 100644 --- a/rts/sm/Storage.c +++ b/rts/sm/Storage.c @@ -416,8 +416,8 @@ newCAF(StgRegTable *reg, StgIndStatic *caf) { // Note [dyn_caf_list] // If we are in GHCi _and_ we are using dynamic libraries, - // then we can't redirect newCAF calls to newDynCAF (see below), - // so we make newCAF behave almost like newDynCAF. + // then we can't redirect newCAF calls to newRetainedCAF (see below), + // so we make newCAF behave almost like newRetainedCAF. // The dynamic libraries might be used by both the interpreted // program and GHCi itself, so they must not be reverted. // This also means that in GHCi with dynamic libraries, CAFs are not @@ -464,17 +464,17 @@ setKeepCAFs (void) keepCAFs = 1; } -// An alternate version of newCaf which is used for dynamically loaded +// An alternate version of newCAF which is used for dynamically loaded // object code in GHCi. In this case we want to retain *all* CAFs in // the object code, because they might be demanded at any time from an // expression evaluated on the command line. // Also, GHCi might want to revert CAFs, so we add these to the // revertible_caf_list. // -// The linker hackily arranges that references to newCaf from dynamic -// code end up pointing to newDynCAF. -StgInd * -newDynCAF (StgRegTable *reg, StgIndStatic *caf) +// The linker hackily arranges that references to newCAF from dynamic +// code end up pointing to newRetainedCAF. +// +StgInd* newRetainedCAF (StgRegTable *reg, StgIndStatic *caf) { StgInd *bh; @@ -491,6 +491,33 @@ newDynCAF (StgRegTable *reg, StgIndStatic *caf) return bh; } +// If we are using loadObj/unloadObj in the linker, then we want to +// +// - retain all CAFs in statically linked code (keepCAFs == rtsTrue), +// because we might link a new object that uses any of these CAFs. +// +// - GC CAFs in dynamically-linked code, so that we can detect when +// a dynamically-linked object is unloadable. +// +// So for this case, we set keepCAFs to rtsTrue, and link newCAF to newGCdCAF +// for dynamically-linked code. +// +StgInd* newGCdCAF (StgRegTable *reg, StgIndStatic *caf) +{ + StgInd *bh; + + bh = lockCAF(reg, caf); + if (!bh) return NULL; + + // Put this CAF on the mutable list for the old generation. + if (oldest_gen->no != 0) { + recordMutableCap((StgClosure*)caf, + regTableToCapability(reg), oldest_gen->no); + } + + return bh; +} + /* ----------------------------------------------------------------------------- Nursery management. -------------------------------------------------------------------------- */ From git at git.haskell.org Mon Jun 8 16:48:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 8 Jun 2015 16:48:30 +0000 (UTC) Subject: [commit: ghc] wip/spj-improvement: Further checkpoint (fa1c29b) Message-ID: <20150608164830.2A4A33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/spj-improvement Link : http://ghc.haskell.org/trac/ghc/changeset/fa1c29bcbd769debafffc3cf477335010b8246d1/ghc >--------------------------------------------------------------- commit fa1c29bcbd769debafffc3cf477335010b8246d1 Author: Simon Peyton Jones Date: Mon Jun 8 17:48:30 2015 +0100 Further checkpoint >--------------------------------------------------------------- fa1c29bcbd769debafffc3cf477335010b8246d1 compiler/typecheck/TcCanonical.hs | 26 +-- compiler/typecheck/TcFlatten.hs | 5 +- compiler/typecheck/TcInteract.hs | 149 ++++--------- compiler/typecheck/TcRnTypes.hs | 29 ++- compiler/typecheck/TcSMonad.hs | 240 +++++++++------------ compiler/typecheck/TcSimplify.hs | 7 +- .../tests/indexed-types/should_fail/T2544.stderr | 21 +- .../tests/indexed-types/should_fail/T2627b.stderr | 6 +- .../tests/indexed-types/should_fail/T6123.stderr | 8 +- .../tests/typecheck/should_compile/Improvement.hs | 1 + testsuite/tests/typecheck/should_compile/tc237.hs | 3 + .../tests/typecheck/should_fail/IPFail.stderr | 15 +- testsuite/tests/typecheck/should_fail/T5236.hs | 10 +- testsuite/tests/typecheck/should_fail/T5853.stderr | 25 ++- testsuite/tests/typecheck/should_fail/T5978.hs | 3 + testsuite/tests/typecheck/should_fail/T5978.stderr | 6 +- .../typecheck/should_fail/TcCoercibleFail.stderr | 19 +- .../tests/typecheck/should_fail/tcfail122.stderr | 4 +- .../tests/typecheck/should_fail/tcfail143.stderr | 4 +- 19 files changed, 257 insertions(+), 324 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc fa1c29bcbd769debafffc3cf477335010b8246d1 From git at git.haskell.org Tue Jun 9 01:39:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 9 Jun 2015 01:39:54 +0000 (UTC) Subject: [commit: ghc] master: Revert "docs: Fix #10416" (7944a68) Message-ID: <20150609013954.3E99B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7944a68f0a91033f50c5d0c56e923948bba30be1/ghc >--------------------------------------------------------------- commit 7944a68f0a91033f50c5d0c56e923948bba30be1 Author: Austin Seipp Date: Mon Jun 8 20:39:46 2015 -0500 Revert "docs: Fix #10416" This causes the buildbots and other users to choke when building the user documentation, but I haven't figured out why. This reverts commit dcaaa980dc59202744bb3888d9662f9a7558cdf6. >--------------------------------------------------------------- 7944a68f0a91033f50c5d0c56e923948bba30be1 docs/users_guide/profiling.xml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/docs/users_guide/profiling.xml b/docs/users_guide/profiling.xml index 84f96b1..4971a7d 100644 --- a/docs/users_guide/profiling.xml +++ b/docs/users_guide/profiling.xml @@ -625,7 +625,7 @@ MAIN MAIN 102 0 0.0 0.0 100.0 1 other than making the PS file generation work, rather than falling over. The result seems to be broken PS on the page with the image. --> - You might also want to take a look From git at git.haskell.org Tue Jun 9 02:48:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 9 Jun 2015 02:48:43 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: testsuite: Fix minor print007 fallout (9c657e5) Message-ID: <20150609024843.2FB403A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/9c657e57c68c8e3ab1a5310ecf046a03a964e24a/ghc >--------------------------------------------------------------- commit 9c657e57c68c8e3ab1a5310ecf046a03a964e24a Author: Austin Seipp Date: Mon Jun 8 21:42:43 2015 -0500 testsuite: Fix minor print007 fallout This was from fixing #10052. Signed-off-by: Austin Seipp >--------------------------------------------------------------- 9c657e57c68c8e3ab1a5310ecf046a03a964e24a testsuite/tests/ghci.debugger/scripts/print007.stderr | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/ghci.debugger/scripts/print007.stderr b/testsuite/tests/ghci.debugger/scripts/print007.stderr index 0debeb4..7b943f9 100644 --- a/testsuite/tests/ghci.debugger/scripts/print007.stderr +++ b/testsuite/tests/ghci.debugger/scripts/print007.stderr @@ -1,6 +1,6 @@ -: warning: +: Warning: -O conflicts with --interactive; -O ignored. -: warning: +: Warning: -O conflicts with --interactive; -O ignored. From git at git.haskell.org Tue Jun 9 02:48:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 9 Jun 2015 02:48:45 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: testsuite: fix T9858e fallout (670c39f) Message-ID: <20150609024845.E67A23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/670c39fb2a3268c790eafe6c2d1949531f8a1bb7/ghc >--------------------------------------------------------------- commit 670c39fb2a3268c790eafe6c2d1949531f8a1bb7 Author: Austin Seipp Date: Mon Jun 8 21:43:57 2015 -0500 testsuite: fix T9858e fallout From 28943a8925427a5aafa7013e3ad47ff4511985da, in which I forgot about the 'error:' thing. Signed-off-by: Austin Seipp >--------------------------------------------------------------- 670c39fb2a3268c790eafe6c2d1949531f8a1bb7 testsuite/tests/typecheck/should_fail/T9858e.stderr | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/typecheck/should_fail/T9858e.stderr b/testsuite/tests/typecheck/should_fail/T9858e.stderr index 10d65b9..53ae2b9 100644 --- a/testsuite/tests/typecheck/should_fail/T9858e.stderr +++ b/testsuite/tests/typecheck/should_fail/T9858e.stderr @@ -1,4 +1,5 @@ -T9858e.hs:9:8: error: + +T9858e.hs:9:8: Couldn't match type ?Eq Int => Int? with ?a0 b0? Expected type: Proxy (a0 b0) Actual type: Proxy (Eq Int => Int) From git at git.haskell.org Tue Jun 9 02:48:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 9 Jun 2015 02:48:49 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: testsuite: Add test for #10489 (2237c98) Message-ID: <20150609024849.04AFE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/2237c9818c1cc719560821c3153ac2059094fdd5/ghc >--------------------------------------------------------------- commit 2237c9818c1cc719560821c3153ac2059094fdd5 Author: Austin Seipp Date: Mon Jun 8 21:47:48 2015 -0500 testsuite: Add test for #10489 This is half of 61b96a86c5342fb1c850361177d60fe855d948f6 essentially - just to make sure the 7.10 branch doesn't regress on #10489. Signed-off-by: Austin Seipp >--------------------------------------------------------------- 2237c9818c1cc719560821c3153ac2059094fdd5 testsuite/tests/typecheck/should_compile/T10489.hs | 3 +++ testsuite/tests/typecheck/should_compile/all.T | 1 + 2 files changed, 4 insertions(+) diff --git a/testsuite/tests/typecheck/should_compile/T10489.hs b/testsuite/tests/typecheck/should_compile/T10489.hs new file mode 100644 index 0000000..892965e --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T10489.hs @@ -0,0 +1,3 @@ +module T10489 where + +convert d = let d' = case d of '0' -> '!' in d' diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index af58fcd..7bb37b4 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -444,3 +444,4 @@ test('T10177', normal, compile, ['']) test('T10195', normal, compile, ['']) test('T10109', normal, compile, ['']) test('T10335', normal, compile, ['']) +test('T10489', normal, compile, ['']) From git at git.haskell.org Tue Jun 9 02:48:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 9 Jun 2015 02:48:51 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Fix #10488 by unwrapping type synonyms. (b901f0f) Message-ID: <20150609024851.C0E103A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/b901f0f6cd3032707b53af4d2fe8e856e015cf2c/ghc >--------------------------------------------------------------- commit b901f0f6cd3032707b53af4d2fe8e856e015cf2c Author: Richard Eisenberg Date: Thu Jun 4 17:05:02 2015 -0400 Fix #10488 by unwrapping type synonyms. Summary: Previously, I had forgotten to unwrap vanilla type synonyms in the "flattener" that is used around the closed-type-family apartness check. Test Plan: validate Reviewers: austin Subscribers: bgamari, thomie Differential Revision: https://phabricator.haskell.org/D955 GHC Trac Issues: #10488 (cherry picked from commit 761fb7c4869a081da7320e4307dcb947b5ed95d1) >--------------------------------------------------------------- b901f0f6cd3032707b53af4d2fe8e856e015cf2c compiler/types/FamInstEnv.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/compiler/types/FamInstEnv.hs b/compiler/types/FamInstEnv.hs index a8ddda3..808dece 100644 --- a/compiler/types/FamInstEnv.hs +++ b/compiler/types/FamInstEnv.hs @@ -1013,6 +1013,8 @@ coreFlattenTys in_scope = go [] coreFlattenTy :: InScopeSet -> FlattenMap -> Type -> (FlattenMap, Type) coreFlattenTy in_scope = go where + go m ty | Just ty' <- coreView ty = go m ty' + go m ty@(TyVarTy {}) = (m, ty) go m (AppTy ty1 ty2) = let (m1, ty1') = go m ty1 (m2, ty2') = go m1 ty2 in From git at git.haskell.org Tue Jun 9 04:34:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 9 Jun 2015 04:34:23 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Update binary submodule to 0.7.5.0 release (1ac6198) Message-ID: <20150609043423.1DB153A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/1ac61980743d790d7e69b7781d0ff0afb715959e/ghc >--------------------------------------------------------------- commit 1ac61980743d790d7e69b7781d0ff0afb715959e Author: Herbert Valerio Riedel Date: Mon Jun 1 10:50:17 2015 +0200 Update binary submodule to 0.7.5.0 release Quoting the changelog, this pulls in the following fixes: binary-0.7.5.0 -------------- - Fix performance bug that was noticable when you get a big strict ByteString and the input to the decoder consists of many small chunks. - https://github.com/kolmodin/binary/issues/73 - https://github.com/kolmodin/binary/pull/76 - Fix memory leak when decoding Double and Float. - Commit 497a181c083fa9faf7fa3aa64d1d8deb9ac76ecb - We now require QuickCheck >= 2.8. Remove our version of arbitrarySizedNatural. binary-0.7.4.0 -------------- - Some invalid UTF-8 strings caused an exception when decoded. Those errors will now now fail in the Get monad instead. See issue 70. Patch contributed by @ttuegel. (cherry picked from commit 7dd0ea7428379df848e3d13528921b39b7bf5b95) >--------------------------------------------------------------- 1ac61980743d790d7e69b7781d0ff0afb715959e libraries/binary | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/binary b/libraries/binary index ff9a48f..86e4c9a 160000 --- a/libraries/binary +++ b/libraries/binary @@ -1 +1 @@ -Subproject commit ff9a48fb213c2d1fd2e58b19c92264a3efadff7a +Subproject commit 86e4c9a6125cdddb0592a653f48c699a574ccf7b From git at git.haskell.org Tue Jun 9 05:10:22 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 9 Jun 2015 05:10:22 +0000 (UTC) Subject: [commit: ghc] master: Refactor wild card renaming (058af6c) Message-ID: <20150609051022.DDEE53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/058af6c90a0e8d122f2d1339b6b4fd0b5ec83d05/ghc >--------------------------------------------------------------- commit 058af6c90a0e8d122f2d1339b6b4fd0b5ec83d05 Author: Thomas Winant Date: Mon Jun 8 23:45:48 2015 -0500 Refactor wild card renaming Summary: Refactor wild card error reporting * Merge `HsWildcardTy` and `HsNamedWildcardTy` into one constructor `HsWildCardTy` with as field the new type `HsWildCardInfo`, which has two constructors: `AnonWildCard` and `NamedWildCard`. * All partial type checks are removed from `RdrHsSyn.hs` and are now done during renaming in order to report better error messages. When wild cards are allowed in a type, the new function `rnLHsTypeWithWildCards` (or `rnHsSigTypeWithWildCards`) should be used. This will bring the named wild cards into scope before renaming them. When this is not done, renaming will trigger "Unexpected wild card..." errors. Unfortunately, this has to be done separately for anonymous wild cards because they are given a fresh name during renaming, so they will not cause an out-of-scope error. They are handled in `tc_hs_type`, as a special case of a lookup that fails. The previous opt-out approach is replaced with an opt-in approach. No more panics because of forgotten checks! * `[t| _ |]` isn't caught by the above two checks, so it is currently handled by a special case. The error message (generated in the `DsM` monad) doesn't provide as much context information as the other cases. * Instead of three (!) functions that walk `HsType`, there is now only one pure function called `collectWildCards`. * Alternative approach: catch all unwanted wild cards in `rnHsTyKi` by looking at the `HsDocContext`. This will reduce the number of places to catch unwanted wild cards form three to one, and make the error messages more uniform, albeit less informative, as the error context for renaming is not as informative as the one for type checking. A new constructor of `HsDocContext` will be required for pattern synonyms signatures. Small problem: currently type-class type signatures can't be distinguished from type signatures using the `HsDocContext`. This requires an update to the Haddock submodule. Test Plan: validate Reviewers: goldfire, simonpj, austin Reviewed By: simonpj Subscribers: bgamari, thomie, goldfire Differential Revision: https://phabricator.haskell.org/D613 GHC Trac Issues: #10098 >--------------------------------------------------------------- 058af6c90a0e8d122f2d1339b6b4fd0b5ec83d05 compiler/deSugar/DsMeta.hs | 5 + compiler/hsSyn/HsTypes.hs | 77 ++++-- compiler/hsSyn/PlaceHolder.hs | 1 + compiler/parser/Parser.y | 35 +-- compiler/parser/RdrHsSyn.hs | 274 +-------------------- compiler/rename/RnBinds.hs | 16 +- compiler/rename/RnExpr.hs | 10 +- compiler/rename/RnTypes.hs | 255 +++++++++++++------ compiler/typecheck/TcEnv.hs | 7 + compiler/typecheck/TcHsType.hs | 9 +- compiler/typecheck/TcRnDriver.hs | 5 +- compiler/typecheck/TcRnMonad.hs | 3 + .../ExtraConstraintsWildcardNotLast.stderr | 6 +- .../should_fail/ExtraConstraintsWildcardTwice.hs | 5 + .../ExtraConstraintsWildcardTwice.stderr | 5 + .../NamedExtraConstraintsWildcard.stderr | 6 +- .../should_fail/NamedWildcardsNotInMonotype.stderr | 8 +- .../NestedExtraConstraintsWildcard.stderr | 8 +- .../NestedNamedExtraConstraintsWildcard.stderr | 6 +- .../should_fail/PartialClassMethodSignature.hs | 2 +- .../should_fail/PartialClassMethodSignature.stderr | 6 +- .../should_fail/PartialClassMethodSignature2.hs | 5 + .../PartialClassMethodSignature2.stderr | 5 + .../should_fail/UnnamedConstraintWildcard1.stderr | 6 +- .../should_fail/UnnamedConstraintWildcard2.stderr | 6 +- .../partial-sigs/should_fail/WildcardInADT1.stderr | 6 +- .../partial-sigs/should_fail/WildcardInADT2.stderr | 6 +- .../partial-sigs/should_fail/WildcardInADT3.stderr | 6 +- .../should_fail/WildcardInADTContext1.stderr | 4 +- .../should_fail/WildcardInADTContext2.stderr | 4 +- .../should_fail/WildcardInDefault.stderr | 5 +- .../should_fail/WildcardInDefaultSignature.hs | 5 +- .../should_fail/WildcardInDefaultSignature.stderr | 7 +- .../should_fail/WildcardInDeriving.stderr | 4 +- .../should_fail/WildcardInForeignExport.stderr | 7 +- .../should_fail/WildcardInForeignImport.stderr | 7 +- .../should_fail/WildcardInGADT1.stderr | 6 +- .../should_fail/WildcardInGADT2.stderr | 5 +- .../should_fail/WildcardInInstanceHead.stderr | 4 +- .../should_fail/WildcardInInstanceSig.stderr | 5 +- .../should_fail/WildcardInNewtype.stderr | 6 +- .../should_fail/WildcardInPatSynSig.stderr | 5 +- .../WildcardInStandaloneDeriving.stderr | 4 +- .../should_fail/WildcardInTypeBrackets.stderr | 4 +- .../WildcardInTypeFamilyInstanceLHS.stderr | 6 +- .../WildcardInTypeFamilyInstanceRHS.stderr | 6 +- .../should_fail/WildcardInTypeSynonymRHS.stderr | 5 +- testsuite/tests/partial-sigs/should_fail/all.T | 2 + utils/haddock | 2 +- 49 files changed, 396 insertions(+), 496 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 058af6c90a0e8d122f2d1339b6b4fd0b5ec83d05 From git at git.haskell.org Tue Jun 9 07:46:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 9 Jun 2015 07:46:38 +0000 (UTC) Subject: [commit: ghc] wip/spj-improvement: Another checkpoint (a7017cc) Message-ID: <20150609074638.6A7B93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/spj-improvement Link : http://ghc.haskell.org/trac/ghc/changeset/a7017cc74c9dcbb8ffde54f8fd3cc8b4c15ac99b/ghc >--------------------------------------------------------------- commit a7017cc74c9dcbb8ffde54f8fd3cc8b4c15ac99b Author: Simon Peyton Jones Date: Tue Jun 9 08:46:08 2015 +0100 Another checkpoint >--------------------------------------------------------------- a7017cc74c9dcbb8ffde54f8fd3cc8b4c15ac99b compiler/typecheck/TcCanonical.hs | 18 ++-- compiler/typecheck/TcInteract.hs | 36 ------- compiler/typecheck/TcSMonad.hs | 117 +++++++++++++++------ testsuite/tests/typecheck/should_compile/T10009.hs | 92 +++++++++++++++- .../tests/typecheck/should_fail/IPFail.stderr | 15 ++- 5 files changed, 194 insertions(+), 84 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a7017cc74c9dcbb8ffde54f8fd3cc8b4c15ac99b From git at git.haskell.org Tue Jun 9 10:40:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 9 Jun 2015 10:40:15 +0000 (UTC) Subject: [commit: ghc] master: build: Clean testsuite before sdist (a48167e) Message-ID: <20150609104015.2A5B43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a48167eaaa984fbdc1ad31c2c674058ba3669ac6/ghc >--------------------------------------------------------------- commit a48167eaaa984fbdc1ad31c2c674058ba3669ac6 Author: Austin Seipp Date: Thu Jun 4 17:10:33 2015 -0500 build: Clean testsuite before sdist When making the `sdist` tarball, we don't really need anything inside $(TOP)/testsuite in order to do our thing. So make sure we clean it first to avoid situations like #10406. With D917 landed, this can actually avoided entirely by fixing the official release process to instead build an `sdist` //first// from the clean git repository and then build that (to fixpoint) and test it. Then the originall clean tarball can be shipped. But it's nice to be safe in the general case where someone might want to (in the future) `sdist` out of their build tree. Signed-off-by: Austin Seipp Reviewed By: thomie Differential Revision: https://phabricator.haskell.org/D956 GHC Trac Issues: #10406 >--------------------------------------------------------------- a48167eaaa984fbdc1ad31c2c674058ba3669ac6 ghc.mk | 1 + 1 file changed, 1 insertion(+) diff --git a/ghc.mk b/ghc.mk index 42b1784..9a2ba48 100644 --- a/ghc.mk +++ b/ghc.mk @@ -1175,6 +1175,7 @@ sdist-testsuite-prep : mkdir -p $(SRC_DIST_TESTSUITE_DIR) mkdir -p $(SRC_DIST_TESTSUITE_DIR)/testsuite cd $(SRC_DIST_TESTSUITE_DIR)/testsuite && lndir $(TOP)/testsuite + cd $(SRC_DIST_TESTSUITE_DIR) && $(MAKE) distclean .PHONY: sdist-ghc sdist-ghc: sdist-ghc-prep From git at git.haskell.org Tue Jun 9 10:44:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 9 Jun 2015 10:44:34 +0000 (UTC) Subject: [commit: ghc] master: Always force the exception in enqueued commands (3b55659) Message-ID: <20150609104434.6557B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3b55659d4f54e503f4e550d762bc55a2650ed13d/ghc >--------------------------------------------------------------- commit 3b55659d4f54e503f4e550d762bc55a2650ed13d Author: Zejun Wu Date: Tue Jun 9 05:42:38 2015 -0500 Always force the exception in enqueued commands `enqueueCommands` should always force exception in commands. Otherwise the exception thrown in `:cmd` (e.g. `:cmd return $ head []`) will cause GHCi to terminate with panic. Test Plan: `cd testsuite/tests/ghci/ && make` Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D967 GHC Trac Issues: #10501 >--------------------------------------------------------------- 3b55659d4f54e503f4e550d762bc55a2650ed13d ghc/InteractiveUI.hs | 16 ++++++++-------- ghc/ghc-bin.cabal.in | 1 + testsuite/tests/ghci/scripts/T10501.script | 2 ++ testsuite/tests/ghci/scripts/T10501.stderr | 2 ++ testsuite/tests/ghci/scripts/all.T | 1 + 5 files changed, 14 insertions(+), 8 deletions(-) diff --git a/ghc/InteractiveUI.hs b/ghc/InteractiveUI.hs index d2940fa..6e4880b 100644 --- a/ghc/InteractiveUI.hs +++ b/ghc/InteractiveUI.hs @@ -64,11 +64,11 @@ import Util -- Haskell Libraries import System.Console.Haskeline as Haskeline -import Control.Monad as Monad - import Control.Applicative hiding (empty) -import Control.Monad.Trans.Class +import Control.DeepSeq (deepseq) +import Control.Monad as Monad import Control.Monad.IO.Class +import Control.Monad.Trans.Class import Data.Array import qualified Data.ByteString.Char8 as BS @@ -881,8 +881,11 @@ checkInputForLayout stmt getStmt = do enqueueCommands :: [String] -> GHCi () enqueueCommands cmds = do - st <- getGHCiState - setGHCiState st{ cmdqueue = cmds ++ cmdqueue st } + -- make sure we force any exceptions in the commands while we're + -- still inside the exception handler, otherwise bad things will + -- happen (see #10501) + cmds `deepseq` return () + modifyGHCiState $ \st -> st{ cmdqueue = cmds ++ cmdqueue st } -- | If we one of these strings prefixes a command, then we treat it as a decl -- rather than a stmt. NB that the appropriate decl prefixes depends on the @@ -1328,9 +1331,6 @@ defineMacro overwrite s = do runMacro :: GHC.HValue{-String -> IO String-} -> String -> GHCi Bool runMacro fun s = do str <- liftIO ((unsafeCoerce# fun :: String -> IO String) s) - -- make sure we force any exceptions in the result, while we are still - -- inside the exception handler for commands: - seqList str (return ()) enqueueCommands (lines str) return False diff --git a/ghc/ghc-bin.cabal.in b/ghc/ghc-bin.cabal.in index b4fdf10..30eb7a7 100644 --- a/ghc/ghc-bin.cabal.in +++ b/ghc/ghc-bin.cabal.in @@ -43,6 +43,7 @@ Executable ghc GHC-Options: -Wall if flag(ghci) + Build-depends: deepseq >= 1.4 && < 1.5 CPP-Options: -DGHCI GHC-Options: -fno-warn-name-shadowing Other-Modules: diff --git a/testsuite/tests/ghci/scripts/T10501.script b/testsuite/tests/ghci/scripts/T10501.script new file mode 100644 index 0000000..06e75ec --- /dev/null +++ b/testsuite/tests/ghci/scripts/T10501.script @@ -0,0 +1,2 @@ +:cmd return $ head [] +:cmd return ('1':'2':undefined) diff --git a/testsuite/tests/ghci/scripts/T10501.stderr b/testsuite/tests/ghci/scripts/T10501.stderr new file mode 100644 index 0000000..6c3cc16 --- /dev/null +++ b/testsuite/tests/ghci/scripts/T10501.stderr @@ -0,0 +1,2 @@ +*** Exception: Prelude.head: empty list +*** Exception: Prelude.undefined diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T index a366c1f..f0d7c19 100755 --- a/testsuite/tests/ghci/scripts/all.T +++ b/testsuite/tests/ghci/scripts/all.T @@ -218,3 +218,4 @@ test('T10248', normal, ghci_script, ['T10248.script']) test('T10110', normal, ghci_script, ['T10110.script']) test('T10322', normal, ghci_script, ['T10322.script']) test('T10466', normal, ghci_script, ['T10466.script']) +test('T10501', normal, ghci_script, ['T10501.script']) From git at git.haskell.org Tue Jun 9 10:45:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 9 Jun 2015 10:45:48 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: docs: More 7.10.2 notes (5888405) Message-ID: <20150609104548.ACAC63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/58884056e2e384e5ad86c3ba628271e2e0e93280/ghc >--------------------------------------------------------------- commit 58884056e2e384e5ad86c3ba628271e2e0e93280 Author: Austin Seipp Date: Tue Jun 9 02:35:12 2015 -0500 docs: More 7.10.2 notes Signed-off-by: Austin Seipp >--------------------------------------------------------------- 58884056e2e384e5ad86c3ba628271e2e0e93280 docs/users_guide/7.10.2-notes.xml | 26 +++++++++++++++++++++++--- 1 file changed, 23 insertions(+), 3 deletions(-) diff --git a/docs/users_guide/7.10.2-notes.xml b/docs/users_guide/7.10.2-notes.xml index 2f5ce76..f9917ca 100644 --- a/docs/users_guide/7.10.2-notes.xml +++ b/docs/users_guide/7.10.2-notes.xml @@ -3,9 +3,11 @@ Release notes for version 7.10.2 - The 7.10.2 release is a bugfix release, with over 40+ bug fixes - from users and contributors. The major bugfixes relative to 7.10.1 - are listed below. + The 7.10.2 release is a bugfix release, with over 70+ bug fixes + from users and contributors relative to 7.10.1. The major bugfixes + are listed below. For the full list with more detail, see the + GHC + 7.10.2 milestone on our bug tracker. @@ -103,6 +105,13 @@ fixed (issue #10218). + + + Several performance-related issues inside GHC have been + fixed. As a result, you should see improved compilation + times and memory usage (issues #10397, #10370). + + @@ -128,6 +137,17 @@ + binary + + + + Version number 0.7.5.0 (was 0.7.3.0) + + + + + + Cabal From git at git.haskell.org Tue Jun 9 10:45:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 9 Jun 2015 10:45:51 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: build: Clean testsuite before sdist (12c1f75) Message-ID: <20150609104551.631E73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/12c1f75901bb1aba2eb054334ab4ac2dccc6b23c/ghc >--------------------------------------------------------------- commit 12c1f75901bb1aba2eb054334ab4ac2dccc6b23c Author: Austin Seipp Date: Thu Jun 4 17:10:33 2015 -0500 build: Clean testsuite before sdist When making the `sdist` tarball, we don't really need anything inside $(TOP)/testsuite in order to do our thing. So make sure we clean it first to avoid situations like #10406. With D917 landed, this can actually avoided entirely by fixing the official release process to instead build an `sdist` //first// from the clean git repository and then build that (to fixpoint) and test it. Then the originall clean tarball can be shipped. But it's nice to be safe in the general case where someone might want to (in the future) `sdist` out of their build tree. Signed-off-by: Austin Seipp Reviewed By: thomie Differential Revision: https://phabricator.haskell.org/D956 GHC Trac Issues: #10406 (cherry picked from commit a48167eaaa984fbdc1ad31c2c674058ba3669ac6) >--------------------------------------------------------------- 12c1f75901bb1aba2eb054334ab4ac2dccc6b23c ghc.mk | 1 + 1 file changed, 1 insertion(+) diff --git a/ghc.mk b/ghc.mk index 18ead9c..4019143 100644 --- a/ghc.mk +++ b/ghc.mk @@ -1190,6 +1190,7 @@ sdist-testsuite-prep : mkdir -p $(SRC_DIST_TESTSUITE_DIR) mkdir -p $(SRC_DIST_TESTSUITE_DIR)/testsuite cd $(SRC_DIST_TESTSUITE_DIR)/testsuite && lndir $(TOP)/testsuite + cd $(SRC_DIST_TESTSUITE_DIR) && $(MAKE) distclean .PHONY: sdist-ghc sdist-ghc: sdist-ghc-prep From git at git.haskell.org Tue Jun 9 10:45:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 9 Jun 2015 10:45:54 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Always force the exception in enqueued commands (d66b59a) Message-ID: <20150609104554.815BF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/d66b59a4a65c98d16b2fc6744152063d25d4c7e2/ghc >--------------------------------------------------------------- commit d66b59a4a65c98d16b2fc6744152063d25d4c7e2 Author: Zejun Wu Date: Tue Jun 9 05:42:38 2015 -0500 Always force the exception in enqueued commands `enqueueCommands` should always force exception in commands. Otherwise the exception thrown in `:cmd` (e.g. `:cmd return $ head []`) will cause GHCi to terminate with panic. Test Plan: `cd testsuite/tests/ghci/ && make` Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D967 GHC Trac Issues: #10501 (cherry picked from commit 3b55659d4f54e503f4e550d762bc55a2650ed13d) >--------------------------------------------------------------- d66b59a4a65c98d16b2fc6744152063d25d4c7e2 ghc/InteractiveUI.hs | 16 ++++++++-------- ghc/ghc-bin.cabal.in | 1 + testsuite/tests/ghci/scripts/T10501.script | 2 ++ testsuite/tests/ghci/scripts/T10501.stderr | 2 ++ testsuite/tests/ghci/scripts/all.T | 1 + 5 files changed, 14 insertions(+), 8 deletions(-) diff --git a/ghc/InteractiveUI.hs b/ghc/InteractiveUI.hs index 7bb3c06..27343e9 100644 --- a/ghc/InteractiveUI.hs +++ b/ghc/InteractiveUI.hs @@ -63,11 +63,11 @@ import Util -- Haskell Libraries import System.Console.Haskeline as Haskeline -import Control.Monad as Monad - import Control.Applicative hiding (empty) -import Control.Monad.Trans.Class +import Control.DeepSeq (deepseq) +import Control.Monad as Monad import Control.Monad.IO.Class +import Control.Monad.Trans.Class import Data.Array import qualified Data.ByteString.Char8 as BS @@ -878,8 +878,11 @@ checkInputForLayout stmt getStmt = do enqueueCommands :: [String] -> GHCi () enqueueCommands cmds = do - st <- getGHCiState - setGHCiState st{ cmdqueue = cmds ++ cmdqueue st } + -- make sure we force any exceptions in the commands while we're + -- still inside the exception handler, otherwise bad things will + -- happen (see #10501) + cmds `deepseq` return () + modifyGHCiState $ \st -> st{ cmdqueue = cmds ++ cmdqueue st } -- | If we one of these strings prefixes a command, then we treat it as a decl -- rather than a stmt. NB that the appropriate decl prefixes depends on the @@ -1308,9 +1311,6 @@ defineMacro overwrite s = do runMacro :: GHC.HValue{-String -> IO String-} -> String -> GHCi Bool runMacro fun s = do str <- liftIO ((unsafeCoerce# fun :: String -> IO String) s) - -- make sure we force any exceptions in the result, while we are still - -- inside the exception handler for commands: - seqList str (return ()) enqueueCommands (lines str) return False diff --git a/ghc/ghc-bin.cabal.in b/ghc/ghc-bin.cabal.in index b4fdf10..30eb7a7 100644 --- a/ghc/ghc-bin.cabal.in +++ b/ghc/ghc-bin.cabal.in @@ -43,6 +43,7 @@ Executable ghc GHC-Options: -Wall if flag(ghci) + Build-depends: deepseq >= 1.4 && < 1.5 CPP-Options: -DGHCI GHC-Options: -fno-warn-name-shadowing Other-Modules: diff --git a/testsuite/tests/ghci/scripts/T10501.script b/testsuite/tests/ghci/scripts/T10501.script new file mode 100644 index 0000000..06e75ec --- /dev/null +++ b/testsuite/tests/ghci/scripts/T10501.script @@ -0,0 +1,2 @@ +:cmd return $ head [] +:cmd return ('1':'2':undefined) diff --git a/testsuite/tests/ghci/scripts/T10501.stderr b/testsuite/tests/ghci/scripts/T10501.stderr new file mode 100644 index 0000000..6c3cc16 --- /dev/null +++ b/testsuite/tests/ghci/scripts/T10501.stderr @@ -0,0 +1,2 @@ +*** Exception: Prelude.head: empty list +*** Exception: Prelude.undefined diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T index 686d3bb..70a816b 100755 --- a/testsuite/tests/ghci/scripts/all.T +++ b/testsuite/tests/ghci/scripts/all.T @@ -210,3 +210,4 @@ test('T9878b', test('T10321', normal, ghci_script, ['T10321.script']) test('T10110', normal, ghci_script, ['T10110.script']) test('T10322', normal, ghci_script, ['T10322.script']) +test('T10501', normal, ghci_script, ['T10501.script']) From git at git.haskell.org Tue Jun 9 11:26:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 9 Jun 2015 11:26:39 +0000 (UTC) Subject: [commit: ghc] master: Revert "The test runner now also works under the msys-native Python." (bb99671) Message-ID: <20150609112639.827573A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bb9967121f2383b857680b47b6bc20607f8fd1ff/ghc >--------------------------------------------------------------- commit bb9967121f2383b857680b47b6bc20607f8fd1ff Author: Thomas Miedema Date: Thu Jun 4 10:49:51 2015 +0200 Revert "The test runner now also works under the msys-native Python." To make the test runner work under msys-native Python... Commit 5258566ee5c89aa757b0cf1433169346319c018f broke the msys testsuite driver (#10441). It changed the quoting of `config.compiler` from single quotes to double quote, which turns out to not be compatible with what the function `passThroughCmd` expected. We could fix `passThroughCmd` to handle the case where `config.compiler` is double quoted, and scatter some notes around to make sure the quoting done in various places of the testsuite driver stay compatible. Instead, this commit reverts 101c62e26286353dd3fac1ef54323529b64c9902, which introdced the function `passThroughCmd` in the first place (#9626). ezyang reports that doing this revert fixes the testsuite driver for him using the the following version of msys2: msys2-keyring r8.3864337-1 msys2-runtime 2.1.0.16351.cd3184b-1 msys2-runtime-devel 2.1.0.16351.cd3184b-1 msys2-w32api-headers 5.0.0.4456.c8b6742-1 msys2-w32api-runtime 5.0.0.4455.32db221-1 Ideally we'd know what minimum version of msys2 we require, but for now this fix is better than nothing. Only gintas ever reported the original problem, and he actually mentioned shortly afterwards: "This may have been fixed by a recent release of msys2, but I am not sure." Differential Revision: https://phabricator.haskell.org/D952 >--------------------------------------------------------------- bb9967121f2383b857680b47b6bc20607f8fd1ff testsuite/driver/testlib.py | 16 ---------------- testsuite/mk/test.mk | 2 ++ 2 files changed, 2 insertions(+), 16 deletions(-) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index 63b42e8..db3ada4 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -1806,25 +1806,9 @@ def rawSystem(cmd_and_args): cmd = cmd_and_args[0] return subprocess.call([strip_quotes(cmd)] + cmd_and_args[1:]) -# When running under native msys Python, any invocations of non-msys binaries, -# including timeout.exe, will have their arguments munged according to some -# heuristics, which leads to malformed command lines (#9626). The easiest way -# to avoid problems is to invoke through /usr/bin/cmd which sidesteps argument -# munging because it is a native msys application. -def passThroughCmd(cmd_and_args): - args = [] - # cmd needs a Windows-style path for its first argument. - args.append(cmd_and_args[0].replace('/', '\\')) - # Other arguments need to be quoted to deal with spaces. - args.extend(['"%s"' % arg for arg in cmd_and_args[1:]]) - return ["cmd", "/c", " ".join(args)] - # Note that this doesn't handle the timeout itself; it is just used for # commands that have timeout handling built-in. def rawSystemWithTimeout(cmd_and_args): - if config.os == 'mingw32' and sys.executable.startswith('/usr'): - # This is only needed when running under msys python. - cmd_and_args = passThroughCmd(cmd_and_args) r = rawSystem(cmd_and_args) if r == 98: # The python timeout program uses 98 to signal that ^C was pressed diff --git a/testsuite/mk/test.mk b/testsuite/mk/test.mk index 5b48205..644de5a 100644 --- a/testsuite/mk/test.mk +++ b/testsuite/mk/test.mk @@ -213,6 +213,8 @@ RUNTEST_OPTS += \ # function) would require another pair of (escaped) quotes, which interfers # with MinGW's magic path handling (see #10449, and # http://www.mingw.org/wiki/Posix_path_conversion). +# We use double instead of single quotes, which may or may not be important +# when using msys2 (#9626, #10441). quote_path = $(if $1,"$1") RUNTEST_OPTS += \ --config 'compiler=$(call quote_path,$(TEST_HC))' \ From git at git.haskell.org Tue Jun 9 11:26:42 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 9 Jun 2015 11:26:42 +0000 (UTC) Subject: [commit: ghc] master: Testsuite: delete expect_fail setups for hugs (43ebe24) Message-ID: <20150609112642.302613A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/43ebe24aed3bfb4decd958ca91313ab2773abd51/ghc >--------------------------------------------------------------- commit 43ebe24aed3bfb4decd958ca91313ab2773abd51 Author: Thomas Miedema Date: Wed Jun 3 14:48:23 2015 +0200 Testsuite: delete expect_fail setups for hugs This makes it easier to grep for expect_fail in the tests directory. Differential Revision: https://phabricator.haskell.org/D964 >--------------------------------------------------------------- 43ebe24aed3bfb4decd958ca91313ab2773abd51 libraries/base/tests/IO/all.T | 13 +++---------- testsuite/tests/module/all.T | 2 +- testsuite/tests/parser/should_compile/all.T | 4 ++-- testsuite/tests/parser/should_fail/all.T | 2 +- testsuite/tests/programs/life_space_leak/test.T | 3 +-- testsuite/tests/typecheck/should_compile/all.T | 4 ++-- testsuite/tests/typecheck/should_fail/all.T | 2 +- 7 files changed, 11 insertions(+), 19 deletions(-) diff --git a/libraries/base/tests/IO/all.T b/libraries/base/tests/IO/all.T index e15c84d..f6c8cc9 100644 --- a/libraries/base/tests/IO/all.T +++ b/libraries/base/tests/IO/all.T @@ -72,21 +72,14 @@ test('openFile001', normal, compile_and_run, ['']) test('openFile002', exit_code(1), compile_and_run, ['']) test('openFile003', extra_clean(['openFile003Dir']), compile_and_run, ['']) test('openFile004', extra_clean(['openFile004.out']), compile_and_run, ['']) -test('openFile005', - [when(compiler_type('hugs'), expect_fail), - extra_clean(['openFile005.out1', 'openFile005.out2'])], +test('openFile005', extra_clean(['openFile005.out1', 'openFile005.out2']), compile_and_run, ['']) test('openFile006', extra_clean(['openFile006.out']), compile_and_run, ['']) -test('openFile007', - [when(compiler_type('hugs'), expect_fail), - extra_clean(['openFile007.out'])], - compile_and_run, ['']) +test('openFile007', extra_clean(['openFile007.out']), compile_and_run, ['']) test('openFile008', cmd_prefix('ulimit -n 1024; '), compile_and_run, ['']) test('putStr001', normal, compile_and_run, ['']) -test('readFile001', - [when(compiler_type('hugs'), expect_fail), - extra_clean(['readFile001.out'])], +test('readFile001', extra_clean(['readFile001.out']), compile_and_run, ['']) test('readwrite001', extra_clean(['readwrite001.inout']), diff --git a/testsuite/tests/module/all.T b/testsuite/tests/module/all.T index d0b37aa..cd1bdac 100644 --- a/testsuite/tests/module/all.T +++ b/testsuite/tests/module/all.T @@ -260,7 +260,7 @@ test('mod150', normal, compile_fail, ['']) test('mod151', normal, compile_fail, ['']) test('mod152', normal, compile_fail, ['']) test('mod153', normal, compile_fail, ['']) -test('mod154', when(compiler_type('hugs'), expect_fail), compile, ['']) +test('mod154', normal, compile, ['']) test('mod155', normal, compile_fail, ['']) test('mod156', normal, compile, ['']) test('mod157', diff --git a/testsuite/tests/parser/should_compile/all.T b/testsuite/tests/parser/should_compile/all.T index 9e7612c..eec0a12 100644 --- a/testsuite/tests/parser/should_compile/all.T +++ b/testsuite/tests/parser/should_compile/all.T @@ -45,8 +45,8 @@ test('read029', normal, compile, ['']) test('read030', normal, compile, ['']) test('read031', normal, compile, ['']) test('read032', normal, compile, ['']) -test('read033', when(compiler_type('hugs'), expect_fail), compile, ['']) -test('read034', when(compiler_type('hugs'), expect_fail), compile, ['']) +test('read033', normal, compile, ['']) +test('read034', normal, compile, ['']) test('read036', normal, compile, ['']) test('read037', normal, compile, ['']) test('read038', normal, compile, ['']) diff --git a/testsuite/tests/parser/should_fail/all.T b/testsuite/tests/parser/should_fail/all.T index 0352235..cc59a14 100644 --- a/testsuite/tests/parser/should_fail/all.T +++ b/testsuite/tests/parser/should_fail/all.T @@ -23,7 +23,7 @@ test('readFail020', normal, compile_fail, ['']) # empty file (length zero) is not a legal Haskell module. It fails to compile # because it doesn't contain a definition of Main.main. GHC 5.02 crashed # on this example. -test('readFail021', when(compiler_type('hugs'), expect_fail), compile_fail, ['']) +test('readFail021', normal, compile_fail, ['']) test('readFail022', normal, compile_fail, ['']) test('readFail023', normal, compile_fail, ['']) diff --git a/testsuite/tests/programs/life_space_leak/test.T b/testsuite/tests/programs/life_space_leak/test.T index 11f73e0..4483137 100644 --- a/testsuite/tests/programs/life_space_leak/test.T +++ b/testsuite/tests/programs/life_space_leak/test.T @@ -1,8 +1,7 @@ # exhausts Hugs's heap (CAF leak) test('life_space_leak', [when(fast(), skip), - extra_clean(['Main.hi', 'Main.o']), - when(compiler_type('hugs'), expect_fail)], + extra_clean(['Main.hi', 'Main.o'])], multimod_compile_and_run, ['Main', '']) diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index dbd6328..bd87afb 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -84,7 +84,7 @@ test('tc079', normal, compile, ['']) test('tc080', normal, compile, ['']) test('tc081', normal, compile, ['']) test('tc082', normal, compile, ['']) -test('tc084', when(compiler_type('hugs'), expect_fail), compile, ['']) +test('tc084', normal, compile, ['']) test('tc085', only_compiler_types(['ghc']), compile, ['']) test('tc086', normal, compile, ['']) test('tc087', normal, compile, ['']) @@ -96,7 +96,7 @@ test('tc092', normal, compile, ['']) test('tc093', normal, compile, ['']) test('tc094', normal, compile, ['']) test('tc095', normal, compile, ['']) -test('tc096', when(compiler_type('hugs'), expect_fail), compile, ['']) +test('tc096', normal, compile, ['']) test('tc097', normal, compile, ['']) test('tc098', normal, compile, ['']) test('tc099', normal, compile, ['']) diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index b9c7d5a..4dfc220 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -24,7 +24,7 @@ test('tcfail023', normal, compile_fail, ['']) test('tcfail027', normal, compile_fail, ['']) test('tcfail028', normal, compile_fail, ['']) test('tcfail029', normal, compile_fail, ['']) -test('tcfail030', when(compiler_type('hugs'), expect_fail), compile_fail, ['']) +test('tcfail030', normal, compile_fail, ['']) test('tcfail031', normal, compile_fail, ['']) test('tcfail032', normal, compile_fail, ['']) test('tcfail033', normal, compile_fail, ['']) From git at git.haskell.org Tue Jun 9 11:26:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 9 Jun 2015 11:26:45 +0000 (UTC) Subject: [commit: ghc] master: Testsuite: delete expect_fail setups for ghc < 7.1 (3445947) Message-ID: <20150609112645.138F43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3445947ae380967b4032233273fdb54d41bce157/ghc >--------------------------------------------------------------- commit 3445947ae380967b4032233273fdb54d41bce157 Author: Thomas Miedema Date: Wed Jun 3 14:55:20 2015 +0200 Testsuite: delete expect_fail setups for ghc < 7.1 This makes it easier to grep for expect_fail in the tests directory. Differential Revision: https://phabricator.haskell.org/D965 >--------------------------------------------------------------- 3445947ae380967b4032233273fdb54d41bce157 testsuite/tests/concurrent/should_run/all.T | 3 +-- testsuite/tests/deSugar/should_compile/all.T | 2 +- testsuite/tests/gadt/all.T | 8 ++++---- testsuite/tests/indexed-types/should_compile/all.T | 2 +- testsuite/tests/indexed-types/should_fail/all.T | 2 +- testsuite/tests/module/base01/all.T | 3 +-- testsuite/tests/rename/should_compile/all.T | 2 +- testsuite/tests/simplCore/should_compile/all.T | 5 ++--- 8 files changed, 12 insertions(+), 15 deletions(-) diff --git a/testsuite/tests/concurrent/should_run/all.T b/testsuite/tests/concurrent/should_run/all.T index e72bffe..5288ff9 100644 --- a/testsuite/tests/concurrent/should_run/all.T +++ b/testsuite/tests/concurrent/should_run/all.T @@ -52,8 +52,7 @@ test('numsparks001', only_ways(['threaded1']), compile_and_run, ['']) test('T4262', [ skip, # skip for now, it doesn't give reliable results only_ways(['threaded1']), - unless(opsys('linux'),skip), - when(compiler_lt('ghc', '7.1'), expect_fail) ], + unless(opsys('linux'),skip) ], compile_and_run, ['']) test('T4813', normal, compile_and_run, ['']) diff --git a/testsuite/tests/deSugar/should_compile/all.T b/testsuite/tests/deSugar/should_compile/all.T index 956f951..2f890f5 100644 --- a/testsuite/tests/deSugar/should_compile/all.T +++ b/testsuite/tests/deSugar/should_compile/all.T @@ -75,7 +75,7 @@ test('GadtOverlap', normal, compile, ['-Wall']) test('T2395', normal, compile, ['']) test('T4371', normal, compile, ['']) test('T4439', normal, compile, ['']) -test('T4488', when(compiler_lt('ghc', '7.1'), expect_fail), compile, ['']) +test('T4488', normal, compile, ['']) test('T4870', [only_ways(['optasm']), only_compiler_types(['ghc']), diff --git a/testsuite/tests/gadt/all.T b/testsuite/tests/gadt/all.T index 315ecb6..cbbc0fc 100644 --- a/testsuite/tests/gadt/all.T +++ b/testsuite/tests/gadt/all.T @@ -102,10 +102,10 @@ test('gadt25', normal, compile, ['']) test('T3651', normal, compile_fail, ['']) test('T3638', normal, compile, ['']) -test('gadtSyntax001', when(compiler_lt('ghc', '7.1'), expect_fail), compile, ['']) -test('gadtSyntaxFail001', when(compiler_lt('ghc', '7.1'), expect_fail), compile_fail, ['']) -test('gadtSyntaxFail002', when(compiler_lt('ghc', '7.1'), expect_fail), compile_fail, ['']) -test('gadtSyntaxFail003', when(compiler_lt('ghc', '7.1'), expect_fail), compile_fail, ['']) +test('gadtSyntax001', normal, compile, ['']) +test('gadtSyntaxFail001', normal, compile_fail, ['']) +test('gadtSyntaxFail002', normal, compile_fail, ['']) +test('gadtSyntaxFail003', normal, compile_fail, ['']) test('T3169', normal, compile_fail, ['']) test('T5424', extra_clean(['T5424a.hi', 'T5424a.o']), diff --git a/testsuite/tests/indexed-types/should_compile/all.T b/testsuite/tests/indexed-types/should_compile/all.T index 27bb853..aaf89e9 100644 --- a/testsuite/tests/indexed-types/should_compile/all.T +++ b/testsuite/tests/indexed-types/should_compile/all.T @@ -159,7 +159,7 @@ test('T4484', normal, compile, ['']) test('T4492', normal, compile, ['']) test('T4494', normal, compile, ['']) test('DataFamDeriv', normal, compile, ['']) -test('T1769', when(compiler_lt('ghc', '7.1'), expect_fail), compile, ['']) +test('T1769', normal, compile, ['']) test('T4497', normal, compile, ['']) test('T3484', normal, compile, ['']) test('T3460', normal, compile, ['']) diff --git a/testsuite/tests/indexed-types/should_fail/all.T b/testsuite/tests/indexed-types/should_fail/all.T index 6615c02..069b5a6 100644 --- a/testsuite/tests/indexed-types/should_fail/all.T +++ b/testsuite/tests/indexed-types/should_fail/all.T @@ -65,7 +65,7 @@ test('T2239', normal, compile, ['']) test('T3440', normal, compile_fail, ['']) test('T4485', normal, compile_fail, ['']) test('T4174', normal, compile_fail, ['']) -test('DerivUnsatFam', when(compiler_lt('ghc', '7.1'), expect_fail), compile_fail, ['']) +test('DerivUnsatFam', normal, compile_fail, ['']) test('T2664', normal, compile_fail, ['']) test('T2664a', normal, compile, ['']) test('T2544', normal, compile_fail, ['']) diff --git a/testsuite/tests/module/base01/all.T b/testsuite/tests/module/base01/all.T index 6fa3e5c..1d1560b 100644 --- a/testsuite/tests/module/base01/all.T +++ b/testsuite/tests/module/base01/all.T @@ -1,8 +1,7 @@ setTestOpts(only_compiler_types(['ghc'])) test('base01', - [when(compiler_lt('ghc', '7.1'), expect_fail), - normalise_slashes, + [normalise_slashes, clean_cmd('$MAKE -s clean')], run_command, ['$MAKE -s base01 --no-print-directory']) diff --git a/testsuite/tests/rename/should_compile/all.T b/testsuite/tests/rename/should_compile/all.T index aa29c43..4bd4e0a 100644 --- a/testsuite/tests/rename/should_compile/all.T +++ b/testsuite/tests/rename/should_compile/all.T @@ -169,7 +169,7 @@ test('T4240', ['$MAKE -s --no-print-directory T4240']) test('T4489', normal, compile, ['']) -test('T4478', when(compiler_lt('ghc', '7.1'), expect_fail), compile, ['']) +test('T4478', normal, compile, ['']) test('T4534', normal, compile, ['']) test('mc09', normal, compile, ['']) diff --git a/testsuite/tests/simplCore/should_compile/all.T b/testsuite/tests/simplCore/should_compile/all.T index daf038a..1f7dffa 100644 --- a/testsuite/tests/simplCore/should_compile/all.T +++ b/testsuite/tests/simplCore/should_compile/all.T @@ -63,8 +63,7 @@ test('T4908', only_ways(['optasm']), compile, ['-O2 -ddump-simpl -dsuppress-uniques']) -test('T4930', [when(compiler_lt('ghc', '7.1'), expect_fail), - only_ways(['optasm'])], +test('T4930', only_ways(['optasm']), compile, ['-O -ddump-simpl -dsuppress-uniques']) @@ -108,7 +107,7 @@ test('T4918', ['$MAKE -s --no-print-directory T4918']) test('T4945', - when(compiler_lt('ghc', '7.1'), expect_fail), + normal, run_command, ['$MAKE -s --no-print-directory T4945']) From git at git.haskell.org Tue Jun 9 11:26:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 9 Jun 2015 11:26:47 +0000 (UTC) Subject: [commit: ghc] master: Build: run autoreconf jobs in parallel (4a0b7a1) Message-ID: <20150609112647.D03B63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4a0b7a10442eec3747d5f95ef186a79bb0648754/ghc >--------------------------------------------------------------- commit 4a0b7a10442eec3747d5f95ef186a79bb0648754 Author: Thomas Miedema Date: Thu Jun 4 23:23:19 2015 +0200 Build: run autoreconf jobs in parallel Running ./boot takes ~20 seconds on my laptop with 2 cores. With this change, that goes down to a little over 10 seconds. There are 8 configure.ac files in total, so max 8 parallel jobs. Differential Revision: https://phabricator.haskell.org/D962 >--------------------------------------------------------------- 4a0b7a10442eec3747d5f95ef186a79bb0648754 boot | 15 ++++++++++++--- 1 file changed, 12 insertions(+), 3 deletions(-) diff --git a/boot b/boot index 8977eaf..af5ccc2 100755 --- a/boot +++ b/boot @@ -155,16 +155,25 @@ sub boot_pkgs { # autoreconf everything that needs it. sub autoreconf { my $dir; + my $fail; foreach $dir (".", glob("libraries/*/")) { if (-f "$dir/configure.ac") { + next if (my $pid = fork); + die "fork failed: $!" if (! defined $pid); print "Booting $dir\n"; chdir $dir or die "can't change to $dir: $!"; - system("autoreconf") == 0 - or die "Running autoreconf failed with exitcode $?"; - chdir $curdir or die "can't change to $curdir: $!"; + exec("autoreconf"); + exit 1; } } + + # Wait for all child processes to finish. + while (wait() != -1) { + $fail = 1 if $?; + } + + die "Running autoreconf failed" if $fail; } sub checkBuildMk { From git at git.haskell.org Tue Jun 9 11:33:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 9 Jun 2015 11:33:57 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: haddock: update submodule (ab6e80a) Message-ID: <20150609113358.004353A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/ab6e80a9b2aced735ba91a098ffc3923af2a1e6d/ghc >--------------------------------------------------------------- commit ab6e80a9b2aced735ba91a098ffc3923af2a1e6d Author: Austin Seipp Date: Tue Jun 9 06:34:06 2015 -0500 haddock: update submodule Signed-off-by: Austin Seipp >--------------------------------------------------------------- ab6e80a9b2aced735ba91a098ffc3923af2a1e6d utils/haddock | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/haddock b/utils/haddock index bf31846..a65953d 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit bf31846b9f7280b5e75f09e91ca18c4ced37af08 +Subproject commit a65953de929fd9488250f8e0257c918465193e43 From git at git.haskell.org Tue Jun 9 11:37:08 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 9 Jun 2015 11:37:08 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Revert "The test runner now also works under the msys-native Python." (49201ed) Message-ID: <20150609113708.438C53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/49201ed15372b132b362c639cf23b89fa169834e/ghc >--------------------------------------------------------------- commit 49201ed15372b132b362c639cf23b89fa169834e Author: Thomas Miedema Date: Thu Jun 4 10:49:51 2015 +0200 Revert "The test runner now also works under the msys-native Python." To make the test runner work under msys-native Python... Commit 5258566ee5c89aa757b0cf1433169346319c018f broke the msys testsuite driver (#10441). It changed the quoting of `config.compiler` from single quotes to double quote, which turns out to not be compatible with what the function `passThroughCmd` expected. We could fix `passThroughCmd` to handle the case where `config.compiler` is double quoted, and scatter some notes around to make sure the quoting done in various places of the testsuite driver stay compatible. Instead, this commit reverts 101c62e26286353dd3fac1ef54323529b64c9902, which introdced the function `passThroughCmd` in the first place (#9626). ezyang reports that doing this revert fixes the testsuite driver for him using the the following version of msys2: msys2-keyring r8.3864337-1 msys2-runtime 2.1.0.16351.cd3184b-1 msys2-runtime-devel 2.1.0.16351.cd3184b-1 msys2-w32api-headers 5.0.0.4456.c8b6742-1 msys2-w32api-runtime 5.0.0.4455.32db221-1 Ideally we'd know what minimum version of msys2 we require, but for now this fix is better than nothing. Only gintas ever reported the original problem, and he actually mentioned shortly afterwards: "This may have been fixed by a recent release of msys2, but I am not sure." Differential Revision: https://phabricator.haskell.org/D952 (cherry picked from commit bb9967121f2383b857680b47b6bc20607f8fd1ff) >--------------------------------------------------------------- 49201ed15372b132b362c639cf23b89fa169834e testsuite/driver/testlib.py | 16 ---------------- testsuite/mk/test.mk | 2 ++ 2 files changed, 2 insertions(+), 16 deletions(-) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index 65ff8ba..9556298 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -1786,25 +1786,9 @@ def rawSystem(cmd_and_args): else: return os.spawnv(os.P_WAIT, cmd, cmd_and_args) -# When running under native msys Python, any invocations of non-msys binaries, -# including timeout.exe, will have their arguments munged according to some -# heuristics, which leads to malformed command lines (#9626). The easiest way -# to avoid problems is to invoke through /usr/bin/cmd which sidesteps argument -# munging because it is a native msys application. -def passThroughCmd(cmd_and_args): - args = [] - # cmd needs a Windows-style path for its first argument. - args.append(cmd_and_args[0].replace('/', '\\')) - # Other arguments need to be quoted to deal with spaces. - args.extend(['"%s"' % arg for arg in cmd_and_args[1:]]) - return ["cmd", "/c", " ".join(args)] - # Note that this doesn't handle the timeout itself; it is just used for # commands that have timeout handling built-in. def rawSystemWithTimeout(cmd_and_args): - if config.os == 'mingw32' and sys.executable.startswith('/usr'): - # This is only needed when running under msys python. - cmd_and_args = passThroughCmd(cmd_and_args) r = rawSystem(cmd_and_args) if r == 98: # The python timeout program uses 98 to signal that ^C was pressed diff --git a/testsuite/mk/test.mk b/testsuite/mk/test.mk index 2522b11..46eeb7e 100644 --- a/testsuite/mk/test.mk +++ b/testsuite/mk/test.mk @@ -213,6 +213,8 @@ RUNTEST_OPTS += \ # function) would require another pair of (escaped) quotes, which interfers # with MinGW's magic path handling (see #10449, and # http://www.mingw.org/wiki/Posix_path_conversion). +# We use double instead of single quotes, which may or may not be important +# when using msys2 (#9626, #10441). quote_path = $(if $1,"$1") RUNTEST_OPTS += \ --config 'compiler=$(call quote_path,$(TEST_HC))' \ From git at git.haskell.org Tue Jun 9 12:31:56 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 9 Jun 2015 12:31:56 +0000 (UTC) Subject: [commit: ghc] master: make sdist: distclean testsuite for real (#10406) (5828457) Message-ID: <20150609123156.00A303A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5828457d8d26fd33130d4b5850847c9a73a8d3e5/ghc >--------------------------------------------------------------- commit 5828457d8d26fd33130d4b5850847c9a73a8d3e5 Author: Thomas Miedema Date: Tue Jun 9 14:31:40 2015 +0200 make sdist: distclean testsuite for real (#10406) >--------------------------------------------------------------- 5828457d8d26fd33130d4b5850847c9a73a8d3e5 ghc.mk | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.mk b/ghc.mk index 9a2ba48..93da0cb 100644 --- a/ghc.mk +++ b/ghc.mk @@ -1175,7 +1175,7 @@ sdist-testsuite-prep : mkdir -p $(SRC_DIST_TESTSUITE_DIR) mkdir -p $(SRC_DIST_TESTSUITE_DIR)/testsuite cd $(SRC_DIST_TESTSUITE_DIR)/testsuite && lndir $(TOP)/testsuite - cd $(SRC_DIST_TESTSUITE_DIR) && $(MAKE) distclean + cd $(SRC_DIST_TESTSUITE_DIR)/testsuite && $(MAKE) distclean .PHONY: sdist-ghc sdist-ghc: sdist-ghc-prep From git at git.haskell.org Tue Jun 9 12:33:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 9 Jun 2015 12:33:00 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: make sdist: distclean testsuite for real (#10406) (38edecd) Message-ID: <20150609123300.D9D653A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/38edecd738c9a7b824ccb00626aa109ed113eaa0/ghc >--------------------------------------------------------------- commit 38edecd738c9a7b824ccb00626aa109ed113eaa0 Author: Thomas Miedema Date: Tue Jun 9 14:31:40 2015 +0200 make sdist: distclean testsuite for real (#10406) (cherry picked from commit 5828457d8d26fd33130d4b5850847c9a73a8d3e5) >--------------------------------------------------------------- 38edecd738c9a7b824ccb00626aa109ed113eaa0 ghc.mk | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.mk b/ghc.mk index 4019143..9aa0dc3 100644 --- a/ghc.mk +++ b/ghc.mk @@ -1190,7 +1190,7 @@ sdist-testsuite-prep : mkdir -p $(SRC_DIST_TESTSUITE_DIR) mkdir -p $(SRC_DIST_TESTSUITE_DIR)/testsuite cd $(SRC_DIST_TESTSUITE_DIR)/testsuite && lndir $(TOP)/testsuite - cd $(SRC_DIST_TESTSUITE_DIR) && $(MAKE) distclean + cd $(SRC_DIST_TESTSUITE_DIR)/testsuite && $(MAKE) distclean .PHONY: sdist-ghc sdist-ghc: sdist-ghc-prep From git at git.haskell.org Wed Jun 10 21:44:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 10 Jun 2015 21:44:43 +0000 (UTC) Subject: [commit: ghc] master: docs: Fix #10416 (ca39b96) Message-ID: <20150610214443.0869C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ca39b96ee783e124909a89ea3ad366bf99defa7b/ghc >--------------------------------------------------------------- commit ca39b96ee783e124909a89ea3ad366bf99defa7b Author: Austin Seipp Date: Wed Jun 10 16:43:23 2015 -0500 docs: Fix #10416 This commit fixes #10416 by using an EPS-based file-format for embedding images in the users guide, as opposed to a png. This is because 'latex' in some distributions is actually 'pdflatex', which supports reading the size of PNGs in DVI mode, while traditional latex does not. Rather than fiddle with the build a whole bunch, it's easy and simple to just convert the png into a eps file and embed that instead. But apparently we already had an EPS file, added in 1cce2f51656cfbd8c7933a914a4bd981792aa1e6! But it was quite large, so instead I used `convert` to shrink it down from 1.7MB to about 20kb, the same size as the original PDF (by using level3 postscript, which is not as wasteful.) Signed-off-by: Austin Seipp Differential Revision: https://phabricator.haskell.org/D970 GHC Trac Issues: #10416 >--------------------------------------------------------------- ca39b96ee783e124909a89ea3ad366bf99defa7b docs/users_guide/ghc.mk | 6 +++--- docs/users_guide/prof_scc.eps | Bin 1685125 -> 17580 bytes docs/users_guide/prof_scc.png | Bin 16815 -> 0 bytes docs/users_guide/profiling.xml | 2 +- 4 files changed, 4 insertions(+), 4 deletions(-) diff --git a/docs/users_guide/ghc.mk b/docs/users_guide/ghc.mk index 4737b5c..eb7eb6a 100644 --- a/docs/users_guide/ghc.mk +++ b/docs/users_guide/ghc.mk @@ -27,10 +27,10 @@ $(eval $(call docbook,docs/users_guide,users_guide)) $(eval $(call clean-target,docs/users_guide,gen,$(docs/users_guide_GENERATED_DOCBOOK_SOURCES))) -html_docs/users_guide : docs/users_guide/users_guide/prof_scc.png +html_docs/users_guide : docs/users_guide/users_guide/prof_scc.eps -docs/users_guide/users_guide/prof_scc.png : \ - docs/users_guide/prof_scc.png \ +docs/users_guide/users_guide/prof_scc.eps : \ + docs/users_guide/prof_scc.eps \ docs/users_guide/users_guide/index.html $(CP) $< $@ # dep. on d/u/u/index.html is to make sure that the d/u/u dir is created first diff --git a/docs/users_guide/prof_scc.eps b/docs/users_guide/prof_scc.eps index db6e8d0..beac36f 100644 Binary files a/docs/users_guide/prof_scc.eps and b/docs/users_guide/prof_scc.eps differ diff --git a/docs/users_guide/prof_scc.png b/docs/users_guide/prof_scc.png deleted file mode 100644 index 5e4157d..0000000 Binary files a/docs/users_guide/prof_scc.png and /dev/null differ diff --git a/docs/users_guide/profiling.xml b/docs/users_guide/profiling.xml index 4971a7d..26d18a0 100644 --- a/docs/users_guide/profiling.xml +++ b/docs/users_guide/profiling.xml @@ -625,7 +625,7 @@ MAIN MAIN 102 0 0.0 0.0 100.0 1 other than making the PS file generation work, rather than falling over. The result seems to be broken PS on the page with the image. --> - You might also want to take a look From git at git.haskell.org Thu Jun 11 12:32:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 Jun 2015 12:32:26 +0000 (UTC) Subject: [commit: ghc] master: Another major improvement of "improvement" (ddbb97d) Message-ID: <20150611123226.B88643A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ddbb97d00fdbc5870a4076ed15af8e607b161cb2/ghc >--------------------------------------------------------------- commit ddbb97d00fdbc5870a4076ed15af8e607b161cb2 Author: Simon Peyton Jones Date: Thu May 7 09:07:51 2015 +0100 Another major improvement of "improvement" I wasn't very happy with my fix to Trac #10009. This is much better. The main idea is that the inert set now contains a "model", which embodies *all* the (nominal) equalities that we know about, with a view to exposing unifications. This requires a lot fewer iterations of the solver than before. There are extensive comments in TcSMonad: Note [inert_model: the inert model] Note [Adding an inert canonical constraint the InertCans] The big changes are * New inert_model field in InertCans * Functions addInertEq, addInertCan deal with adding a constraint, maintaining the model * A nice improvement is that unification variables can unify with fmvs, so that from, say alpha ~ fmv we get alpha := fmv See Note [Orientation of equalities with fmvs] in TcFlatten It's still not perfect, as the Note explains New flag -fconstraint-solver-iterations=n, allows us to control the number of constraint solver iterations, and in particular will flag up when it's more than a small number. Performance is generally slightly better: T5837 is a lot better for some reason. >--------------------------------------------------------------- ddbb97d00fdbc5870a4076ed15af8e607b161cb2 compiler/basicTypes/BasicTypes.hs | 6 +- compiler/main/Constants.hs | 5 + compiler/main/DynFlags.hs | 5 + compiler/typecheck/TcCanonical.hs | 65 +- compiler/typecheck/TcFlatten.hs | 447 ++---- compiler/typecheck/TcInteract.hs | 641 ++------- compiler/typecheck/TcRnTypes.hs | 118 +- compiler/typecheck/TcSMonad.hs | 1443 ++++++++++++++++---- compiler/typecheck/TcSimplify.hs | 74 +- compiler/typecheck/TcType.hs | 9 +- docs/users_guide/flags.xml | 12 +- .../tests/indexed-types/should_fail/T2544.stderr | 21 +- .../tests/indexed-types/should_fail/T2627b.stderr | 6 +- .../tests/indexed-types/should_fail/T3330c.stderr | 6 +- .../tests/indexed-types/should_fail/T4254.stderr | 4 - .../tests/indexed-types/should_fail/T6123.stderr | 8 +- .../tests/indexed-types/should_fail/T9662.stderr | 72 +- testsuite/tests/perf/compiler/all.T | 3 +- .../tests/typecheck/should_compile/Improvement.hs | 1 + testsuite/tests/typecheck/should_compile/T10009.hs | 90 +- testsuite/tests/typecheck/should_compile/tc237.hs | 3 + .../tests/typecheck/should_fail/IPFail.stderr | 2 +- testsuite/tests/typecheck/should_fail/T5236.hs | 10 +- testsuite/tests/typecheck/should_fail/T5853.stderr | 25 +- testsuite/tests/typecheck/should_fail/T5978.hs | 3 + testsuite/tests/typecheck/should_fail/T5978.stderr | 6 +- .../typecheck/should_fail/TcCoercibleFail.stderr | 19 +- testsuite/tests/typecheck/should_fail/tcfail138.hs | 2 +- .../tests/typecheck/should_fail/tcfail143.stderr | 4 +- .../tests/typecheck/should_fail/tcfail201.stderr | 2 +- 30 files changed, 1781 insertions(+), 1331 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ddbb97d00fdbc5870a4076ed15af8e607b161cb2 From git at git.haskell.org Thu Jun 11 12:32:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 Jun 2015 12:32:29 +0000 (UTC) Subject: [commit: ghc] master: IndTypesPerfMerge no longer seems to requre -M20M (c0dc79f) Message-ID: <20150611123229.7C69E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c0dc79fbef90bf26e771d24a102044060ac001fb/ghc >--------------------------------------------------------------- commit c0dc79fbef90bf26e771d24a102044060ac001fb Author: Simon Peyton Jones Date: Thu Jun 11 08:54:27 2015 +0100 IndTypesPerfMerge no longer seems to requre -M20M >--------------------------------------------------------------- c0dc79fbef90bf26e771d24a102044060ac001fb testsuite/tests/indexed-types/should_compile/Makefile | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/indexed-types/should_compile/Makefile b/testsuite/tests/indexed-types/should_compile/Makefile index 5401afd..e5970c0 100644 --- a/testsuite/tests/indexed-types/should_compile/Makefile +++ b/testsuite/tests/indexed-types/should_compile/Makefile @@ -11,8 +11,8 @@ NewTyCo: IndTypesPerf: $(RM) IndTypesPerf.o IndTypesPerf.hi $(RM) IndTypesPerfMerge.o IndTypesPerfMerge.hi - '$(TEST_HC)' $(TEST_HC_OPTS) -O -c IndTypesPerfMerge.hs +RTS -M20M - '$(TEST_HC)' $(TEST_HC_OPTS) -O -c IndTypesPerf.hs +RTS -M20M + '$(TEST_HC)' $(TEST_HC_OPTS) -O -c IndTypesPerfMerge.hs + '$(TEST_HC)' $(TEST_HC_OPTS) -O -c IndTypesPerf.hs T5955: $(RM) T5955.o T5955.hi T5955a.o T5955a.hi From git at git.haskell.org Thu Jun 11 15:23:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 Jun 2015 15:23:31 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: Major rewrite Pt 13: Like the paper (c4758de) Message-ID: <20150611152331.0E0053A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/c4758de70e8d579066feda1591ff8f6533290c8a/ghc >--------------------------------------------------------------- commit c4758de70e8d579066feda1591ff8f6533290c8a Author: George Karachalias Date: Fri May 8 12:16:12 2015 +0200 Major rewrite Pt 13: Like the paper TODOs: * Proper typing * Fix pretty-printing >--------------------------------------------------------------- c4758de70e8d579066feda1591ff8f6533290c8a compiler/basicTypes/Var.hs | 1 + compiler/deSugar/Check.hs | 1593 ++++++++++++++++-------------------------- compiler/deSugar/Match.hs | 5 +- compiler/deSugar/MatchLit.hs | 60 -- 4 files changed, 613 insertions(+), 1046 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c4758de70e8d579066feda1591ff8f6533290c8a From git at git.haskell.org Thu Jun 11 17:10:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 Jun 2015 17:10:35 +0000 (UTC) Subject: [commit: ghc] master: Fix DWARF generation for MinGW (#10468) (a66ef35) Message-ID: <20150611171035.46C533A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a66ef3567ea29c93a9c010befc672602dc1c644c/ghc >--------------------------------------------------------------- commit a66ef3567ea29c93a9c010befc672602dc1c644c Author: Peter Wortmann Date: Thu Jun 11 12:09:55 2015 -0500 Fix DWARF generation for MinGW (#10468) Fortunately this is relatively straightforward - all we need to do is switch to a non-ELF-specific way of specifying object file sections and make sure that section-relative addresses work correctly. This is enough to make "gdb" work on MinGW builds. >--------------------------------------------------------------- a66ef3567ea29c93a9c010befc672602dc1c644c compiler/nativeGen/Dwarf.hs | 2 +- compiler/nativeGen/Dwarf/Constants.hs | 12 +++++++----- compiler/nativeGen/Dwarf/Types.hs | 14 ++++++++------ 3 files changed, 16 insertions(+), 12 deletions(-) diff --git a/compiler/nativeGen/Dwarf.hs b/compiler/nativeGen/Dwarf.hs index ff86fd8..34f1ed6 100644 --- a/compiler/nativeGen/Dwarf.hs +++ b/compiler/nativeGen/Dwarf.hs @@ -86,7 +86,7 @@ compileUnitHeader unitU = sdocWithPlatform $ \plat -> in vcat [ ptext (sLit "\t.long ") <> length -- compilation unit size , ppr cuLabel <> colon , ptext (sLit "\t.word 3") -- DWARF version - , pprDwWord (sectionOffset dwarfAbbrevLabel dwarfAbbrevLabel) + , sectionOffset dwarfAbbrevLabel dwarfAbbrevLabel -- abbrevs offset , ptext (sLit "\t.byte ") <> ppr (platformWordSize plat) -- word size ] diff --git a/compiler/nativeGen/Dwarf/Constants.hs b/compiler/nativeGen/Dwarf/Constants.hs index 2cd54a7..4b334fc 100644 --- a/compiler/nativeGen/Dwarf/Constants.hs +++ b/compiler/nativeGen/Dwarf/Constants.hs @@ -122,12 +122,14 @@ dwarfFrameSection = dwarfSection "frame" dwarfGhcSection = dwarfSection "ghc" dwarfSection :: String -> SDoc -dwarfSection name = sdocWithPlatform $ \plat -> +dwarfSection name = sdocWithPlatform $ \plat -> ftext $ mkFastString $ case platformOS plat of - OSDarwin -> ftext $ mkFastString $ - ".section __DWARF,__debug_" ++ name ++ ",regular,debug" - _other -> ftext $ mkFastString $ - ".section .debug_" ++ name ++ ",\"\", at progbits" + os | osElfTarget os + -> "\t.section .debug_" ++ name ++ ",\"\", at progbits" + | osMachOTarget os + -> "\t.section __DWARF,__debug_" ++ name ++ ",regular,debug" + | otherwise + -> "\t.section .debug_" ++ name ++ ",\"dr\"" -- | Dwarf section labels dwarfInfoLabel, dwarfAbbrevLabel, dwarfLineLabel, dwarfFrameLabel :: LitString diff --git a/compiler/nativeGen/Dwarf/Types.hs b/compiler/nativeGen/Dwarf/Types.hs index 520b5ae..00d0535 100644 --- a/compiler/nativeGen/Dwarf/Types.hs +++ b/compiler/nativeGen/Dwarf/Types.hs @@ -119,7 +119,7 @@ pprDwarfInfoOpen haveSrc (DwarfCompileUnit _ name producer compDir lineLbl) = $$ pprString compDir $$ pprFlag True -- use UTF8 $$ if haveSrc - then pprData4' (sectionOffset lineLbl dwarfLineLabel) + then sectionOffset lineLbl dwarfLineLabel else empty pprDwarfInfoOpen _ (DwarfSubprogram _ name label) = sdocWithDynFlags $ \df -> pprAbbrev DwAbbrSubprogram @@ -431,11 +431,13 @@ escapeChar c -- | Generate an offset into another section. This is tricky because -- this is handled differently depending on platform: Mac Os expects --- us to calculate the offset using assembler arithmetic. Meanwhile, --- GNU tools expect us to just reference the target directly, and will --- figure out on their own that we actually need an offset. +-- us to calculate the offset using assembler arithmetic. Linux expects +-- us to just reference the target directly, and will figure out on +-- their own that we actually need an offset. Finally, Windows has +-- a special directive to refer to relative offsets. Fun. sectionOffset :: LitString -> LitString -> SDoc sectionOffset target section = sdocWithPlatform $ \plat -> case platformOS plat of - OSDarwin -> ptext target <> char '-' <> ptext section - _other -> ptext target + OSDarwin -> pprDwWord (ptext target <> char '-' <> ptext section) + OSMinGW32 -> text "\t.secrel32 " <> ptext target + _other -> pprDwWord (ptext target) From git at git.haskell.org Thu Jun 11 17:29:52 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 Jun 2015 17:29:52 +0000 (UTC) Subject: [commit: ghc] master: Update submodule process to master (c1dc421) Message-ID: <20150611172952.3223C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c1dc4216efc3db1a8fbd56a658981b53b7e42eda/ghc >--------------------------------------------------------------- commit c1dc4216efc3db1a8fbd56a658981b53b7e42eda Author: Thomas Miedema Date: Thu Jun 11 19:24:25 2015 +0200 Update submodule process to master This allows a warning free build on Windows, and thus an error free validate. >--------------------------------------------------------------- c1dc4216efc3db1a8fbd56a658981b53b7e42eda libraries/process | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/process b/libraries/process index 67efaf5..e0983fb 160000 --- a/libraries/process +++ b/libraries/process @@ -1 +1 @@ -Subproject commit 67efaf599a03f454a98a3905820ce40aa80825c7 +Subproject commit e0983fbbfa8a3d81c7b99e83a3169fc686caab62 From git at git.haskell.org Thu Jun 11 17:29:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 Jun 2015 17:29:55 +0000 (UTC) Subject: [commit: ghc] master: Testsuite Windows: fix T8172 (#8172) (da84fd5) Message-ID: <20150611172955.19C1F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/da84fd5475d189c39bd3e12d29f45618c92ed800/ghc >--------------------------------------------------------------- commit da84fd5475d189c39bd3e12d29f45618c92ed800 Author: Thomas Miedema Date: Thu Jun 11 19:26:11 2015 +0200 Testsuite Windows: fix T8172 (#8172) Use the new function `normalise_drive_letter` to change D:\ to C:\ before comparing outputs. >--------------------------------------------------------------- da84fd5475d189c39bd3e12d29f45618c92ed800 testsuite/driver/testlib.py | 4 ++++ testsuite/tests/ghci/scripts/all.T | 3 ++- 2 files changed, 6 insertions(+), 1 deletion(-) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index db3ada4..671db9a 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -517,6 +517,10 @@ def normalise_version( *pkgs ): _normalise_errmsg_fun(name, opts, normalise_version_(*pkgs)) return normalise_version__ +def normalise_drive_letter(name, opts): + # Windows only. Change D:\\ to C:\\. + _normalise_fun(name, opts, lambda str: re.sub(r'[A-Z]:\\', r'C:\\', str)) + def join_normalisers(*a): """ Compose functions, flattening sequences. diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T index f0d7c19..8d7b5de 100755 --- a/testsuite/tests/ghci/scripts/all.T +++ b/testsuite/tests/ghci/scripts/all.T @@ -168,7 +168,8 @@ test('T7939', normal, ghci_script, ['T7939.script']) test('T7894', normal, ghci_script, ['T7894.script']) test('T8116', normal, ghci_script, ['T8116.script']) test('T8113', normal, ghci_script, ['T8113.script']) -test('T8172', normal, ghci_script, ['T8172.script']) +test('T8172', when(opsys('mingw32'), normalise_drive_letter), + ghci_script, ['T8172.script']) test('T8215', normal, ghci_script, ['T8215.script']) test('T8357', normal, ghci_script, ['T8357.script']) test('T8383', normal, ghci_script, ['T8383.script']) From git at git.haskell.org Thu Jun 11 17:29:58 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 Jun 2015 17:29:58 +0000 (UTC) Subject: [commit: ghc] master: Testsuite: mark tests as expect_broken on win64 (a765f72) Message-ID: <20150611172958.082DF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a765f72c130111cdbd30f2a3e159186c6e625d2a/ghc >--------------------------------------------------------------- commit a765f72c130111cdbd30f2a3e159186c6e625d2a Author: Thomas Miedema Date: Thu Jun 11 19:28:03 2015 +0200 Testsuite: mark tests as expect_broken on win64 Tickets: #1407, #9381, #9878. Differential Revision: https://phabricator.haskell.org/D977 >--------------------------------------------------------------- a765f72c130111cdbd30f2a3e159186c6e625d2a testsuite/tests/ghci/linking/all.T | 3 ++- testsuite/tests/ghci/scripts/all.T | 3 ++- testsuite/tests/rts/all.T | 1 + 3 files changed, 5 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/ghci/linking/all.T b/testsuite/tests/ghci/linking/all.T index c7ce1c3..4d05b8f 100644 --- a/testsuite/tests/ghci/linking/all.T +++ b/testsuite/tests/ghci/linking/all.T @@ -51,4 +51,5 @@ test('T3333', run_command, ['$MAKE -s --no-print-directory T3333']) -test('T1407', normal, ghci_script, ['T1407.script']) +test('T1407', when(opsys('mingw32'), expect_broken(1407)), + ghci_script, ['T1407.script']) diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T index 8d7b5de..df02add 100755 --- a/testsuite/tests/ghci/scripts/all.T +++ b/testsuite/tests/ghci/scripts/all.T @@ -204,7 +204,8 @@ test('T9878', [extra_clean(['T9878.hi','T9878.o'])], ghci_script, ['T9878.script']) test('T9878b', - [ extra_run_opts('-fobject-code'), + [ when(opsys('mingw32'), expect_broken(9878)), + extra_run_opts('-fobject-code'), extra_clean(['T9878b.hi','T9878b.o'])], ghci_script, ['T9878b.script']) test('T10122', normal, ghci_script, ['T10122.script']) diff --git a/testsuite/tests/rts/all.T b/testsuite/tests/rts/all.T index 914603d..029cf82 100644 --- a/testsuite/tests/rts/all.T +++ b/testsuite/tests/rts/all.T @@ -248,6 +248,7 @@ test('T10017', [ when(opsys('mingw32'), skip) , only_ways(threaded_ways), extra_run_opts('+RTS -N2 -RTS') ], compile_and_run, ['']) test('rdynamic', [ unless(opsys('linux') or opsys('mingw32'), skip) + , when(opsys('mingw32'), expect_broken(9381)) # this needs runtime infrastructure to do in ghci: # '-rdynamic' ghc, load modules only via dlopen(RTLD_BLOBAL) and more. , omit_ways(['ghci']) From git at git.haskell.org Thu Jun 11 17:34:56 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 Jun 2015 17:34:56 +0000 (UTC) Subject: [commit: ghc] master: Testsuite: mark T4945 as expect_broken (#4945) (506522c) Message-ID: <20150611173456.0CDBB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/506522c95f5d43db4d469135878c56fe20eb81f6/ghc >--------------------------------------------------------------- commit 506522c95f5d43db4d469135878c56fe20eb81f6 Author: Thomas Miedema Date: Thu Jun 11 17:25:47 2015 +0200 Testsuite: mark T4945 as expect_broken (#4945) In commit 7d519dabd2006c9742e82fce02df55704da15482, the file T4945.stdout was added to the repository, to make T4945 pass validatation presumably. When that test produces output however, there is a bug somewhere, and we shouldn't hide it. There is a comment in the Makefile which says: "When SpecConstr works there are no STUArrays at all" So here we remove T4945.stdout again, mark T4945 as expect_broken, and reopen the ticket. Differential Revision: https://phabricator.haskell.org/D976 >--------------------------------------------------------------- 506522c95f5d43db4d469135878c56fe20eb81f6 testsuite/tests/simplCore/should_compile/T4945.stdout | 9 --------- testsuite/tests/simplCore/should_compile/all.T | 2 +- 2 files changed, 1 insertion(+), 10 deletions(-) diff --git a/testsuite/tests/simplCore/should_compile/T4945.stdout b/testsuite/tests/simplCore/should_compile/T4945.stdout deleted file mode 100644 index 4e53cfd..0000000 --- a/testsuite/tests/simplCore/should_compile/T4945.stdout +++ /dev/null @@ -1,9 +0,0 @@ - -> STUArray RealWorld Int Int -> (# State# RealWorld, () #) - (ipv3 [OS=OneShot] :: STUArray RealWorld Int Int) -> - case ipv3 of _ [Occ=Dead] { STUArray ds5 ds6 dt ds7 -> - (Data.Array.Base.STUArray - (Data.Array.Base.STUArray - (Data.Array.Base.STUArray - (Data.Array.Base.STUArray - (Data.Array.Base.STUArray - (Data.Array.Base.STUArray diff --git a/testsuite/tests/simplCore/should_compile/all.T b/testsuite/tests/simplCore/should_compile/all.T index 1f7dffa..26f73e9 100644 --- a/testsuite/tests/simplCore/should_compile/all.T +++ b/testsuite/tests/simplCore/should_compile/all.T @@ -107,7 +107,7 @@ test('T4918', ['$MAKE -s --no-print-directory T4918']) test('T4945', - normal, + expect_broken(4945), run_command, ['$MAKE -s --no-print-directory T4945']) From git at git.haskell.org Thu Jun 11 18:00:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 Jun 2015 18:00:31 +0000 (UTC) Subject: [commit: ghc] master: Testsuite: mention the existence of ticket #10510 (6cefeb3) Message-ID: <20150611180031.041E93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6cefeb373e13c25f6c8c1d08975e14a8655f0bc9/ghc >--------------------------------------------------------------- commit 6cefeb373e13c25f6c8c1d08975e14a8655f0bc9 Author: Thomas Miedema Date: Thu Jun 11 13:46:41 2015 +0200 Testsuite: mention the existence of ticket #10510 [skip ci] >--------------------------------------------------------------- 6cefeb373e13c25f6c8c1d08975e14a8655f0bc9 testsuite/driver/runtests.py | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/driver/runtests.py b/testsuite/driver/runtests.py index 87a0889..5a0770d 100644 --- a/testsuite/driver/runtests.py +++ b/testsuite/driver/runtests.py @@ -139,7 +139,7 @@ if config.use_threads == 1: print("Warning: Ignoring request to use threads as python version is 2.7.2") print("See http://bugs.python.org/issue13817 for details.") config.use_threads = 0 - if windows: + if windows: # See Trac ticket #10510. print("Warning: Ignoring request to use threads as running on Windows") config.use_threads = 0 From git at git.haskell.org Thu Jun 11 18:00:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 Jun 2015 18:00:33 +0000 (UTC) Subject: [commit: ghc] master: Testsuite: change some expect_fail tests to expect_broken (5e66a69) Message-ID: <20150611180033.C54163A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5e66a698dae8c01bcd1a9335346145b32016e119/ghc >--------------------------------------------------------------- commit 5e66a698dae8c01bcd1a9335346145b32016e119 Author: Thomas Miedema Date: Wed Jun 3 15:15:57 2015 +0200 Testsuite: change some expect_fail tests to expect_broken Change the following tests from expect_fail to expect_broken: and list the ticket number: * driver/sigof03m/sigof03 (#9252) * driver/static001 (#8127) * partial-sigs/should_compile/EqualityConstraint (#9478) * partial-sigs/should_compile/ExtraNumAMROn (#9478) * partial-sigs/should_compile/PatBind2 (#9478) * partial-sigs/should_fail/TidyClash2 (#9478) * simplCore/should_compile/T8832 (#8832) The following tests are still marked as expect_fail, but it is not clearly documented why so: * gadt/lazypatok * indexed-types/should_fail/SkolemOccursLoop All other expect_fail tests are only expected to fail on either a certain platform/os or for a certain way only. Differential Revision: https://phabricator.haskell.org/D966 >--------------------------------------------------------------- 5e66a698dae8c01bcd1a9335346145b32016e119 testsuite/driver/testlib.py | 5 +++++ testsuite/tests/driver/T8602/T8602.T | 3 +++ testsuite/tests/driver/all.T | 2 +- testsuite/tests/driver/sigof03/all.T | 2 +- testsuite/tests/gadt/all.T | 2 ++ testsuite/tests/gadt/lazypatok.hs | 2 +- testsuite/tests/partial-sigs/should_compile/all.T | 6 +++--- testsuite/tests/partial-sigs/should_fail/all.T | 2 +- testsuite/tests/simplCore/should_compile/all.T | 2 +- 9 files changed, 18 insertions(+), 8 deletions(-) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index 671db9a..c6150da 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -84,6 +84,9 @@ def skip( name, opts ): opts.skip = 1 def expect_fail( name, opts ): + # The compiler, testdriver, OS or platform is missing a certain + # feature, and we don't plan to or can't fix it now or in the + # future. opts.expect = 'fail'; def reqlib( lib ): @@ -149,6 +152,8 @@ def _expect_fail_for( name, opts, ways ): opts.expect_fail_for = ways def expect_broken( bug ): + # This test is a expected not to work due to the indicated trac bug + # number. return lambda name, opts, b=bug: _expect_broken (name, opts, b ) def _expect_broken( name, opts, bug ): diff --git a/testsuite/tests/driver/T8602/T8602.T b/testsuite/tests/driver/T8602/T8602.T index 7706031..22a63e2 100644 --- a/testsuite/tests/driver/T8602/T8602.T +++ b/testsuite/tests/driver/T8602/T8602.T @@ -1,4 +1,7 @@ test('T8602', [extra_clean(['t8602.sh']), + # Windows runs the preprocessor using runInteractiveProcess and can't + # properly run the generated shell script as a result, since it can't + # recognize e.g. a shebang or anything. when(opsys('mingw32'), expect_fail)], ghci_script, ['T8602.script']) diff --git a/testsuite/tests/driver/all.T b/testsuite/tests/driver/all.T index 5d936d7..fa9e7b0 100644 --- a/testsuite/tests/driver/all.T +++ b/testsuite/tests/driver/all.T @@ -317,7 +317,7 @@ else: only_darwin = skip test('static001', - [only_darwin, expect_fail, + [only_darwin, expect_broken(8127), extra_clean(['Static001.hi', 'Static001.o', 'liba.a', 'Static001_stub.h', 'Static001_stub.o'])], run_command, ['$MAKE -s --no-print-directory static001']) diff --git a/testsuite/tests/driver/sigof03/all.T b/testsuite/tests/driver/sigof03/all.T index e8df3e1..a143508 100644 --- a/testsuite/tests/driver/sigof03/all.T +++ b/testsuite/tests/driver/sigof03/all.T @@ -6,6 +6,6 @@ test('sigof03', # This doesn't work yet, because the instances aren't found the # right way (they don't go in the EPS, differently from one-shot) test('sigof03m', - [ clean_cmd('rm -rf tmp_sigof03m'), expect_fail ], + [ clean_cmd('rm -rf tmp_sigof03m'), expect_broken(9252) ], run_command, ['$MAKE -s --no-print-directory sigof03m']) diff --git a/testsuite/tests/gadt/all.T b/testsuite/tests/gadt/all.T index cbbc0fc..c3d35bc 100644 --- a/testsuite/tests/gadt/all.T +++ b/testsuite/tests/gadt/all.T @@ -46,6 +46,8 @@ test('nbe', normal, compile, ['']) test('while', normal, compile_and_run, ['']) test('rw', normal, compile_fail, ['']) test('lazypat', normal, compile_fail, ['']) +# Not marked as expect_broken, because it's not clear whether this test should +# succeed or fail. test('lazypatok', expect_fail, compile, ['']) test('tc', normal, compile_and_run, ['']) test('arrow', normal, compile, ['']) diff --git a/testsuite/tests/gadt/lazypatok.hs b/testsuite/tests/gadt/lazypatok.hs index bf1282f..544705f 100644 --- a/testsuite/tests/gadt/lazypatok.hs +++ b/testsuite/tests/gadt/lazypatok.hs @@ -2,7 +2,7 @@ -- It's not clear whether this one should succed or fail, -- Arguably it should succeed because the type refinement on --- T1 should make (y::Int). Currently, though, it succeeds +-- T1 should make (y::Int). Currently, though, it fails. module ShouldFail where diff --git a/testsuite/tests/partial-sigs/should_compile/all.T b/testsuite/tests/partial-sigs/should_compile/all.T index 812ff0a..56f1045 100644 --- a/testsuite/tests/partial-sigs/should_compile/all.T +++ b/testsuite/tests/partial-sigs/should_compile/all.T @@ -13,14 +13,14 @@ test('Either', normal, compile, ['-ddump-types -fno-warn-partial-type-signatures test('Every', normal, compile, ['-ddump-types -fno-warn-partial-type-signatures']) test('EveryNamed', normal, compile, ['-ddump-types -fno-warn-partial-type-signatures']) # Bug -test('EqualityConstraint', expect_fail, compile, ['-ddump-types -fno-warn-partial-type-signatures']) +test('EqualityConstraint', expect_broken(9478), compile, ['-ddump-types -fno-warn-partial-type-signatures']) test('ExpressionSig', normal, compile, ['-ddump-types -fno-warn-partial-type-signatures']) test('ExpressionSigNamed', normal, compile, ['-ddump-types -fno-warn-partial-type-signatures']) test('ExtraConstraints1', normal, compile, ['-ddump-types -fno-warn-partial-type-signatures']) test('ExtraConstraints2', normal, compile, ['-ddump-types -fno-warn-partial-type-signatures']) test('ExtraConstraints3', normal, compile, ['-ddump-types -fno-warn-partial-type-signatures']) # Bug -test('ExtraNumAMROn', expect_fail, compile, ['-ddump-types -fno-warn-partial-type-signatures']) +test('ExtraNumAMROn', expect_broken(9478), compile, ['-ddump-types -fno-warn-partial-type-signatures']) test('ExtraNumAMROff', normal, compile, ['-ddump-types -fno-warn-partial-type-signatures']) test('Forall1', normal, compile, ['-ddump-types -fno-warn-partial-type-signatures']) test('GenNamed', normal, compile, ['-ddump-types -fno-warn-partial-type-signatures']) @@ -34,7 +34,7 @@ test('NamedTyVar', normal, compile, ['-ddump-types -fno-warn-partial-type-signat test('ParensAroundContext', normal, compile, ['-ddump-types -fno-warn-partial-type-signatures']) test('PatBind', normal, compile, ['-ddump-types -fno-warn-partial-type-signatures']) # Bug -test('PatBind2', expect_fail, compile, ['-ddump-types -fno-warn-partial-type-signatures']) +test('PatBind2', expect_broken(9478), compile, ['-ddump-types -fno-warn-partial-type-signatures']) test('PatternSig', normal, compile, ['-ddump-types -fno-warn-partial-type-signatures']) test('Recursive', normal, compile, ['-ddump-types -fno-warn-partial-type-signatures']) test('ScopedNamedWildcards', normal, compile, ['-ddump-types -fno-warn-partial-type-signatures']) diff --git a/testsuite/tests/partial-sigs/should_fail/all.T b/testsuite/tests/partial-sigs/should_fail/all.T index 412dd77..16d809d 100644 --- a/testsuite/tests/partial-sigs/should_fail/all.T +++ b/testsuite/tests/partial-sigs/should_fail/all.T @@ -19,7 +19,7 @@ test('PartialTypeSignaturesDisabled', normal, compile_fail, ['']) test('ScopedNamedWildcardsBad', normal, compile_fail, ['']) test('TidyClash', normal, compile_fail, ['']) # Bug -test('TidyClash2', expect_fail, compile_fail, ['']) +test('TidyClash2', expect_broken(9478), compile_fail, ['']) test('Trac10045', normal, compile_fail, ['']) test('UnnamedConstraintWildcard1', normal, compile_fail, ['']) test('UnnamedConstraintWildcard2', normal, compile_fail, ['']) diff --git a/testsuite/tests/simplCore/should_compile/all.T b/testsuite/tests/simplCore/should_compile/all.T index 26f73e9..f7ff85b 100644 --- a/testsuite/tests/simplCore/should_compile/all.T +++ b/testsuite/tests/simplCore/should_compile/all.T @@ -198,7 +198,7 @@ test('T5996', ['$MAKE -s --no-print-directory T5996']) test('T8537', normal, compile, ['']) test('T8832', - expect_fail, + expect_broken(8832), run_command, ['$MAKE -s --no-print-directory T8832 T8832_WORDSIZE_OPTS=' + ('-DT8832_WORDSIZE_64' if wordsize(64) else '')]) From git at git.haskell.org Thu Jun 11 18:33:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 Jun 2015 18:33:40 +0000 (UTC) Subject: [commit: ghc] master: Travis: use apt-get -q (a4318c6) Message-ID: <20150611183340.928523A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a4318c668fa49ff3423feed184c0ce58227359b8/ghc >--------------------------------------------------------------- commit a4318c668fa49ff3423feed184c0ce58227359b8 Author: Thomas Miedema Date: Fri Jun 5 12:53:51 2015 +0200 Travis: use apt-get -q [skip ci] >--------------------------------------------------------------- a4318c668fa49ff3423feed184c0ce58227359b8 .travis.yml | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/.travis.yml b/.travis.yml index 836e62a..a1e22c9 100644 --- a/.travis.yml +++ b/.travis.yml @@ -10,9 +10,9 @@ before_install: - travis_retry sudo add-apt-repository -y ppa:ubuntu-toolchain-r/test - travis_retry sudo sh -c "echo 'deb http://llvm.org/apt/precise/ llvm-toolchain-precise-3.6 main' >> /etc/apt/sources.list" - wget -O - http://llvm.org/apt/llvm-snapshot.gpg.key | sudo apt-key add - - - travis_retry sudo apt-get update - - travis_retry sudo apt-get install cabal-install-1.18 ghc-7.6.3 alex-3.1.3 happy-1.19.4 - - travis_retry sudo apt-get install llvm-3.6 + - travis_retry sudo apt-get -q update + - travis_retry sudo apt-get -q install cabal-install-1.18 ghc-7.6.3 alex-3.1.3 happy-1.19.4 + - travis_retry sudo apt-get -q install llvm-3.6 - export PATH=/opt/ghc/7.6.3/bin:/opt/cabal/1.18/bin:/opt/alex/3.1.3/bin:/opt/happy/1.19.4/bin:/usr/lib/llvm-3.6/bin:$PATH # Be explicit about which protocol to use, such that we don't have to repeat the rewrite command for each. From git at git.haskell.org Thu Jun 11 18:33:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 Jun 2015 18:33:43 +0000 (UTC) Subject: [commit: ghc] master: Removes all occurrences of __MINGW32__ (#10485) (0db0ac4) Message-ID: <20150611183343.4EF213A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0db0ac4a255931036c5859c3f22108f4e27ccd11/ghc >--------------------------------------------------------------- commit 0db0ac4a255931036c5859c3f22108f4e27ccd11 Author: Thomas Miedema Date: Thu Jun 11 20:31:24 2015 +0200 Removes all occurrences of __MINGW32__ (#10485) In Haskell files, replace `__MINGW32__` by `mingw32_HOST_OS`. In .c and .h files, delete `__MINGW32__` when `_WIN32` is also tested because `_WIN32` is always defined when `__MINGW32__` is. Also replace `__MINGW32__` by `_WIN32` when used standalone for consistency. Differential Revision: https://phabricator.haskell.org/D971 >--------------------------------------------------------------- 0db0ac4a255931036c5859c3f22108f4e27ccd11 libraries/base/System/Posix/Internals.hs | 14 +++++++------- libraries/base/cbits/Win32Utils.c | 2 +- libraries/base/cbits/consUtils.c | 4 ++-- libraries/base/cbits/iconv.c | 2 +- libraries/base/cbits/inputReady.c | 4 ++-- libraries/base/include/HsBase.h | 22 +++++++++++----------- utils/hp2ps/Main.c | 2 +- utils/touchy/touchy.c | 2 +- 8 files changed, 26 insertions(+), 26 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 0db0ac4a255931036c5859c3f22108f4e27ccd11 From git at git.haskell.org Thu Jun 11 21:57:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 Jun 2015 21:57:47 +0000 (UTC) Subject: [commit: ghc] master: Add failing test for #9562. (23582b0) Message-ID: <20150611215747.0681C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/23582b0c16bb147dad6bd7dee98686a8b61eacea/ghc >--------------------------------------------------------------- commit 23582b0c16bb147dad6bd7dee98686a8b61eacea Author: Edward Z. Yang Date: Thu Jun 11 14:57:50 2015 -0700 Add failing test for #9562. Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- 23582b0c16bb147dad6bd7dee98686a8b61eacea testsuite/.gitignore | 1 + testsuite/tests/driver/T9562/A.hs | 5 +++++ testsuite/tests/driver/T9562/B.hs | 11 +++++++++++ .../tests/{ghci/prog010/B.hs => driver/T9562/B.hs-boot} | 2 ++ .../scripts/break023/A1.hs => driver/T9562/C.hs} | 3 ++- testsuite/tests/driver/T9562/D.hs | 11 +++++++++++ testsuite/tests/driver/T9562/Main.hs | 5 +++++ testsuite/tests/driver/T9562/Makefile | 12 ++++++++++++ testsuite/tests/driver/T9562/all.T | 6 ++++++ 9 files changed, 55 insertions(+), 1 deletion(-) diff --git a/testsuite/.gitignore b/testsuite/.gitignore index 1855727..ade0024 100644 --- a/testsuite/.gitignore +++ b/testsuite/.gitignore @@ -540,6 +540,7 @@ mk/ghcconfig*_inplace_bin_ghc-stage2.exe.mk /tests/driver/T7835/Test /tests/driver/T8526/A.inc /tests/driver/T8602/t8602.sh +/tests/driver/T9562/Main /tests/driver/Test.081b /tests/driver/Test.081b.hs /tests/driver/Test_081a diff --git a/testsuite/tests/driver/T9562/A.hs b/testsuite/tests/driver/T9562/A.hs new file mode 100644 index 0000000..03f5ad3 --- /dev/null +++ b/testsuite/tests/driver/T9562/A.hs @@ -0,0 +1,5 @@ +{-# LANGUAGE TypeFamilies #-} + +module A where + +type family F a b diff --git a/testsuite/tests/driver/T9562/B.hs b/testsuite/tests/driver/T9562/B.hs new file mode 100644 index 0000000..34fe7b8 --- /dev/null +++ b/testsuite/tests/driver/T9562/B.hs @@ -0,0 +1,11 @@ +{-# LANGUAGE TypeFamilies #-} + +module B where + +import A +import C + +type instance F a b = b + +oops :: F a b -> a -> b +oops = const diff --git a/testsuite/tests/ghci/prog010/B.hs b/testsuite/tests/driver/T9562/B.hs-boot similarity index 50% copy from testsuite/tests/ghci/prog010/B.hs copy to testsuite/tests/driver/T9562/B.hs-boot index ce9e7e4..facbc8c 100644 --- a/testsuite/tests/ghci/prog010/B.hs +++ b/testsuite/tests/driver/T9562/B.hs-boot @@ -1,3 +1,5 @@ module B where import A + +oops :: F a b -> a -> b diff --git a/testsuite/tests/ghci.debugger/scripts/break023/A1.hs b/testsuite/tests/driver/T9562/C.hs similarity index 51% copy from testsuite/tests/ghci.debugger/scripts/break023/A1.hs copy to testsuite/tests/driver/T9562/C.hs index 138a4fa..bca4f46 100644 --- a/testsuite/tests/ghci.debugger/scripts/break023/A1.hs +++ b/testsuite/tests/driver/T9562/C.hs @@ -1,2 +1,3 @@ -module A where +module C (oops) where + import {-# SOURCE #-} B diff --git a/testsuite/tests/driver/T9562/D.hs b/testsuite/tests/driver/T9562/D.hs new file mode 100644 index 0000000..c9beceb --- /dev/null +++ b/testsuite/tests/driver/T9562/D.hs @@ -0,0 +1,11 @@ +{-# LANGUAGE TypeFamilies #-} + +module D where + +import A +import C + +type instance F a b = a + +unsafeCoerce :: a -> b +unsafeCoerce x = oops x x diff --git a/testsuite/tests/driver/T9562/Main.hs b/testsuite/tests/driver/T9562/Main.hs new file mode 100644 index 0000000..fabf5f5 --- /dev/null +++ b/testsuite/tests/driver/T9562/Main.hs @@ -0,0 +1,5 @@ +module Main where + +import D ( unsafeCoerce ) + +main = print $ (unsafeCoerce True :: Int) diff --git a/testsuite/tests/driver/T9562/Makefile b/testsuite/tests/driver/T9562/Makefile new file mode 100644 index 0000000..423389d --- /dev/null +++ b/testsuite/tests/driver/T9562/Makefile @@ -0,0 +1,12 @@ +TOP=../../.. +include $(TOP)/mk/boilerplate.mk +include $(TOP)/mk/test.mk + +T9562: + rm -f *.o *.hi *.o-boot *.hi-boot Main + '$(TEST_HC)' -c A.hs + '$(TEST_HC)' -c B.hs-boot + '$(TEST_HC)' -c C.hs + '$(TEST_HC)' -c B.hs + '$(TEST_HC)' -c D.hs + ! ('$(TEST_HC)' Main.hs && ./Main) diff --git a/testsuite/tests/driver/T9562/all.T b/testsuite/tests/driver/T9562/all.T new file mode 100644 index 0000000..ab379ee --- /dev/null +++ b/testsuite/tests/driver/T9562/all.T @@ -0,0 +1,6 @@ +setTestOpts(only_compiler_types(['ghc'])) + +test('T9562', + [extra_clean(['A011.hi', 'A011.o']), expect_broken(9562)], + run_command, + ['$MAKE -s --no-print-directory T9562']) From git at git.haskell.org Thu Jun 11 22:21:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 Jun 2015 22:21:54 +0000 (UTC) Subject: [commit: ghc] master: Remove redundant tcg_visible_orphan_mods, it is recorded in imp_orphs. (28e04de) Message-ID: <20150611222154.AA40D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/28e04de37151f05c35377ec74ac214d0cfa2f521/ghc >--------------------------------------------------------------- commit 28e04de37151f05c35377ec74ac214d0cfa2f521 Author: Edward Z. Yang Date: Wed Jun 3 15:29:00 2015 -0700 Remove redundant tcg_visible_orphan_mods, it is recorded in imp_orphs. Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: simonpj, austin Subscribers: bgamari, thomie Differential Revision: https://phabricator.haskell.org/D947 >--------------------------------------------------------------- 28e04de37151f05c35377ec74ac214d0cfa2f521 compiler/typecheck/Inst.hs | 2 +- compiler/typecheck/TcEnv.hs | 2 +- compiler/typecheck/TcRnDriver.hs | 17 ++++++++--------- compiler/typecheck/TcRnMonad.hs | 1 - compiler/typecheck/TcRnTypes.hs | 11 +++++------ 5 files changed, 15 insertions(+), 18 deletions(-) diff --git a/compiler/typecheck/Inst.hs b/compiler/typecheck/Inst.hs index c1a1c5a..07d7e0a 100644 --- a/compiler/typecheck/Inst.hs +++ b/compiler/typecheck/Inst.hs @@ -514,7 +514,7 @@ addLocalInst (home_ie, my_insts) ispec | otherwise = eps_inst_env eps inst_envs = InstEnvs { ie_global = global_ie , ie_local = home_ie' - , ie_visible = tcg_visible_orphan_mods tcg_env } + , ie_visible = tcVisibleOrphanMods tcg_env } (matches, _, _) = lookupInstEnv False inst_envs cls tys dups = filter (identicalClsInstHead ispec) (map fst matches) diff --git a/compiler/typecheck/TcEnv.hs b/compiler/typecheck/TcEnv.hs index 6337b3d..8db9f26 100644 --- a/compiler/typecheck/TcEnv.hs +++ b/compiler/typecheck/TcEnv.hs @@ -232,7 +232,7 @@ tcGetInstEnvs = do { eps <- getEps ; env <- getGblEnv ; return (InstEnvs { ie_global = eps_inst_env eps , ie_local = tcg_inst_env env - , ie_visible = tcg_visible_orphan_mods env }) } + , ie_visible = tcVisibleOrphanMods env }) } instance MonadThings (IOEnv (Env TcGblEnv TcLclEnv)) where lookupThing = tcLookupGlobal diff --git a/compiler/typecheck/TcRnDriver.hs b/compiler/typecheck/TcRnDriver.hs index 16c8d37..585d3b3 100644 --- a/compiler/typecheck/TcRnDriver.hs +++ b/compiler/typecheck/TcRnDriver.hs @@ -418,9 +418,6 @@ tcRnImports hsc_env import_decls tcg_rdr_env = tcg_rdr_env gbl `plusGlobalRdrEnv` rdr_env, tcg_imports = tcg_imports gbl `plusImportAvails` imports, tcg_rn_imports = rn_imports, - tcg_visible_orphan_mods = foldl extendModuleSet - (tcg_visible_orphan_mods gbl) - (imp_orphs imports), tcg_inst_env = extendInstEnvList (tcg_inst_env gbl) home_insts, tcg_fam_inst_env = extendFamInstEnvList (tcg_fam_inst_env gbl) home_fam_insts, @@ -1405,14 +1402,18 @@ runTcInteractive hsc_env thing_inside vcat (map ppr [ local_gres | gres <- occEnvElts (ic_rn_gbl_env icxt) , let local_gres = filter isLocalGRE gres , not (null local_gres) ]) ] + ; let getOrphans m = fmap (concatMap (\iface -> mi_module iface : dep_orphs (mi_deps iface))) (loadSrcInterface (text "runTcInteractive") m False Nothing) - ; ic_visible_mods <- fmap concat . forM (ic_imports icxt) $ \i -> + ; orphs <- fmap concat . forM (ic_imports icxt) $ \i -> case i of IIModule n -> getOrphans n IIDecl i -> getOrphans (unLoc (ideclName i)) + ; let imports = emptyImportAvails { + imp_orphs = orphs + } ; (gbl_env, lcl_env) <- getEnvs ; let gbl_env' = gbl_env { tcg_rdr_env = ic_rn_gbl_env icxt @@ -1430,11 +1431,9 @@ runTcInteractive hsc_env thing_inside -- to make RecordWildCards work (test: ghci049) , tcg_fix_env = ic_fix_env icxt , tcg_default = ic_default icxt - , tcg_visible_orphan_mods = mkModuleSet ic_visible_mods - -- I guess there's a risk ic_imports will be - -- desynchronized with the true RdrEnv; probably - -- should insert some ASSERTs somehow. - -- TODO: Cache this + -- must calculate imp_orphs of the ImportAvails + -- so that instance visibility is done correctly + , tcg_imports = imports } ; lcl_env' <- tcExtendLocalTypeEnv lcl_env lcl_ids diff --git a/compiler/typecheck/TcRnMonad.hs b/compiler/typecheck/TcRnMonad.hs index c299f29..3c69b95 100644 --- a/compiler/typecheck/TcRnMonad.hs +++ b/compiler/typecheck/TcRnMonad.hs @@ -133,7 +133,6 @@ initTc hsc_env hsc_src keep_rn_syntax mod loc do_this tcg_inst_env = emptyInstEnv, tcg_fam_inst_env = emptyFamInstEnv, tcg_ann_env = emptyAnnEnv, - tcg_visible_orphan_mods = mkModuleSet [mod], tcg_th_used = th_var, tcg_th_splice_used = th_splice_var, tcg_exports = [], diff --git a/compiler/typecheck/TcRnTypes.hs b/compiler/typecheck/TcRnTypes.hs index 1509356..cf7e39c 100644 --- a/compiler/typecheck/TcRnTypes.hs +++ b/compiler/typecheck/TcRnTypes.hs @@ -26,6 +26,7 @@ module TcRnTypes( Env(..), TcGblEnv(..), TcLclEnv(..), IfGblEnv(..), IfLclEnv(..), + tcVisibleOrphanMods, -- Renamer types ErrCtxt, RecFieldEnv(..), @@ -374,12 +375,6 @@ data TcGblEnv tcg_fam_inst_env :: FamInstEnv, -- ^ Ditto for family instances tcg_ann_env :: AnnEnv, -- ^ And for annotations - tcg_visible_orphan_mods :: ModuleSet, - -- ^ The set of orphan modules which transitively reachable from - -- direct imports. We use this to figure out if an orphan instance - -- in the global InstEnv should be considered visible. - -- See Note [Instance lookup and orphan instances] in InstEnv - -- Now a bunch of things about this module that are simply -- accumulated, but never consulted until the end. -- Nevertheless, it's convenient to accumulate them along @@ -499,6 +494,10 @@ data TcGblEnv -- ^ Wanted constraints of static forms. } +tcVisibleOrphanMods :: TcGblEnv -> ModuleSet +tcVisibleOrphanMods tcg_env + = mkModuleSet (tcg_mod tcg_env : imp_orphs (tcg_imports tcg_env)) + -- Note [Signature parameters in TcGblEnv and DynFlags] -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -- When compiling signature files, we need to know which implementation From git at git.haskell.org Thu Jun 11 23:18:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 Jun 2015 23:18:29 +0000 (UTC) Subject: [commit: ghc] master: Revert "Support for multiple signature files in scope." (bac927b) Message-ID: <20150611231829.190943A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bac927b9770ff769128b66d13a3e72bf5a9bc514/ghc >--------------------------------------------------------------- commit bac927b9770ff769128b66d13a3e72bf5a9bc514 Author: Edward Z. Yang Date: Thu Jun 11 15:24:27 2015 -0700 Revert "Support for multiple signature files in scope." This reverts commit a7524eaed33324e2155c47d4a705bef1d70a2b5b. >--------------------------------------------------------------- bac927b9770ff769128b66d13a3e72bf5a9bc514 compiler/deSugar/DsMonad.hs | 2 +- compiler/ghci/Linker.hs | 46 ++--- compiler/iface/LoadIface.hs | 18 +- compiler/iface/MkIface.hs | 18 +- compiler/main/DriverMkDepend.hs | 5 +- compiler/main/DynamicLoading.hs | 21 +- compiler/main/Finder.hs | 77 +++----- compiler/main/GHC.hs | 30 +-- compiler/main/GhcMake.hs | 19 +- compiler/main/HscTypes.hs | 36 +--- compiler/main/Packages.hs | 214 +++++++-------------- docs/users_guide/separate_compilation.xml | 5 - ghc/Main.hs | 5 +- testsuite/.gitignore | 6 - testsuite/tests/cabal/sigcabal02/Main.hs | 7 - testsuite/tests/cabal/sigcabal02/Makefile | 34 ---- testsuite/tests/cabal/sigcabal02/Setup.hs | 2 - testsuite/tests/cabal/sigcabal02/ShouldFail.hs | 1 - testsuite/tests/cabal/sigcabal02/all.T | 9 - testsuite/tests/cabal/sigcabal02/p/LICENSE | 0 testsuite/tests/cabal/sigcabal02/p/Map.hsig | 18 -- testsuite/tests/cabal/sigcabal02/p/P.hs | 12 -- testsuite/tests/cabal/sigcabal02/p/Set.hsig | 13 -- testsuite/tests/cabal/sigcabal02/p/p.cabal | 14 -- testsuite/tests/cabal/sigcabal02/q/LICENSE | 0 testsuite/tests/cabal/sigcabal02/q/Map.hsig | 7 - testsuite/tests/cabal/sigcabal02/q/Q.hs | 7 - testsuite/tests/cabal/sigcabal02/q/q.cabal | 13 -- testsuite/tests/cabal/sigcabal02/sigcabal02.stderr | 4 - testsuite/tests/cabal/sigcabal02/sigcabal02.stdout | 5 - testsuite/tests/driver/recomp014/Makefile | 31 --- testsuite/tests/driver/recomp014/all.T | 4 - testsuite/tests/driver/recomp014/recomp014.stdout | 4 - testsuite/tests/driver/sigof01/Makefile | 6 - testsuite/tests/driver/sigof01/all.T | 10 - testsuite/tests/driver/sigof01/sigof01i.script | 1 - testsuite/tests/driver/sigof01/sigof01i.stdout | 3 - testsuite/tests/driver/sigof01/sigof01i2.script | 3 - testsuite/tests/driver/sigof01/sigof01i2.stdout | 8 - testsuite/tests/package/package09e.stderr | 2 +- 40 files changed, 139 insertions(+), 581 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc bac927b9770ff769128b66d13a3e72bf5a9bc514 From git at git.haskell.org Thu Jun 11 23:18:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 11 Jun 2015 23:18:31 +0000 (UTC) Subject: [commit: ghc] master: Revert "Change loadSrcInterface to return a list of ModIface" (c60704f) Message-ID: <20150611231831.E9CF23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c60704fc405149407c155e297433f1cc299ae58a/ghc >--------------------------------------------------------------- commit c60704fc405149407c155e297433f1cc299ae58a Author: Edward Z. Yang Date: Thu Jun 11 15:33:59 2015 -0700 Revert "Change loadSrcInterface to return a list of ModIface" As it turns out, in our new design these changes are no longer needed. The code is simpler without returning a list of ModIface, so let's do it! This reverts commit 8c7d20d8c7e63a1123755aae69cfa825c749e9e8. >--------------------------------------------------------------- c60704fc405149407c155e297433f1cc299ae58a compiler/iface/LoadIface.hs | 50 ++++----------------------- compiler/rename/RnEnv.hs | 5 ++- compiler/rename/RnNames.hs | 74 +++++++++++++++------------------------- compiler/typecheck/TcRnDriver.hs | 5 ++- 4 files changed, 38 insertions(+), 96 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c60704fc405149407c155e297433f1cc299ae58a From git at git.haskell.org Fri Jun 12 09:03:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 12 Jun 2015 09:03:57 +0000 (UTC) Subject: [commit: ghc] master: Delete _MSC_VER when not necessary, fix #10511 (ce53138) Message-ID: <20150612090357.B07C93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ce53138ff0d156e9f229d0adab745d2d4cfaf582/ghc >--------------------------------------------------------------- commit ce53138ff0d156e9f229d0adab745d2d4cfaf582 Author: Bernard Desmyter Date: Fri Jun 12 11:01:45 2015 +0200 Delete _MSC_VER when not necessary, fix #10511 Simplify some preprocessor expressions involving `_MSC_VER` because `_WIN32` is always defined when `_MSC_VER` is. Differential Revision: https://phabricator.haskell.org/D981 >--------------------------------------------------------------- ce53138ff0d156e9f229d0adab745d2d4cfaf582 libraries/base/cbits/Win32Utils.c | 2 +- libraries/base/cbits/consUtils.c | 2 +- libraries/base/cbits/inputReady.c | 4 ++-- libraries/base/include/HsBase.h | 4 ++-- utils/hp2ps/Main.c | 2 +- utils/touchy/touchy.c | 2 +- 6 files changed, 8 insertions(+), 8 deletions(-) diff --git a/libraries/base/cbits/Win32Utils.c b/libraries/base/cbits/Win32Utils.c index 1b9292c..965adc2 100644 --- a/libraries/base/cbits/Win32Utils.c +++ b/libraries/base/cbits/Win32Utils.c @@ -4,7 +4,7 @@ Useful Win32 bits ------------------------------------------------------------------------- */ -#if defined(_MSC_VER) || defined(_WIN32) +#if defined(_WIN32) #include "HsBase.h" diff --git a/libraries/base/cbits/consUtils.c b/libraries/base/cbits/consUtils.c index c56be21..0c9202d 100644 --- a/libraries/base/cbits/consUtils.c +++ b/libraries/base/cbits/consUtils.c @@ -3,7 +3,7 @@ * * Win32 Console API support */ -#if defined(_MSC_VER) || defined(_WIN32) || defined(__CYGWIN__) +#if defined(_WIN32) || defined(__CYGWIN__) /* to the end */ #include "consUtils.h" diff --git a/libraries/base/cbits/inputReady.c b/libraries/base/cbits/inputReady.c index edb4472..8714eea 100644 --- a/libraries/base/cbits/inputReady.c +++ b/libraries/base/cbits/inputReady.c @@ -17,7 +17,7 @@ int fdReady(int fd, int write, int msecs, int isSock) { if -#if defined(_MSC_VER) || defined(_WIN32) +#if defined(_WIN32) ( isSock ) { #else ( 1 ) { @@ -54,7 +54,7 @@ fdReady(int fd, int write, int msecs, int isSock) /* 1 => Input ready, 0 => not ready, -1 => error */ return (ready); } -#if defined(_MSC_VER) || defined(_WIN32) +#if defined(_WIN32) else { DWORD rc; HANDLE hFile = (HANDLE)_get_osfhandle(fd); diff --git a/libraries/base/include/HsBase.h b/libraries/base/include/HsBase.h index 7afd5a5..a5512cc 100644 --- a/libraries/base/include/HsBase.h +++ b/libraries/base/include/HsBase.h @@ -298,7 +298,7 @@ __hscore_ftruncate( int fd, off_t where ) INLINE int __hscore_setmode( int fd, HsBool toBin ) { -#if defined(_MSC_VER) || defined(_WIN32) +#if defined(_WIN32) return setmode(fd,(toBin == HS_BOOL_TRUE) ? _O_BINARY : _O_TEXT); #else return 0; @@ -383,7 +383,7 @@ __hscore_sizeof_termios( void ) } #endif -#if !defined(_MSC_VER) && !defined(_WIN32) +#if !defined(_WIN32) INLINE HsInt __hscore_sizeof_sigset_t( void ) { diff --git a/utils/hp2ps/Main.c b/utils/hp2ps/Main.c index 709bb13..74d1bce 100644 --- a/utils/hp2ps/Main.c +++ b/utils/hp2ps/Main.c @@ -143,7 +143,7 @@ nextarg: ; if (!filter) { pathName = copystring(argv[0]); DropSuffix(pathName, ".hp"); -#if defined(_MSC_VER) || defined(_WIN32) +#if defined(_WIN32) DropSuffix(pathName, ".exe"); #endif baseName = copystring(Basename(pathName)); diff --git a/utils/touchy/touchy.c b/utils/touchy/touchy.c index a8ac146..88ababa 100644 --- a/utils/touchy/touchy.c +++ b/utils/touchy/touchy.c @@ -2,7 +2,7 @@ * Simple 'touch' program for Windows * */ -#if !defined(_MSC_VER) && !defined(_WIN32) +#if !defined(_WIN32) #error "Win32-only, the platform you're using is supposed to have 'touch' already." #else #include From git at git.haskell.org Fri Jun 12 09:19:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 12 Jun 2015 09:19:39 +0000 (UTC) Subject: [commit: ghc] master: docs: Fix unicode alternatives table (fixes #10509). (016bbfd) Message-ID: <20150612091939.2BE313A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/016bbfd261b91193baa99ec008b469a70c66b8be/ghc >--------------------------------------------------------------- commit 016bbfd261b91193baa99ec008b469a70c66b8be Author: Sebastian Reu?e Date: Fri Jun 12 10:36:15 2015 +0200 docs: Fix unicode alternatives table (fixes #10509). The alternatives table gave the wrong glyphs for LEFTWARDS resp. RIGHTWARDS ARROW-TAIL notation. The listed codepoint was correct, but the entities corresponded to characters different from those codepoints. This also adds the glyphs for LEFTWARDS resp. RIGHTWARDS DOUBLE ARROW-TAIL, which were formerly missing, and the PROPORTION glyph, which was formerly given as ASCII. >--------------------------------------------------------------- 016bbfd261b91193baa99ec008b469a70c66b8be docs/users_guide/glasgow_exts.xml | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/docs/users_guide/glasgow_exts.xml b/docs/users_guide/glasgow_exts.xml index 303833a..08208d4 100644 --- a/docs/users_guide/glasgow_exts.xml +++ b/docs/users_guide/glasgow_exts.xml @@ -322,7 +322,7 @@ Indeed, the bindings can even be recursive. :: - :: + 0x2237 PROPORTION @@ -363,7 +363,7 @@ Indeed, the bindings can even be recursive. -< - + 0x2919 LEFTWARDS ARROW-TAIL @@ -372,7 +372,7 @@ Indeed, the bindings can even be recursive. >- - + 0x291A RIGHTWARDS ARROW-TAIL @@ -381,7 +381,7 @@ Indeed, the bindings can even be recursive. -<< - + 0x291B LEFTWARDS DOUBLE ARROW-TAIL @@ -390,7 +390,7 @@ Indeed, the bindings can even be recursive. >>- - + 0x291C RIGHTWARDS DOUBLE ARROW-TAIL From git at git.haskell.org Fri Jun 12 09:23:28 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 12 Jun 2015 09:23:28 +0000 (UTC) Subject: [commit: ghc] master: Squash typos in comments (0ef7174) Message-ID: <20150612092328.B13E33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0ef71740f6cc5ffddc08eb610b4add7fbdaab54a/ghc >--------------------------------------------------------------- commit 0ef71740f6cc5ffddc08eb610b4add7fbdaab54a Author: Gabor Greif Date: Mon Jun 8 17:15:09 2015 +0200 Squash typos in comments >--------------------------------------------------------------- 0ef71740f6cc5ffddc08eb610b4add7fbdaab54a compiler/cmm/CmmUtils.hs | 2 +- rts/Linker.c | 2 +- rts/Trace.c | 2 +- 3 files changed, 3 insertions(+), 3 deletions(-) diff --git a/compiler/cmm/CmmUtils.hs b/compiler/cmm/CmmUtils.hs index d21d703..5495798 100644 --- a/compiler/cmm/CmmUtils.hs +++ b/compiler/cmm/CmmUtils.hs @@ -241,7 +241,7 @@ cmmLabelOff :: CLabel -> Int -> CmmLit cmmLabelOff lbl 0 = CmmLabel lbl cmmLabelOff lbl byte_off = CmmLabelOff lbl byte_off --- | Useful for creating an index into an array, with a staticaly known offset. +-- | Useful for creating an index into an array, with a statically known offset. -- The type is the element type; used for making the multiplier cmmIndex :: DynFlags -> Width -- Width w diff --git a/rts/Linker.c b/rts/Linker.c index bbf75bf..f3b170b 100644 --- a/rts/Linker.c +++ b/rts/Linker.c @@ -1692,7 +1692,7 @@ initLinker_ (int retain_cafs) barf("ghciInsertSymbolTable failed"); } - // Redurect newCAF to newRetainedCAF if retain_cafs is true. + // Redirect newCAF to newRetainedCAF if retain_cafs is true. if (! ghciInsertSymbolTable(WSTR("(GHCi built-in symbols)"), symhash, MAYBE_LEADING_UNDERSCORE_STR("newCAF"), retain_cafs ? newRetainedCAF : newGCdCAF, diff --git a/rts/Trace.c b/rts/Trace.c index bd4d332..dab7347 100644 --- a/rts/Trace.c +++ b/rts/Trace.c @@ -461,7 +461,7 @@ void traceOSProcessInfo_(void) { getpid()); #if !defined(cygwin32_HOST_OS) && !defined (mingw32_HOST_OS) -/* Windows has no strong concept of process heirarchy, so no getppid(). +/* Windows has no strong concept of process hierarchy, so no getppid(). * In any case, this trace event is mainly useful for tracing programs * that use 'forkProcess' which Windows doesn't support anyway. */ From git at git.haskell.org Fri Jun 12 09:39:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 12 Jun 2015 09:39:13 +0000 (UTC) Subject: [commit: ghc] master: Testsuite: fix the little known CHECK_FILES_WRITTEN=1 (c14bd01) Message-ID: <20150612093913.033B33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c14bd01756ffaf3a0bf34c766cfc1d611dba0dc4/ghc >--------------------------------------------------------------- commit c14bd01756ffaf3a0bf34c766cfc1d611dba0dc4 Author: Thomas Miedema Date: Sat May 30 12:33:20 2015 +0200 Testsuite: fix the little known CHECK_FILES_WRITTEN=1 The testsuite driver has a little known feature to check which files each test writes to, whether there are tests that write to same file, and whether the tests leave any files behind when CLEANUP=1. It uses strace under the hood. This commit fixes some bitrot, and filters out some more strace lines that we're not interested in (and are shown as framework failures otherwise). Differential Revision: https://phabricator.haskell.org/D979 >--------------------------------------------------------------- c14bd01756ffaf3a0bf34c766cfc1d611dba0dc4 testsuite/driver/testlib.py | 20 +++++++++++++++++--- 1 file changed, 17 insertions(+), 3 deletions(-) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index c6150da..462c854 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -1868,7 +1868,7 @@ def runCmdFor( name, cmd, timeout_multiplier=1.0 ): r = rawSystemWithTimeout( ["strace", "-o", fn, "-fF", "-e", "creat,open,chdir,clone,vfork", - config.timeout_prog, str(timeout), cmd]) + strip_quotes(config.timeout_prog), str(timeout), cmd]) addTestFilesWritten(name, fn) rm_no_fail(fn) else: @@ -1885,7 +1885,10 @@ def runCmdExitCode( cmd ): # checking for files being written to by multiple tests re_strace_call_end = '(\) += ([0-9]+|-1 E.*)| )$' -re_strace_unavailable = re.compile('^\) += \? $') +re_strace_unavailable_end ='\) += \? $' + +re_strace_unavailable_line = re.compile('^' + re_strace_unavailable_end) +re_strace_unavailable_cntnt = re.compile('^<\.\.\. .* resumed> ' + re_strace_unavailable_end) re_strace_pid = re.compile('^([0-9]+) +(.*)') re_strace_clone = re.compile('^(clone\(|<... clone resumed> ).*\) = ([0-9]+)$') re_strace_clone_unfinished = re.compile('^clone\( $') @@ -1896,7 +1899,10 @@ re_strace_chdir_resumed = re.compile('^<\.\.\. chdir resumed> \) += 0$') re_strace_open = re.compile('^open\("([^"]*)", ([A-Z_|]*)(, [0-9]+)?' + re_strace_call_end) re_strace_open_resumed = re.compile('^<... open resumed> ' + re_strace_call_end) re_strace_ignore_sigchild = re.compile('^--- SIGCHLD \(Child exited\) @ 0 \(0\) ---$') +re_strace_ignore_sigchild2 = re.compile('^--- SIGCHLD {si_signo=SIGCHLD, si_code=CLD_EXITED, .*} ---$') +re_strace_ignore_exited = re.compile('^\+\+\+ exited with [0-9]* \+\+\+$') re_strace_ignore_sigvtalarm = re.compile('^--- SIGVTALRM \(Virtual timer expired\) @ 0 \(0\) ---$') +re_strace_ignore_sigvtalarm2= re.compile('^--- SIGVTALRM {si_signo=SIGVTALRM, si_code=SI_TIMER, .*} ---$') re_strace_ignore_sigint = re.compile('^--- SIGINT \(Interrupt\) @ 0 \(0\) ---$') re_strace_ignore_sigfpe = re.compile('^--- SIGFPE \(Floating point exception\) @ 0 \(0\) ---$') re_strace_ignore_sigsegv = re.compile('^--- SIGSEGV \(Segmentation fault\) @ 0 \(0\) ---$') @@ -1942,7 +1948,7 @@ def addTestFilesWrittenHelper(name, fn): if m_pid: pid = m_pid.group(1) content = m_pid.group(2) - elif re_strace_unavailable.match(line): + elif re_strace_unavailable_line.match(line): next else: framework_fail(name, 'strace', "Can't find pid in strace line: " + line) @@ -1994,8 +2000,14 @@ def addTestFilesWrittenHelper(name, fn): pass elif re_strace_ignore_sigchild.match(content): pass + elif re_strace_ignore_sigchild2.match(content): + pass + elif re_strace_ignore_exited.match(content): + pass elif re_strace_ignore_sigvtalarm.match(content): pass + elif re_strace_ignore_sigvtalarm2.match(content): + pass elif re_strace_ignore_sigint.match(content): pass elif re_strace_ignore_sigfpe.match(content): @@ -2004,6 +2016,8 @@ def addTestFilesWrittenHelper(name, fn): pass elif re_strace_ignore_sigpipe.match(content): pass + elif re_strace_unavailable_cntnt.match(content): + pass else: framework_fail(name, 'strace', "Can't understand strace line: " + line) From git at git.haskell.org Fri Jun 12 12:15:06 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 12 Jun 2015 12:15:06 +0000 (UTC) Subject: [commit: ghc] master: Add parseExpr and compileParsedExpr and use them in GHC API and GHCi (d20031d) Message-ID: <20150612121506.4BA1C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d20031d4c88b256cdae264cb05d9d850e973d956/ghc >--------------------------------------------------------------- commit d20031d4c88b256cdae264cb05d9d850e973d956 Author: Simon Marlow Date: Fri Jun 12 13:15:18 2015 +0100 Add parseExpr and compileParsedExpr and use them in GHC API and GHCi Summary: This commit brings following changes and fixes: * Implement parseExpr and compileParsedExpr; * Fix compileExpr and dynCompilerExpr, which returned `()` for empty expr; * Fix :def and :cmd, which didn't work if `IO` or `String` is not in scope; * Use GHCiMonad instead IO in :def and :cmd; * Clean PrelInfo: delete dead comment and duplicate entries, add assertion. See new tests for more details. Test Plan: ./validate Reviewers: austin, dterei, simonmar Reviewed By: simonmar Subscribers: thomie, bgamari Differential Revision: https://phabricator.haskell.org/D974 GHC Trac Issues: #10508 >--------------------------------------------------------------- d20031d4c88b256cdae264cb05d9d850e973d956 compiler/main/GHC.hs | 9 +++- compiler/main/HscMain.hs | 71 +++++++++++++++++------------ compiler/main/InteractiveEval.hs | 73 ++++++++++++++++-------------- compiler/prelude/PrelInfo.hs | 19 ++++++-- compiler/prelude/PrelNames.hs | 23 ++++------ ghc/InteractiveUI.hs | 46 +++++++++++++------ testsuite/.gitignore | 1 + testsuite/tests/ghc-api/T10508_api.hs | 32 +++++++++++++ testsuite/tests/ghc-api/T10508_api.stderr | 4 ++ testsuite/tests/ghc-api/T10508_api.stdout | 3 ++ testsuite/tests/ghc-api/all.T | 7 ++- testsuite/tests/ghci/scripts/T10508.script | 21 +++++++++ testsuite/tests/ghci/scripts/T10508.stderr | 8 ++++ testsuite/tests/ghci/scripts/T10508.stdout | 6 +++ testsuite/tests/ghci/scripts/all.T | 1 + 15 files changed, 226 insertions(+), 98 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d20031d4c88b256cdae264cb05d9d850e973d956 From git at git.haskell.org Fri Jun 12 16:45:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 12 Jun 2015 16:45:43 +0000 (UTC) Subject: [commit: ghc] master: Do not copy stack after stack overflow, refix #8435 (892c3e9) Message-ID: <20150612164543.8F4493A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/892c3e98bcef50aa56ec818f4d001aee36e05bbc/ghc >--------------------------------------------------------------- commit 892c3e98bcef50aa56ec818f4d001aee36e05bbc Author: Flaviu Andrei Csernik (archblob) Date: Fri Jun 12 11:45:55 2015 -0500 Do not copy stack after stack overflow, refix #8435 Summary: This was reverted in d70b19bfb5ed79b22c2ac31e22f46782fc47a117 and is a part of the reason for #10445. Test Plan: validate Reviewers: ezyang, simonmar, austin Reviewed By: simonmar, austin Subscribers: bgamari, thomie Differential Revision: https://phabricator.haskell.org/D938 GHC Trac Issues: #8435 >--------------------------------------------------------------- 892c3e98bcef50aa56ec818f4d001aee36e05bbc rts/Threads.c | 1 + 1 file changed, 1 insertion(+) diff --git a/rts/Threads.c b/rts/Threads.c index ce297bd..434e129 100644 --- a/rts/Threads.c +++ b/rts/Threads.c @@ -551,6 +551,7 @@ threadStackOverflow (Capability *cap, StgTSO *tso) // Note [Throw to self when masked], also #767 and #8303. throwToSelf(cap, tso, (StgClosure *)stackOverflow_closure); + return; } From git at git.haskell.org Fri Jun 12 17:40:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 12 Jun 2015 17:40:44 +0000 (UTC) Subject: [commit: ghc] master: Fix typo in `traceShowM` haddock comment (#10392) (dd5cac7) Message-ID: <20150612174044.DBF8C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/dd5cac7cd379367d29c3ca486989f5c32e5ae848/ghc >--------------------------------------------------------------- commit dd5cac7cd379367d29c3ca486989f5c32e5ae848 Author: Thomas Miedema Date: Fri Jun 12 19:30:36 2015 +0200 Fix typo in `traceShowM` haddock comment (#10392) [skip ci] >--------------------------------------------------------------- dd5cac7cd379367d29c3ca486989f5c32e5ae848 libraries/base/Debug/Trace.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/libraries/base/Debug/Trace.hs b/libraries/base/Debug/Trace.hs index 47abcae..16aba3c 100644 --- a/libraries/base/Debug/Trace.hs +++ b/libraries/base/Debug/Trace.hs @@ -169,9 +169,9 @@ Like 'traceM', but uses 'show' on the argument to convert it to a 'String'. > ... = do > x <- ... -> traceMShow $ x +> traceShowM $ x > y <- ... -> traceMShow $ x + y +> traceShowM $ x + y @since 4.7.0.0 -} From git at git.haskell.org Fri Jun 12 17:40:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 12 Jun 2015 17:40:47 +0000 (UTC) Subject: [commit: ghc] master: Docs: it's `gv --orientation=seascape` nowadays (#10497) (0a086c8) Message-ID: <20150612174047.9EBDA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0a086c82638c443df10fa2f80896e30107e546e3/ghc >--------------------------------------------------------------- commit 0a086c82638c443df10fa2f80896e30107e546e3 Author: Thomas Miedema Date: Fri Jun 12 19:38:03 2015 +0200 Docs: it's `gv --orientation=seascape` nowadays (#10497) [skip ci] >--------------------------------------------------------------- 0a086c82638c443df10fa2f80896e30107e546e3 docs/users_guide/profiling.xml | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/docs/users_guide/profiling.xml b/docs/users_guide/profiling.xml index 26d18a0..d14419b 100644 --- a/docs/users_guide/profiling.xml +++ b/docs/users_guide/profiling.xml @@ -1335,7 +1335,7 @@ profile of your program as it runs. Simply generate an incremental heap profile as described in the previous section. Run gv on your profile: - gv -watch -seascape FOO.ps + gv -watch -orientation=seascape FOO.ps If you forget the -watch flag you can still select "Watch file" from the "State" menu. Now each time you generate a new @@ -1348,7 +1348,7 @@ This can all be encapsulated in a little script: #!/bin/sh head -`fgrep -n END_SAMPLE FOO.hp | tail -1 | cut -d : -f 1` FOO.hp \ | hp2ps > FOO.ps - gv -watch -seascape FOO.ps & + gv -watch -orientation=seascape FOO.ps & while [ 1 ] ; do sleep 10 # We generate a new profile every 10 seconds. head -`fgrep -n END_SAMPLE FOO.hp | tail -1 | cut -d : -f 1` FOO.hp \ From git at git.haskell.org Fri Jun 12 18:52:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 12 Jun 2015 18:52:57 +0000 (UTC) Subject: [commit: ghc] master: Docs: `-XTypeOperators` (#10175) (b07dccc) Message-ID: <20150612185257.B43873A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b07dcccd2219eb2d08868bc6144f289b4e0aadf1/ghc >--------------------------------------------------------------- commit b07dcccd2219eb2d08868bc6144f289b4e0aadf1 Author: Thomas Miedema Date: Fri Jun 12 20:06:31 2015 +0200 Docs: `-XTypeOperators` (#10175) [skip ci] >--------------------------------------------------------------- b07dcccd2219eb2d08868bc6144f289b4e0aadf1 docs/users_guide/glasgow_exts.xml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/docs/users_guide/glasgow_exts.xml b/docs/users_guide/glasgow_exts.xml index 08208d4..f5e04e0 100644 --- a/docs/users_guide/glasgow_exts.xml +++ b/docs/users_guide/glasgow_exts.xml @@ -2922,7 +2922,7 @@ if you write import M( (+) ) do you mean the function (+) or the type constructor (+)? The default is the former, but with (which is implied -by ) GHC allows you to specify the latter +by ) GHC allows you to specify the latter by preceding it with the keyword type, thus: import M( type (+) ) From git at git.haskell.org Fri Jun 12 18:56:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 12 Jun 2015 18:56:37 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Do not copy stack after stack overflow, refix #8435 (9c9bc6b) Message-ID: <20150612185637.0DA3B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/9c9bc6bf74f53300b8aa01fbccc279a18197459a/ghc >--------------------------------------------------------------- commit 9c9bc6bf74f53300b8aa01fbccc279a18197459a Author: Flaviu Andrei Csernik (archblob) Date: Fri Jun 12 11:45:55 2015 -0500 Do not copy stack after stack overflow, refix #8435 Summary: This was reverted in d70b19bfb5ed79b22c2ac31e22f46782fc47a117 and is a part of the reason for #10445. Test Plan: validate Reviewers: ezyang, simonmar, austin Reviewed By: simonmar, austin Subscribers: bgamari, thomie Differential Revision: https://phabricator.haskell.org/D938 GHC Trac Issues: #8435 (cherry picked from commit 892c3e98bcef50aa56ec818f4d001aee36e05bbc) >--------------------------------------------------------------- 9c9bc6bf74f53300b8aa01fbccc279a18197459a rts/Threads.c | 1 + 1 file changed, 1 insertion(+) diff --git a/rts/Threads.c b/rts/Threads.c index 99f2be7..38ddfb8 100644 --- a/rts/Threads.c +++ b/rts/Threads.c @@ -553,6 +553,7 @@ threadStackOverflow (Capability *cap, StgTSO *tso) // Note [Throw to self when masked], also #767 and #8303. throwToSelf(cap, tso, (StgClosure *)stackOverflow_closure); + return; } From git at git.haskell.org Fri Jun 12 18:56:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 12 Jun 2015 18:56:39 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Fix DWARF generation for MinGW (#10468) (800888b) Message-ID: <20150612185639.B88803A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/800888b0f56206038fe0b6276f6849fd24e3292b/ghc >--------------------------------------------------------------- commit 800888b0f56206038fe0b6276f6849fd24e3292b Author: Peter Wortmann Date: Thu Jun 11 12:09:55 2015 -0500 Fix DWARF generation for MinGW (#10468) Fortunately this is relatively straightforward - all we need to do is switch to a non-ELF-specific way of specifying object file sections and make sure that section-relative addresses work correctly. This is enough to make "gdb" work on MinGW builds. (cherry picked from commit a66ef3567ea29c93a9c010befc672602dc1c644c) >--------------------------------------------------------------- 800888b0f56206038fe0b6276f6849fd24e3292b compiler/nativeGen/Dwarf.hs | 2 +- compiler/nativeGen/Dwarf/Constants.hs | 12 +++++++----- compiler/nativeGen/Dwarf/Types.hs | 14 ++++++++------ 3 files changed, 16 insertions(+), 12 deletions(-) diff --git a/compiler/nativeGen/Dwarf.hs b/compiler/nativeGen/Dwarf.hs index ff86fd8..34f1ed6 100644 --- a/compiler/nativeGen/Dwarf.hs +++ b/compiler/nativeGen/Dwarf.hs @@ -86,7 +86,7 @@ compileUnitHeader unitU = sdocWithPlatform $ \plat -> in vcat [ ptext (sLit "\t.long ") <> length -- compilation unit size , ppr cuLabel <> colon , ptext (sLit "\t.word 3") -- DWARF version - , pprDwWord (sectionOffset dwarfAbbrevLabel dwarfAbbrevLabel) + , sectionOffset dwarfAbbrevLabel dwarfAbbrevLabel -- abbrevs offset , ptext (sLit "\t.byte ") <> ppr (platformWordSize plat) -- word size ] diff --git a/compiler/nativeGen/Dwarf/Constants.hs b/compiler/nativeGen/Dwarf/Constants.hs index 2cd54a7..4b334fc 100644 --- a/compiler/nativeGen/Dwarf/Constants.hs +++ b/compiler/nativeGen/Dwarf/Constants.hs @@ -122,12 +122,14 @@ dwarfFrameSection = dwarfSection "frame" dwarfGhcSection = dwarfSection "ghc" dwarfSection :: String -> SDoc -dwarfSection name = sdocWithPlatform $ \plat -> +dwarfSection name = sdocWithPlatform $ \plat -> ftext $ mkFastString $ case platformOS plat of - OSDarwin -> ftext $ mkFastString $ - ".section __DWARF,__debug_" ++ name ++ ",regular,debug" - _other -> ftext $ mkFastString $ - ".section .debug_" ++ name ++ ",\"\", at progbits" + os | osElfTarget os + -> "\t.section .debug_" ++ name ++ ",\"\", at progbits" + | osMachOTarget os + -> "\t.section __DWARF,__debug_" ++ name ++ ",regular,debug" + | otherwise + -> "\t.section .debug_" ++ name ++ ",\"dr\"" -- | Dwarf section labels dwarfInfoLabel, dwarfAbbrevLabel, dwarfLineLabel, dwarfFrameLabel :: LitString diff --git a/compiler/nativeGen/Dwarf/Types.hs b/compiler/nativeGen/Dwarf/Types.hs index 520b5ae..00d0535 100644 --- a/compiler/nativeGen/Dwarf/Types.hs +++ b/compiler/nativeGen/Dwarf/Types.hs @@ -119,7 +119,7 @@ pprDwarfInfoOpen haveSrc (DwarfCompileUnit _ name producer compDir lineLbl) = $$ pprString compDir $$ pprFlag True -- use UTF8 $$ if haveSrc - then pprData4' (sectionOffset lineLbl dwarfLineLabel) + then sectionOffset lineLbl dwarfLineLabel else empty pprDwarfInfoOpen _ (DwarfSubprogram _ name label) = sdocWithDynFlags $ \df -> pprAbbrev DwAbbrSubprogram @@ -431,11 +431,13 @@ escapeChar c -- | Generate an offset into another section. This is tricky because -- this is handled differently depending on platform: Mac Os expects --- us to calculate the offset using assembler arithmetic. Meanwhile, --- GNU tools expect us to just reference the target directly, and will --- figure out on their own that we actually need an offset. +-- us to calculate the offset using assembler arithmetic. Linux expects +-- us to just reference the target directly, and will figure out on +-- their own that we actually need an offset. Finally, Windows has +-- a special directive to refer to relative offsets. Fun. sectionOffset :: LitString -> LitString -> SDoc sectionOffset target section = sdocWithPlatform $ \plat -> case platformOS plat of - OSDarwin -> ptext target <> char '-' <> ptext section - _other -> ptext target + OSDarwin -> pprDwWord (ptext target <> char '-' <> ptext section) + OSMinGW32 -> text "\t.secrel32 " <> ptext target + _other -> pprDwWord (ptext target) From git at git.haskell.org Fri Jun 12 18:56:42 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 12 Jun 2015 18:56:42 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: docs: Fix #10416 (e6eaa9e) Message-ID: <20150612185642.6AA463A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/e6eaa9e44bc077189f3750b1b9bebdf8b204cfab/ghc >--------------------------------------------------------------- commit e6eaa9e44bc077189f3750b1b9bebdf8b204cfab Author: Austin Seipp Date: Wed Jun 10 16:43:23 2015 -0500 docs: Fix #10416 This commit fixes #10416 by using an EPS-based file-format for embedding images in the users guide, as opposed to a png. This is because 'latex' in some distributions is actually 'pdflatex', which supports reading the size of PNGs in DVI mode, while traditional latex does not. Rather than fiddle with the build a whole bunch, it's easy and simple to just convert the png into a eps file and embed that instead. But apparently we already had an EPS file, added in 1cce2f51656cfbd8c7933a914a4bd981792aa1e6! But it was quite large, so instead I used `convert` to shrink it down from 1.7MB to about 20kb, the same size as the original PDF (by using level3 postscript, which is not as wasteful.) Signed-off-by: Austin Seipp Differential Revision: https://phabricator.haskell.org/D970 GHC Trac Issues: #10416 (cherry picked from commit ca39b96ee783e124909a89ea3ad366bf99defa7b) >--------------------------------------------------------------- e6eaa9e44bc077189f3750b1b9bebdf8b204cfab docs/users_guide/ghc.mk | 6 +++--- docs/users_guide/prof_scc.eps | Bin 1685125 -> 17580 bytes docs/users_guide/prof_scc.png | Bin 16815 -> 0 bytes docs/users_guide/profiling.xml | 2 +- 4 files changed, 4 insertions(+), 4 deletions(-) diff --git a/docs/users_guide/ghc.mk b/docs/users_guide/ghc.mk index 4737b5c..eb7eb6a 100644 --- a/docs/users_guide/ghc.mk +++ b/docs/users_guide/ghc.mk @@ -27,10 +27,10 @@ $(eval $(call docbook,docs/users_guide,users_guide)) $(eval $(call clean-target,docs/users_guide,gen,$(docs/users_guide_GENERATED_DOCBOOK_SOURCES))) -html_docs/users_guide : docs/users_guide/users_guide/prof_scc.png +html_docs/users_guide : docs/users_guide/users_guide/prof_scc.eps -docs/users_guide/users_guide/prof_scc.png : \ - docs/users_guide/prof_scc.png \ +docs/users_guide/users_guide/prof_scc.eps : \ + docs/users_guide/prof_scc.eps \ docs/users_guide/users_guide/index.html $(CP) $< $@ # dep. on d/u/u/index.html is to make sure that the d/u/u dir is created first diff --git a/docs/users_guide/prof_scc.eps b/docs/users_guide/prof_scc.eps index db6e8d0..beac36f 100644 Binary files a/docs/users_guide/prof_scc.eps and b/docs/users_guide/prof_scc.eps differ diff --git a/docs/users_guide/prof_scc.png b/docs/users_guide/prof_scc.png deleted file mode 100644 index 5e4157d..0000000 Binary files a/docs/users_guide/prof_scc.png and /dev/null differ diff --git a/docs/users_guide/profiling.xml b/docs/users_guide/profiling.xml index 4971a7d..26d18a0 100644 --- a/docs/users_guide/profiling.xml +++ b/docs/users_guide/profiling.xml @@ -625,7 +625,7 @@ MAIN MAIN 102 0 0.0 0.0 100.0 1 other than making the PS file generation work, rather than falling over. The result seems to be broken PS on the page with the image. --> - You might also want to take a look From git at git.haskell.org Fri Jun 12 19:00:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 12 Jun 2015 19:00:23 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: libraries: update Cabal submodule (0d8ca63) Message-ID: <20150612190023.404EE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/0d8ca63d493cb9aadb3a76f317a16b7d8a1d6626/ghc >--------------------------------------------------------------- commit 0d8ca63d493cb9aadb3a76f317a16b7d8a1d6626 Author: Austin Seipp Date: Fri Jun 12 14:00:01 2015 -0500 libraries: update Cabal submodule Signed-off-by: Austin Seipp >--------------------------------------------------------------- 0d8ca63d493cb9aadb3a76f317a16b7d8a1d6626 libraries/Cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Cabal b/libraries/Cabal index bda1ce6..8402899 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit bda1ce6b757cdaca93f2eba4e1906a4658719537 +Subproject commit 8402899d220e0ad034944470ae86819b5f711801 From git at git.haskell.org Fri Jun 12 19:00:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 12 Jun 2015 19:00:26 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: utils: update haddock submodule (435808f) Message-ID: <20150612190026.062823A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/435808f534ab3c4e7d970d48526446111b28248d/ghc >--------------------------------------------------------------- commit 435808f534ab3c4e7d970d48526446111b28248d Author: Austin Seipp Date: Fri Jun 12 14:00:40 2015 -0500 utils: update haddock submodule Signed-off-by: Austin Seipp >--------------------------------------------------------------- 435808f534ab3c4e7d970d48526446111b28248d utils/haddock | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/haddock b/utils/haddock index a65953d..f48474f 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit a65953de929fd9488250f8e0257c918465193e43 +Subproject commit f48474f640387dca4b42182c1ac78ba30865742d From git at git.haskell.org Fri Jun 12 19:09:10 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 12 Jun 2015 19:09:10 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: docs: More 7.10.2 release notes (4e2c8f2) Message-ID: <20150612190910.242E13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/4e2c8f23cea9f966a943123c6ea949dac197a8ef/ghc >--------------------------------------------------------------- commit 4e2c8f23cea9f966a943123c6ea949dac197a8ef Author: Austin Seipp Date: Fri Jun 12 14:09:25 2015 -0500 docs: More 7.10.2 release notes Signed-off-by: Austin Seipp >--------------------------------------------------------------- 4e2c8f23cea9f966a943123c6ea949dac197a8ef docs/users_guide/7.10.2-notes.xml | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) diff --git a/docs/users_guide/7.10.2-notes.xml b/docs/users_guide/7.10.2-notes.xml index f9917ca..daaa67e 100644 --- a/docs/users_guide/7.10.2-notes.xml +++ b/docs/users_guide/7.10.2-notes.xml @@ -22,6 +22,11 @@ + DWARF support should now work on Windows/MinGW (#10468). + + + + A bug which caused GHC's libffi.so library to be built with executable stacks on some platforms has been fixed (issue #10208). @@ -152,7 +157,7 @@ - Version number 1.22.3.0 (was 1.22.2.0) + Version number 1.22.4.0 (was 1.22.2.0). From git at git.haskell.org Fri Jun 12 19:11:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 12 Jun 2015 19:11:41 +0000 (UTC) Subject: [commit: ghc] master: Add versioning section to Backpack docs. (e02a4f2) Message-ID: <20150612191141.B4D513A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e02a4f2329030f1843817298edf823578b4a0630/ghc >--------------------------------------------------------------- commit e02a4f2329030f1843817298edf823578b4a0630 Author: Edward Z. Yang Date: Fri Jun 12 12:11:41 2015 -0700 Add versioning section to Backpack docs. Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- e02a4f2329030f1843817298edf823578b4a0630 docs/backpack/Makefile | 5 +- docs/backpack/algorithm.pdf | Bin 280399 -> 288880 bytes docs/backpack/algorithm.tex | 147 ++++++++++++++++++++++++++++++++++++++++++++ 3 files changed, 148 insertions(+), 4 deletions(-) diff --git a/docs/backpack/Makefile b/docs/backpack/Makefile index a8df945..1cf4a8d 100644 --- a/docs/backpack/Makefile +++ b/docs/backpack/Makefile @@ -1,7 +1,4 @@ -all: backpack-impl.pdf backpack-manual.pdf ubackpack.pdf algorithm.pdf - -ubackpack.pdf: ubackpack.tex - latexmk -pdf -latexoption=-halt-on-error -latexoption=-file-line-error -latexoption=-synctex=1 ubackpack.tex || ! rm -f $@ +all: backpack-impl.pdf backpack-manual.pdf algorithm.pdf backpack-impl.pdf: backpack-impl.tex latexmk -pdf -latexoption=-halt-on-error -latexoption=-file-line-error -latexoption=-synctex=1 backpack-impl.tex || ! rm -f $@ diff --git a/docs/backpack/algorithm.pdf b/docs/backpack/algorithm.pdf index bff61ae..b8da93c 100644 Binary files a/docs/backpack/algorithm.pdf and b/docs/backpack/algorithm.pdf differ diff --git a/docs/backpack/algorithm.tex b/docs/backpack/algorithm.tex index 106dcc2..79ddccf 100644 --- a/docs/backpack/algorithm.tex +++ b/docs/backpack/algorithm.tex @@ -1283,4 +1283,151 @@ for \verb|T|, because the export of \verb|foo| is an \I{AvailTC} which does mention \verb|T|. \end{aside} +\section{Cabal} + +Design goals: + +\begin{itemize} + \item Backpack files are user-written. (In an earlier design, we had + the idea that Cabal would generate Backpack files; however, we've + since made Backpack files more user-friendly and reasonable to + write by hand.) + + \item Backpack files are optional. A package can add a Backpack file + to replace some (but not all) of the fields in a Cabal description. + + \item Backpack files can be compiled without GHC, if it is self-contained + with respect to all the indefinite packages it includes. To include + an indefinite package which is not locally defined but installed + to the package database, you must use Cabal. + + \item Backpack packages are \emph{unversioned}; you never see a version + number in a Backpack package. +\end{itemize} + +\subsection{Versioning} + +In this section, we discuss how Cabal's version numbers factor into +Backpack, namely how we specify \I{PkgKey}s. + +\paragraph{History} +Prior to GHC 7.10, GHC has allowed an arbitrary combination of libraries +to be linked together, assuming that the package IDs (e.g. +\verb|foo-0.1|) were all unique. Cabal enforces a stronger restriction, +which is that there exists some unique mapping from package name to +package version which is consistent with all transitive dependencies. + +\paragraph{Design goals} +Here are some design goals for versioning: + +\begin{enumerate} + \item GHC only tests for equality on versioning; Cabal is + responsible for determining the version of a package. For example, + pre-7.10 the linker symbols were prefixed using a package name and + version, but GHC simply represented this internally as an opaque + string. As another example, package qualified imports only allow + qualification by package name, and not by version. + + \item Cabal only tests for equality on package keys; GHC is + responsible for calculating the package key of a package. (This is + because GHC must be able to maintain a mapping between the unhashed + and hashed versions of a key, and the hashing process must be + deterministic.) If Cabal needs to generate a new package key, it + must do so through GHC. + + \item Our design should, in principle, support mutual recursion + between packages, even if the implementation does not (presently). + + \item GHC should not lose functionality, i.e. it should still be + possible to link together the same package with different versions; + however, Cabal may arrange for this to not occur by default unless a + user explicitly asks for it. +\end{enumerate} + +These goals imply a few things: + +\begin{enumerate} + \item Backpack files should not contain any version numbers, + and should be agnostic to versioning. + + \item Package keys must record versioning information, otherwise + we can't link together two different versions of the same package. +\end{enumerate} + +\paragraph{Package keys} + +Earlier, we specified \I{PkgKey} as a package name $p$ and then a list +of hole instantiations. To allow linking together multiple versions of +the same package, we must record versioning information into the +\I{PkgKey}. To do this, we include in the \I{PkgKey} a \I{VersionHash}. +Cabal is responsible for defining \I{VersionHash}, but we give two possible +definitions in Figure~\ref{fig:version}. + +\begin{figure}[htpb] +$$ +\begin{array}{rcll} +p && \mbox{Package name} \\ +v && \mbox{Version number} \\[1em] +\I{VersionHash} & ::= & p \verb|-| v\; \verb|{| \, p_0 \; \verb|->| \; \I{VersionHash}_0 \verb|,|\, \ldots\, p_n \; \verb|->| \; \I{VersionHash}_n \, \verb|}| & \mbox{Full version hash} \\ +\I{VersionHash'} & ::= & p \; \verb|{| \, p_0\verb|-|v_0 \verb|,|\, \ldots\, p_n\verb|-|v_n \, \verb|}| & \mbox{Simplified version hash} \\ +\I{PkgKey} & ::= & \I{VersionHash} \verb|(| \, m \; \verb|->| \; \I{Module} \verb|,|\, \ldots\, \verb|)| \\ +\end{array} +$$ +\caption{Version hash} \label{fig:version} +\end{figure} + +The difference between a full version hash and a simplified version hash +is what linking restrictions they impose on programs: the full version +hash supports linking arbitrary versions of packages with arbitrary +other versions, whereas the simplified hash has a Cabal-style requirement +that there be some globally consistent mapping from package name to version. + +The full version hash has some subtleties: + +\begin{itemize} + \item Each sub-\I{VersionHash} recorded in a \I{VersionHash} is + identified by a package name, which may not necessarily equal the + package name in the \I{VersionHash}. This permits us to calculate + a \I{VersionHash} for a package like: +\begin{verbatim} + package p where + include network (Network) + include network-old (Network as Network.Old) + ... +\end{verbatim} + if we want \verb|network| to refer to \verb|network-2.0| and + \verb|network-old| to refer to \verb|network-1.0|. Without + identifying each subdependency by package name, we wouldn't know + what \verb|network-old| would refer to. + + \item If a package is locally specified in a Backpack + file, it does not occur in the \I{VersionHash}. This is because + we always refer to the same package; there are no different versions! + + \item You might wonder why we need a \I{VersionHash} as well as a \I{PkgKey}; + why not just specify \I{PkgKey} as $p-v \; \verb|{| \, p \; \verb|->| \; \I{PkgKey} \verb|,|\, \ldots\, \verb|}| \verb|(| \, m \; \verb|->| \; \I{Module} \verb|,|\, \ldots\, \verb|)|$? However, there is ``too much'' information in the \I{PkgKey}, causing the scheme to not work with mutual recursion: + +\begin{verbatim} + package p where + module M + include q +\end{verbatim} + + To specify the package key of \verb|p|, we need the package key of \verb|q|; to + specify the package key of \verb|q|, we need the module identifier of \verb|M| + which contains the package key of \verb|p|: circularity! (The simplified + version hash does not have this problem as it is not recursive.) +\end{itemize} + +\paragraph{Cabal to GHC} + +Prior to GHC-7.10, Cabal passed versioning information to GHC using the +\verb|-package-name| flag. In GHC 7.10, this flag was renamed to +\verb|-this-package-key|. We propose that this flag be renamed once +again to \verb|-this-version-hash|, to which Cabal passes a hash (or string) +describing the versioning of the package which is then incorporated +into the package key. Cabal no longer needs to calculate package keys. +In the absence of Backpack, there will be no semantic difference if we +switch to full version hashes. + \end{document} % chktex 16 From git at git.haskell.org Fri Jun 12 19:13:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 12 Jun 2015 19:13:40 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: docs: More 7.10.2 release notes (b43df7c) Message-ID: <20150612191340.20A3E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/b43df7ca1847815ceb969ad989cd4d0c8ca6525a/ghc >--------------------------------------------------------------- commit b43df7ca1847815ceb969ad989cd4d0c8ca6525a Author: Austin Seipp Date: Fri Jun 12 14:13:59 2015 -0500 docs: More 7.10.2 release notes Signed-off-by: Austin Seipp >--------------------------------------------------------------- b43df7ca1847815ceb969ad989cd4d0c8ca6525a docs/users_guide/7.10.2-notes.xml | 7 +++++++ 1 file changed, 7 insertions(+) diff --git a/docs/users_guide/7.10.2-notes.xml b/docs/users_guide/7.10.2-notes.xml index daaa67e..e53f5de 100644 --- a/docs/users_guide/7.10.2-notes.xml +++ b/docs/users_guide/7.10.2-notes.xml @@ -117,6 +117,13 @@ times and memory usage (issues #10397, #10370). + + + A bug which could cause GHCi to crash if exceptions were + raised in the :cmd command has been + fixed. + + From git at git.haskell.org Fri Jun 12 19:14:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 12 Jun 2015 19:14:41 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: docs: More 7.10.2 release notes (65344f6) Message-ID: <20150612191441.8E2913A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/65344f66b0827cedbf4cdac50aa136ec2dd085c3/ghc >--------------------------------------------------------------- commit 65344f66b0827cedbf4cdac50aa136ec2dd085c3 Author: Austin Seipp Date: Fri Jun 12 14:15:04 2015 -0500 docs: More 7.10.2 release notes Signed-off-by: Austin Seipp >--------------------------------------------------------------- 65344f66b0827cedbf4cdac50aa136ec2dd085c3 docs/users_guide/7.10.2-notes.xml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/docs/users_guide/7.10.2-notes.xml b/docs/users_guide/7.10.2-notes.xml index e53f5de..bf6bec2 100644 --- a/docs/users_guide/7.10.2-notes.xml +++ b/docs/users_guide/7.10.2-notes.xml @@ -114,7 +114,7 @@ Several performance-related issues inside GHC have been fixed. As a result, you should see improved compilation - times and memory usage (issues #10397, #10370). + times and memory usage (issues #10397, #10370, #10422). From git at git.haskell.org Fri Jun 12 19:15:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 12 Jun 2015 19:15:55 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: docs: More 7.10.2 release notes (41ed737) Message-ID: <20150612191555.7CDCD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/41ed7378e08f7a6b0ae5f15f18394bbfe6a82521/ghc >--------------------------------------------------------------- commit 41ed7378e08f7a6b0ae5f15f18394bbfe6a82521 Author: Austin Seipp Date: Fri Jun 12 14:16:18 2015 -0500 docs: More 7.10.2 release notes Signed-off-by: Austin Seipp >--------------------------------------------------------------- 41ed7378e08f7a6b0ae5f15f18394bbfe6a82521 docs/users_guide/7.10.2-notes.xml | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/docs/users_guide/7.10.2-notes.xml b/docs/users_guide/7.10.2-notes.xml index bf6bec2..2389668 100644 --- a/docs/users_guide/7.10.2-notes.xml +++ b/docs/users_guide/7.10.2-notes.xml @@ -4,10 +4,10 @@ The 7.10.2 release is a bugfix release, with over 70+ bug fixes - from users and contributors relative to 7.10.1. The major bugfixes - are listed below. For the full list with more detail, see the - GHC - 7.10.2 milestone on our bug tracker. + relative to 7.10.1. The major fixes are listed below. For the full + list with more detail, see the GHC 7.10.2 + milestone on our bug tracker. From git at git.haskell.org Fri Jun 12 19:20:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 12 Jun 2015 19:20:09 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: docs: More 7.10.2 release notes (636fc2e) Message-ID: <20150612192009.EC94B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/636fc2eb4992e0c1b19a8a42444913b9afee4b5a/ghc >--------------------------------------------------------------- commit 636fc2eb4992e0c1b19a8a42444913b9afee4b5a Author: Austin Seipp Date: Fri Jun 12 14:18:40 2015 -0500 docs: More 7.10.2 release notes Signed-off-by: Austin Seipp >--------------------------------------------------------------- 636fc2eb4992e0c1b19a8a42444913b9afee4b5a docs/users_guide/7.10.2-notes.xml | 7 +++++++ 1 file changed, 7 insertions(+) diff --git a/docs/users_guide/7.10.2-notes.xml b/docs/users_guide/7.10.2-notes.xml index 2389668..65d9f89 100644 --- a/docs/users_guide/7.10.2-notes.xml +++ b/docs/users_guide/7.10.2-notes.xml @@ -124,6 +124,13 @@ fixed. + + + A bug in the event manager which could cause 'multi-shot' + event registrations to only fire once has been fixed + (issue #10317). + + From git at git.haskell.org Fri Jun 12 19:30:27 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 12 Jun 2015 19:30:27 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: docs: More 7.10.2 release notes (f4f6f18) Message-ID: <20150612193027.178FC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/f4f6f1834a63a0f61b0fee659ba1ee58ca6e4da0/ghc >--------------------------------------------------------------- commit f4f6f1834a63a0f61b0fee659ba1ee58ca6e4da0 Author: Austin Seipp Date: Fri Jun 12 14:30:46 2015 -0500 docs: More 7.10.2 release notes Signed-off-by: Austin Seipp >--------------------------------------------------------------- f4f6f1834a63a0f61b0fee659ba1ee58ca6e4da0 docs/users_guide/7.10.2-notes.xml | 19 +++++++++++++++++++ 1 file changed, 19 insertions(+) diff --git a/docs/users_guide/7.10.2-notes.xml b/docs/users_guide/7.10.2-notes.xml index 65d9f89..661d3eb 100644 --- a/docs/users_guide/7.10.2-notes.xml +++ b/docs/users_guide/7.10.2-notes.xml @@ -16,6 +16,13 @@ + A bug in the typechecker which could result in strange, + inconsistent reduction of type families has been fixed + (issue #10488). + + + + A bug which caused GHC to generate bad DWARF unwinding information has been fixed (issue #10236). @@ -131,6 +138,18 @@ (issue #10317). + + + A bug which could cause compiled programs to loop forever + when glibc's iconv implementation (gconv) wasn't available + has been fixed, so these programs will now terminate with + an error. As a result of this change, however, GHC + compiled programs now also specifically recognize ASCII + encodings, and can bypass iconv in these cases. This + allows statically compiled programs to exist inside an + initramfs, for example. (issues #10298, #7695). + + From git at git.haskell.org Fri Jun 12 23:01:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 12 Jun 2015 23:01:31 +0000 (UTC) Subject: [commit: ghc] master: Testsuite: diff non-whitespace normalised output (#10152) (5ddd904) Message-ID: <20150612230131.65DC33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5ddd90415f307cac72d75d86da58e552b168ee30/ghc >--------------------------------------------------------------- commit 5ddd90415f307cac72d75d86da58e552b168ee30 Author: Thomas Miedema Date: Fri Jun 12 16:29:18 2015 +0200 Testsuite: diff non-whitespace normalised output (#10152) On a test failure, we show a diff between the expected and the actual output. The method of how we do this has changed a couple of times: * In 2007: 9951189ccf90b709436fa55ee49eeef031f79f4e "On failure, diff the normalised test outputs" * In 2011: 3019b1e409c129ef7af63e6a7408fb36ec44444b "When the output files differ, present the diffs between the *actual* output, not the normalised output. The latter may have newlines removed, making the diff unreadable." * In 2015 (now): do something in between. - Do apply the normalisers again, to make the diff smaller (only showing the actual problem). - But don't apply normalise_whitespace, as it indeed makes the diff unreadable. Differential Revision: https://phabricator.haskell.org/D984 >--------------------------------------------------------------- 5ddd90415f307cac72d75d86da58e552b168ee30 testsuite/driver/testlib.py | 65 +++++++++++++++++++++++++-------------------- 1 file changed, 36 insertions(+), 29 deletions(-) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index 462c854..b277a35 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -1053,9 +1053,9 @@ def do_compile( name, way, should_fail, top_mod, extra_mods, extra_hc_opts, over if not compare_outputs(way, 'stderr', join_normalisers(getTestOpts().extra_errmsg_normaliser, - normalise_errmsg, - normalise_whitespace), - expected_stderr_file, actual_stderr_file): + normalise_errmsg), + expected_stderr_file, actual_stderr_file, + whitespace_normaliser=normalise_whitespace): return failBecause('stderr mismatch') # no problems found, this test passed @@ -1634,52 +1634,44 @@ def check_prof_ok(name, way): if not os.path.exists(expected_prof_file): return True else: - return compare_outputs(way, 'prof', - join_normalisers(normalise_whitespace,normalise_prof), \ - expected_prof_file, prof_file) + return compare_outputs(way, 'prof', normalise_prof, + expected_prof_file, prof_file, + whitespace_normaliser=normalise_whitespace) # Compare expected output to actual output, and optionally accept the # new output. Returns true if output matched or was accepted, false -# otherwise. -def compare_outputs(way, kind, normaliser, expected_file, actual_file): +# otherwise. See Note [Output comparison] for the meaning of the +# normaliser and whitespace_normaliser parameters. +def compare_outputs(way, kind, normaliser, expected_file, actual_file, + whitespace_normaliser=lambda x:x): + if os.path.exists(expected_file): - expected_raw = read_no_crs(expected_file) - # print "norm:", normaliser(expected_raw) - expected_str = normaliser(expected_raw) - expected_file_for_diff = expected_file + expected_str = normaliser(read_no_crs(expected_file)) + expected_normalised_file = expected_file + ".normalised" else: expected_str = '' - expected_file_for_diff = '/dev/null' + expected_normalised_file = '/dev/null' actual_raw = read_no_crs(actual_file) actual_str = normaliser(actual_raw) - if expected_str == actual_str: + # See Note [Output comparison]. + if whitespace_normaliser(expected_str) == whitespace_normaliser(actual_str): return 1 else: if config.verbose >= 1 and _expect_pass(way): print('Actual ' + kind + ' output differs from expected:') - if expected_file_for_diff == '/dev/null': - expected_normalised_file = '/dev/null' - else: - expected_normalised_file = expected_file + ".normalised" + if expected_normalised_file != '/dev/null': write_file(expected_normalised_file, expected_str) actual_normalised_file = actual_file + ".normalised" write_file(actual_normalised_file, actual_str) - # Ignore whitespace when diffing. We should only get to this - # point if there are non-whitespace differences - # - # Note we are diffing the *actual* output, not the normalised - # output. The normalised output may have whitespace squashed - # (including newlines) so the diff would be hard to read. - # This does mean that the diff might contain changes that - # would be normalised away. if config.verbose >= 1 and _expect_pass(way): - r = os.system( 'diff -uw ' + expected_file_for_diff + \ - ' ' + actual_file ) + # See Note [Output comparison]. + r = os.system('diff -uw ' + expected_normalised_file + + ' ' + actual_normalised_file) # If for some reason there were no non-whitespace differences, # then do a full diff @@ -1698,11 +1690,26 @@ def compare_outputs(way, kind, normaliser, expected_file, actual_file): else: return 0 +# Note [Output comparison] +# +# We do two types of output comparison: +# +# 1. To decide whether a test has failed. We apply a `normaliser` and an +# optional `whitespace_normaliser` to the expected and the actual +# output, before comparing the two. +# +# 2. To show as a diff to the user when the test indeed failed. We apply +# the same `normaliser` function to the outputs, to make the diff as +# small as possible (only showing the actual problem). But we don't +# apply the `whitespace_normaliser` here, because it might completely +# squash all whitespace, making the diff unreadable. Instead we rely +# on the `diff` program to ignore whitespace changes as much as +# possible (#10152). def normalise_whitespace( str ): # Merge contiguous whitespace characters into a single space. str = re.sub('[ \t\n]+', ' ', str) - return str + return str.strip() def normalise_errmsg( str ): # remove " error:" and lower-case " Warning:" to make patch for From git at git.haskell.org Fri Jun 12 23:01:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 12 Jun 2015 23:01:34 +0000 (UTC) Subject: [commit: ghc] master: Testsuite: add function compile_timeout_multiplier (#10345) (6e542a6) Message-ID: <20150612230134.1F75E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6e542a62e070b113f95908315c81d01c300d8803/ghc >--------------------------------------------------------------- commit 6e542a62e070b113f95908315c81d01c300d8803 Author: Thomas Miedema Date: Fri Jun 12 13:52:02 2015 +0200 Testsuite: add function compile_timeout_multiplier (#10345) And rename timeout_multiplier to run_timeout_multiplier. timeout_multiplier was added in commit a00389794b839971c7d52ead9e8570bfaa25ac55. The name suggested that it would affect any test, but it actually only affected tests that had a run component, and only that run component (as needed by test T367). Differential Revision: https://phabricator.haskell.org/D982 >--------------------------------------------------------------- 6e542a62e070b113f95908315c81d01c300d8803 testsuite/driver/testglobals.py | 3 ++- testsuite/driver/testlib.py | 22 +++++++++++++++------- testsuite/tests/concurrent/should_run/all.T | 8 ++++++-- testsuite/tests/parser/should_fail/all.T | 3 ++- 4 files changed, 25 insertions(+), 11 deletions(-) diff --git a/testsuite/driver/testglobals.py b/testsuite/driver/testglobals.py index 4b6acfd..76d26a3 100644 --- a/testsuite/driver/testglobals.py +++ b/testsuite/driver/testglobals.py @@ -278,7 +278,8 @@ class TestOptions: self.combined_output = False # How should the timeout be adjusted on this test? - self.timeout_multiplier = 1.0 + self.compile_timeout_multiplier = 1.0 + self.run_timeout_multiplier = 1.0 # The default set of options global default_testopts diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index b277a35..3da01ce 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -249,11 +249,17 @@ def signal_exit_code( val ): # ----- -def timeout_multiplier( val ): - return lambda name, opts, v=val: _timeout_multiplier(name, opts, v) +def compile_timeout_multiplier( val ): + return lambda name, opts, v=val: _compile_timeout_multiplier(name, opts, v) -def _timeout_multiplier( name, opts, v ): - opts.timeout_multiplier = v +def _compile_timeout_multiplier( name, opts, v ): + opts.compile_timeout_multiplier = v + +def run_timeout_multiplier( val ): + return lambda name, opts, v=val: _run_timeout_multiplier(name, opts, v) + +def _run_timeout_multiplier( name, opts, v ): + opts.run_timeout_multiplier = v # ----- @@ -1256,7 +1262,7 @@ def simple_build( name, way, extra_hc_opts, should_fail, top_mod, link, addsuf, '> {errname} 2>&1' ).format(**locals()) - result = runCmdFor(name, cmd) + result = runCmdFor(name, cmd, timeout_multiplier=opts.compile_timeout_multiplier) if result != 0 and not should_fail: actual_stderr = qualify(name, 'comp.stderr') @@ -1338,7 +1344,7 @@ def simple_run( name, way, prog, args ): cmd = 'cd ' + opts.testdir + ' && ' + cmd # run the command - result = runCmdFor(name, cmd, timeout_multiplier=opts.timeout_multiplier) + result = runCmdFor(name, cmd, timeout_multiplier=opts.run_timeout_multiplier) exit_code = result >> 8 signal = result & 0xff @@ -1384,6 +1390,8 @@ def rts_flags(way): # Run a program in the interpreter and check its output def interpreter_run( name, way, extra_hc_opts, compile_only, top_mod ): + opts = getTestOpts() + outname = add_suffix(name, 'interp.stdout') errname = add_suffix(name, 'interp.stderr') rm_no_fail(outname) @@ -1449,7 +1457,7 @@ def interpreter_run( name, way, extra_hc_opts, compile_only, top_mod ): cmd = 'cd ' + getTestOpts().testdir + " && " + cmd - result = runCmdFor(name, cmd, timeout_multiplier=getTestOpts().timeout_multiplier) + result = runCmdFor(name, cmd, timeout_multiplier=opts.run_timeout_multiplier) exit_code = result >> 8 signal = result & 0xff diff --git a/testsuite/tests/concurrent/should_run/all.T b/testsuite/tests/concurrent/should_run/all.T index 5288ff9..2d3ac2e 100644 --- a/testsuite/tests/concurrent/should_run/all.T +++ b/testsuite/tests/concurrent/should_run/all.T @@ -22,8 +22,12 @@ test('conc072', only_ways(['threaded2']), compile_and_run, ['']) test('conc073', normal, compile_and_run, ['']) # vector code must get inlined to become non-allocating -test('T367', [reqlib('vector'), omit_ways(['ghci']), timeout_multiplier(0.001)], compile_and_run, ['-O2 -fno-omit-yields']) -test('T367_letnoescape', [timeout_multiplier(0.02), expect_broken_for(7297,['optllvm'])], compile_and_run, ['-fno-omit-yields']) +test('T367', + [reqlib('vector'), omit_ways(['ghci']), run_timeout_multiplier(0.001)], + compile_and_run, ['-O2 -fno-omit-yields']) +test('T367_letnoescape', + [run_timeout_multiplier(0.02), expect_broken_for(7297,['optllvm'])], + compile_and_run, ['-fno-omit-yields']) test('T1980', normal, compile_and_run, ['']) test('T2910', normal, compile_and_run, ['']) diff --git a/testsuite/tests/parser/should_fail/all.T b/testsuite/tests/parser/should_fail/all.T index cc59a14..affea92 100644 --- a/testsuite/tests/parser/should_fail/all.T +++ b/testsuite/tests/parser/should_fail/all.T @@ -84,6 +84,7 @@ test('T984', normal, compile_fail, ['']) test('T7848', normal, compile_fail, ['-dppr-user-length=100']) test('ExportCommaComma', normal, compile_fail, ['']) test('T8430', literate, compile_fail, ['']) -test('T8431', [timeout_multiplier(0.05)], compile_fail, ['-XAlternativeLayoutRule']) +test('T8431', compile_timeout_multiplier(0.05), + compile_fail, ['-XAlternativeLayoutRule']) test('T8506', normal, compile_fail, ['']) test('T9225', normal, compile_fail, ['']) From git at git.haskell.org Sun Jun 14 15:42:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 14 Jun 2015 15:42:59 +0000 (UTC) Subject: [commit: ghc] master: UNREG: fix pprHexVal to emit zeros (#10518) (a508455) Message-ID: <20150614154259.4FC1D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a5084557b0b30faf3f89386ee6ee5a308dae51b1/ghc >--------------------------------------------------------------- commit a5084557b0b30faf3f89386ee6ee5a308dae51b1 Author: Sergei Trofimovich Date: Sun Jun 14 16:42:03 2015 +0100 UNREG: fix pprHexVal to emit zeros (#10518) jakzale on #ghc reported a build failure when ported GHC on a new target. The code 'pprHexVal (2^32) W32' emits '0xU' which is invalid C. I've introduced bug in 43f1b2ecd1960fa7377cf55a2b97c66059a701ef when added literal truncation. That truncation is a new source of zeros. Signed-off-by: Sergei Trofimovich Test Plan: added test and tested on UNREG ghc Reviewers: austin Reviewed By: austin Subscribers: thomie, bgamari Differential Revision: https://phabricator.haskell.org/D987 GHC Trac Issues: #10518 >--------------------------------------------------------------- a5084557b0b30faf3f89386ee6ee5a308dae51b1 compiler/cmm/PprC.hs | 5 +++-- testsuite/tests/codeGen/should_compile/T10518.cmm | 5 +++++ testsuite/tests/codeGen/should_compile/all.T | 1 + 3 files changed, 9 insertions(+), 2 deletions(-) diff --git a/compiler/cmm/PprC.hs b/compiler/cmm/PprC.hs index 92c8182..538dfcd 100644 --- a/compiler/cmm/PprC.hs +++ b/compiler/cmm/PprC.hs @@ -1214,7 +1214,6 @@ commafy xs = hsep $ punctuate comma xs -- Print in C hex format: 0x13fa pprHexVal :: Integer -> Width -> SDoc -pprHexVal 0 _ = ptext (sLit "0x0") pprHexVal w rep | w < 0 = parens (char '-' <> ptext (sLit "0x") <> intToDoc (-w) <> repsuffix rep) @@ -1234,7 +1233,9 @@ pprHexVal w rep repsuffix _ = char 'U' intToDoc :: Integer -> SDoc - intToDoc i = go (truncInt i) + intToDoc i = case truncInt i of + 0 -> char '0' + v -> go v -- We need to truncate value as Cmm backend does not drop -- redundant bits to ease handling of negative values. diff --git a/testsuite/tests/codeGen/should_compile/T10518.cmm b/testsuite/tests/codeGen/should_compile/T10518.cmm new file mode 100644 index 0000000..966cd4a --- /dev/null +++ b/testsuite/tests/codeGen/should_compile/T10518.cmm @@ -0,0 +1,5 @@ +foo() { + bits64 a; + a = 0x10000000000000000; // overflows 64 bits + return (a); +} diff --git a/testsuite/tests/codeGen/should_compile/all.T b/testsuite/tests/codeGen/should_compile/all.T index e06cead..c78f9ac 100644 --- a/testsuite/tests/codeGen/should_compile/all.T +++ b/testsuite/tests/codeGen/should_compile/all.T @@ -30,3 +30,4 @@ test('debug', extra_clean(['debug.cmm']), run_command, ['$MAKE -s --no-print-directory debug']) test('T9964', normal, compile, ['-O']) +test('T10518', [cmm_src], compile, ['']) From git at git.haskell.org Mon Jun 15 01:22:08 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Jun 2015 01:22:08 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: relnotes: Remove duplicate 'known bugs' entry (a9c540e) Message-ID: <20150615012208.706133A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/a9c540eb173720584c606d75430b3f55e9fd157d/ghc >--------------------------------------------------------------- commit a9c540eb173720584c606d75430b3f55e9fd157d Author: Austin Seipp Date: Sun Jun 14 20:22:30 2015 -0500 relnotes: Remove duplicate 'known bugs' entry Signed-off-by: Austin Seipp >--------------------------------------------------------------- a9c540eb173720584c606d75430b3f55e9fd157d docs/users_guide/7.10.2-notes.xml | 7 ------- 1 file changed, 7 deletions(-) diff --git a/docs/users_guide/7.10.2-notes.xml b/docs/users_guide/7.10.2-notes.xml index 661d3eb..88a9c2f 100644 --- a/docs/users_guide/7.10.2-notes.xml +++ b/docs/users_guide/7.10.2-notes.xml @@ -241,13 +241,6 @@ - GHC's LLVM backend is currently incompatible with LLVM - 3.4 (issue #9929). - - - - GHCi fails to appropriately load .dyn_o files (issue #8736). From git at git.haskell.org Mon Jun 15 01:33:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Jun 2015 01:33:07 +0000 (UTC) Subject: [commit: ghc] master: add type annotations to SrcLoc functions (1cf7fc0) Message-ID: <20150615013308.001233A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1cf7fc0f182602b18ac04427b248f0374d2e626e/ghc >--------------------------------------------------------------- commit 1cf7fc0f182602b18ac04427b248f0374d2e626e Author: ?mer Sinan A?acan Date: Sun Jun 14 20:30:29 2015 -0500 add type annotations to SrcLoc functions Because sometimes types make more sense than docs. Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D983 >--------------------------------------------------------------- 1cf7fc0f182602b18ac04427b248f0374d2e626e compiler/parser/Parser.y | 3 +++ 1 file changed, 3 insertions(+) diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y index b88a3b1..682b342 100644 --- a/compiler/parser/Parser.y +++ b/compiler/parser/Parser.y @@ -3207,12 +3207,15 @@ sL span a = span `seq` a `seq` L span a -- replaced last 3 CPP macros in this file {-# INLINE sL0 #-} +sL0 :: a -> Located a sL0 = L noSrcSpan -- #define L0 L noSrcSpan {-# INLINE sL1 #-} +sL1 :: Located a -> b -> Located b sL1 x = sL (getLoc x) -- #define sL1 sL (getLoc $1) {-# INLINE sLL #-} +sLL :: Located a -> Located b -> c -> Located c sLL x y = sL (comb2 x y) -- #define LL sL (comb2 $1 $>) {- Note [Adding location info] From git at git.haskell.org Mon Jun 15 01:33:10 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Jun 2015 01:33:10 +0000 (UTC) Subject: [commit: ghc] master: Increase constraint tuple limit to 62 (Trac #10451) (dd3080f) Message-ID: <20150615013310.B6B763A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/dd3080fe0263082f65bf2570f49189c277b12e28/ghc >--------------------------------------------------------------- commit dd3080fe0263082f65bf2570f49189c277b12e28 Author: Nick Terrell Date: Sun Jun 14 20:32:22 2015 -0500 Increase constraint tuple limit to 62 (Trac #10451) * Increase max constraint tuple size to 62 * Modify test case to reflect change Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D986 GHC Trac Issues: #10451 >--------------------------------------------------------------- dd3080fe0263082f65bf2570f49189c277b12e28 compiler/main/Constants.hs | 2 +- libraries/ghc-prim/GHC/Classes.hs | 293 +++++++++++++++++++++++++++++++- testsuite/tests/polykinds/T10451.hs | 30 +++- testsuite/tests/polykinds/T10451.stderr | 8 +- 4 files changed, 328 insertions(+), 5 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc dd3080fe0263082f65bf2570f49189c277b12e28 From git at git.haskell.org Mon Jun 15 07:53:06 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Jun 2015 07:53:06 +0000 (UTC) Subject: [commit: ghc] branch 'wip/api-annots-7.10-3' deleted Message-ID: <20150615075306.66A493A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/api-annots-7.10-3 From git at git.haskell.org Mon Jun 15 07:54:22 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Jun 2015 07:54:22 +0000 (UTC) Subject: [commit: ghc] branch 'wip/api-annot-tweaks-7.10' deleted Message-ID: <20150615075422.BB5A13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/api-annot-tweaks-7.10 From git at git.haskell.org Mon Jun 15 09:02:50 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Jun 2015 09:02:50 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #10348 (a607011) Message-ID: <20150615090250.B86F63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a607011dbf522c97c9b6428ffa3203c56ab8dde6/ghc >--------------------------------------------------------------- commit a607011dbf522c97c9b6428ffa3203c56ab8dde6 Author: Gabor Greif Date: Mon Jun 15 11:00:45 2015 +0200 Test Trac #10348 >--------------------------------------------------------------- a607011dbf522c97c9b6428ffa3203c56ab8dde6 testsuite/tests/typecheck/should_compile/T10348.hs | 20 ++++++++++++++++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 2 files changed, 21 insertions(+) diff --git a/testsuite/tests/typecheck/should_compile/T10348.hs b/testsuite/tests/typecheck/should_compile/T10348.hs new file mode 100644 index 0000000..e8ec37c --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T10348.hs @@ -0,0 +1,20 @@ +{-# LANGUAGE AutoDeriveTypeable, GADTs, DataKinds, KindSignatures, StandaloneDeriving #-} + +module T10348 where + +import GHC.TypeLits +import Data.Typeable + +data Foo (n :: Nat) where + Hey :: KnownNat n => Foo n + +deriving instance Show (Foo n) + +data T t where + T :: (Show t, Typeable t) => t -> T t + +deriving instance Show (T n) + +hey :: (Typeable n, KnownNat n) => T (Foo n) +-- SHOULD BE: hey :: KnownNat n => T (Foo n) +hey = T Hey diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index bd87afb..8f42129 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -458,3 +458,4 @@ test('T8555', normal, compile, ['']) test('T8799', normal, compile, ['']) test('T10423', normal, compile, ['']) test('T10489', normal, compile, ['']) +test('T10348', normal, compile, ['']) From git at git.haskell.org Mon Jun 15 11:35:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Jun 2015 11:35:11 +0000 (UTC) Subject: [commit: ghc] master: Demonstrate that inferring Typeable for type literals works (77e5ec8) Message-ID: <20150615113511.6E58A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/77e5ec83617fce4cec530c744a435535bf06130b/ghc >--------------------------------------------------------------- commit 77e5ec83617fce4cec530c744a435535bf06130b Author: Gabor Greif Date: Mon Jun 15 13:30:24 2015 +0200 Demonstrate that inferring Typeable for type literals works So #10348 is only missing the variable case: Known{Nat,Symbol} lit => Typeable lit >--------------------------------------------------------------- 77e5ec83617fce4cec530c744a435535bf06130b compiler/typecheck/TcEvidence.hs | 2 +- compiler/typecheck/TcInstDcls.hs | 2 +- testsuite/tests/typecheck/should_compile/T10348.hs | 3 +++ 3 files changed, 5 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcEvidence.hs b/compiler/typecheck/TcEvidence.hs index 6e02694..e7ab902 100644 --- a/compiler/typecheck/TcEvidence.hs +++ b/compiler/typecheck/TcEvidence.hs @@ -733,7 +733,7 @@ data EvTerm -- | Instructions on how to make a 'Typeable' dictionary. data EvTypeable = EvTypeableTyCon TyCon [Kind] - -- ^ Dicitionary for concrete type constructors. + -- ^ Dictionary for concrete type constructors. | EvTypeableTyApp (EvTerm,Type) (EvTerm,Type) -- ^ Dictionary for type applications; this is used when we have diff --git a/compiler/typecheck/TcInstDcls.hs b/compiler/typecheck/TcInstDcls.hs index 9ce2d2f..c815d2d 100644 --- a/compiler/typecheck/TcInstDcls.hs +++ b/compiler/typecheck/TcInstDcls.hs @@ -433,7 +433,7 @@ tcInstDecls1 tycl_decls inst_decls deriv_decls 2 (pprInstanceHdr (iSpec i)) -- Report an error or a warning for a `Typeable` instances. - -- If we are workikng on an .hs-boot file, we just report a warning, + -- If we are working on an .hs-boot file, we just report a warning, -- and ignore the instance. We do this, to give users a chance to fix -- their code. typeable_err i = diff --git a/testsuite/tests/typecheck/should_compile/T10348.hs b/testsuite/tests/typecheck/should_compile/T10348.hs index e8ec37c..213079b 100644 --- a/testsuite/tests/typecheck/should_compile/T10348.hs +++ b/testsuite/tests/typecheck/should_compile/T10348.hs @@ -18,3 +18,6 @@ deriving instance Show (T n) hey :: (Typeable n, KnownNat n) => T (Foo n) -- SHOULD BE: hey :: KnownNat n => T (Foo n) hey = T Hey + +ho :: T (Foo 42) +ho = T Hey From git at git.haskell.org Mon Jun 15 12:26:22 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Jun 2015 12:26:22 +0000 (UTC) Subject: [commit: ghc] master: Remove derived CFunEqCans after solving givens (efa136f) Message-ID: <20150615122622.C644C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/efa136f7199f9313e91ba2c1724b307aff45c9eb/ghc >--------------------------------------------------------------- commit efa136f7199f9313e91ba2c1724b307aff45c9eb Author: Simon Peyton Jones Date: Mon Jun 15 13:23:16 2015 +0100 Remove derived CFunEqCans after solving givens See Note [The inert set after solving Givens] in TcSMonad. This fixes Trac #10507. >--------------------------------------------------------------- efa136f7199f9313e91ba2c1724b307aff45c9eb compiler/typecheck/TcInteract.hs | 5 +- compiler/typecheck/TcSMonad.hs | 55 ++++++++++++++-------- .../tests/indexed-types/should_compile/T10507.hs | 23 +++++++++ testsuite/tests/indexed-types/should_compile/all.T | 2 + 4 files changed, 64 insertions(+), 21 deletions(-) diff --git a/compiler/typecheck/TcInteract.hs b/compiler/typecheck/TcInteract.hs index 0000ff0..01b0ba1 100644 --- a/compiler/typecheck/TcInteract.hs +++ b/compiler/typecheck/TcInteract.hs @@ -126,13 +126,14 @@ must keep track of them separately. solveSimpleGivens :: CtLoc -> [EvVar] -> TcS Cts -- Solves the givens, adding them to the inert set --- Returns any insoluble givens, taking those ones out of the inert set +-- Returns any insoluble givens, which represent inaccessible code, +-- taking those ones out of the inert set solveSimpleGivens loc givens | null givens -- Shortcut for common case = return emptyCts | otherwise = do { go (map mk_given_ct givens) - ; takeInertInsolubles } + ; takeGivenInsolubles } where mk_given_ct ev_id = mkNonCanonical (CtGiven { ctev_evar = ev_id , ctev_pred = evVarPred ev_id diff --git a/compiler/typecheck/TcSMonad.hs b/compiler/typecheck/TcSMonad.hs index f067d74..2ea302e 100644 --- a/compiler/typecheck/TcSMonad.hs +++ b/compiler/typecheck/TcSMonad.hs @@ -9,7 +9,7 @@ module TcSMonad ( extendWorkListCts, appendWorkList, selectNextWorkItem, workListSize, workListWantedCount, - updWorkListTcS, updWorkListTcS_return, + updWorkListTcS, -- The TcS monad TcS, runTcS, runTcSWithEvBinds, @@ -41,7 +41,7 @@ module TcSMonad ( updInertTcS, updInertCans, updInertDicts, updInertIrreds, getNoGivenEqs, setInertCans, getInertEqs, getInertCans, getInertModel, getInertGivens, - emptyInert, getTcSInerts, setTcSInerts, takeInertInsolubles, + emptyInert, getTcSInerts, setTcSInerts, takeGivenInsolubles, getUnsolvedInerts, removeInertCts, addInertCan, addInertEq, insertFunEq, @@ -1474,15 +1474,43 @@ getInertCans = do { inerts <- getTcSInerts; return (inert_cans inerts) } setInertCans :: InertCans -> TcS () setInertCans ics = updInertTcS $ \ inerts -> inerts { inert_cans = ics } -takeInertInsolubles :: TcS Cts --- Take the insoluble constraints out of the inert set -takeInertInsolubles +takeGivenInsolubles :: TcS Cts +-- See Note [The inert set after solving Givens] +takeGivenInsolubles + = updRetInertCans $ \ cans -> + ( inert_insols cans + , cans { inert_insols = emptyBag + , inert_funeqs = filterFunEqs isGivenCt (inert_funeqs cans) } ) + +{- Note [The inert set after solving Givens] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +After solving the Givens we take two things out of the inert set + + a) The insolubles; we return these to report inaccessible code + We return these separately. We don't want to leave them in + the inert set, lest we onfuse them with insolubles arising from + solving wanteds + + b) Any Derived CFunEqCans. Derived CTyEqCans are in the + inert_model and do no harm. In contrast, Derived CFunEqCans + get mixed up with the Wanteds later and confuse the + post-solve-wanted unflattening (Trac #10507). + E.g. From [G] 1 <= m, [G] m <= n + We get [D] 1 <= n, and we must remove it! + Otherwise we unflatten it more then once, and assign + to its fmv more than once...disaster. + It's ok to remove them because they turned ont not to + yield an insoluble, and hence have now done their work. +-} + +updRetInertCans :: (InertCans -> (a, InertCans)) -> TcS a +-- Modify the inert set with the supplied function +updRetInertCans upd_fn = do { is_var <- getTcSInertsRef ; wrapTcS (do { inerts <- TcM.readTcRef is_var - ; let cans = inert_cans inerts - cans' = cans { inert_insols = emptyBag } + ; let (res, cans') = upd_fn (inert_cans inerts) ; TcM.writeTcRef is_var (inerts { inert_cans = cans' }) - ; return (inert_insols cans) }) } + ; return res }) } updInertCans :: (InertCans -> InertCans) -> TcS () -- Modify the inert set with the supplied function @@ -2282,17 +2310,6 @@ updWorkListTcS f ; let new_work = f wl_curr ; wrapTcS (TcM.writeTcRef wl_var new_work) } -updWorkListTcS_return :: (WorkList -> (a,WorkList)) -> TcS a --- Process the work list, returning a depleted work list, --- plus a value extracted from it (typically a work item removed from it) -updWorkListTcS_return f - = do { wl_var <- getTcSWorkListRef - ; wl_curr <- wrapTcS (TcM.readTcRef wl_var) - ; traceTcS "updWorkList" (ppr wl_curr) - ; let (res,new_work) = f wl_curr - ; wrapTcS (TcM.writeTcRef wl_var new_work) - ; return res } - emitWorkNC :: [CtEvidence] -> TcS () emitWorkNC evs | null evs diff --git a/testsuite/tests/indexed-types/should_compile/T10507.hs b/testsuite/tests/indexed-types/should_compile/T10507.hs new file mode 100644 index 0000000..14ef057 --- /dev/null +++ b/testsuite/tests/indexed-types/should_compile/T10507.hs @@ -0,0 +1,23 @@ +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE EmptyDataDecls #-} +{-# LANGUAGE ExplicitNamespaces #-} +{-# LANGUAGE GADTs #-} +{-# LANGUAGE KindSignatures #-} +{-# LANGUAGE TypeOperators #-} +{-# OPTIONS_GHC -fno-warn-redundant-constraints #-} +module T10507 where + +import Data.Type.Equality ( (:~:)(Refl) ) +import Prelude (Maybe(..), undefined) +import GHC.TypeLits ( Nat, type (<=)) + +data V (n::Nat) + +testEq :: (m <= n) => V m -> V n -> Maybe (m :~: n) +testEq = undefined + + +uext :: (1 <= m, m <= n) => V m -> V n -> V n +uext e w = + case testEq e w of + Just Refl -> e diff --git a/testsuite/tests/indexed-types/should_compile/all.T b/testsuite/tests/indexed-types/should_compile/all.T index aaf89e9..67be121 100644 --- a/testsuite/tests/indexed-types/should_compile/all.T +++ b/testsuite/tests/indexed-types/should_compile/all.T @@ -259,3 +259,5 @@ test('T10079', normal, compile, ['']) test('T10139', normal, compile, ['']) test('T10340', normal, compile, ['']) test('T10226', normal, compile, ['']) +test('T10507', normal, compile, ['']) + From git at git.haskell.org Mon Jun 15 13:23:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Jun 2015 13:23:29 +0000 (UTC) Subject: [commit: ghc] master: GHCi: fix scoping for record selectors (a3f6239) Message-ID: <20150615132329.A98443A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a3f6239d905ad4b8fb597f43bd4ef9947c83362f/ghc >--------------------------------------------------------------- commit a3f6239d905ad4b8fb597f43bd4ef9947c83362f Author: Simon Peyton Jones Date: Mon Jun 15 13:32:48 2015 +0100 GHCi: fix scoping for record selectors This fixes Trac #10520. See the "Ugh" note about record selectors in HscTypes.icExtendGblRdrEnv. >--------------------------------------------------------------- a3f6239d905ad4b8fb597f43bd4ef9947c83362f compiler/main/HscMain.hs | 19 +++++++------- compiler/main/HscTypes.hs | 41 ++++++++++++++++++++---------- testsuite/tests/ghci/scripts/T10520.script | 3 +++ testsuite/tests/ghci/scripts/T10520.stdout | 1 + testsuite/tests/ghci/scripts/all.T | 1 + 5 files changed, 42 insertions(+), 23 deletions(-) diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs index 2708396..94896b0 100644 --- a/compiler/main/HscMain.hs +++ b/compiler/main/HscMain.hs @@ -1513,16 +1513,15 @@ hscDeclsWithLocation hsc_env0 str source linenumber = , not (isDFunId id || isImplicitId id) ] -- We only need to keep around the external bindings -- (as decided by TidyPgm), since those are the only ones - -- that might be referenced elsewhere. - -- The DFunIds are in 'cls_insts' (see Note [ic_tythings] in HscTypes - -- Implicit Ids are implicit in tcs - - tythings = map AnId ext_ids ++ map ATyCon tcs ++ map (AConLike . PatSynCon) patsyns - - let icontext = hsc_IC hsc_env - ictxt = extendInteractiveContext icontext ext_ids tcs - cls_insts fam_insts defaults patsyns - return (tythings, ictxt) + -- that might later be looked up by name. But we can exclude + -- - DFunIds, which are in 'cls_insts' (see Note [ic_tythings] in HscTypes + -- - Implicit Ids, which are implicit in tcs + -- c.f. TcRnDriver.runTcInteractive, which reconstructs the TypeEnv + + new_tythings = map AnId ext_ids ++ map ATyCon tcs ++ map (AConLike . PatSynCon) patsyns + ictxt = hsc_IC hsc_env + new_ictxt = extendInteractiveContext ictxt new_tythings cls_insts fam_insts defaults + return (new_tythings, new_ictxt) hscImport :: HscEnv -> String -> IO (ImportDecl RdrName) hscImport hsc_env str = runInteractiveHsc hsc_env $ do diff --git a/compiler/main/HscTypes.hs b/compiler/main/HscTypes.hs index 67b0694..c2a5153 100644 --- a/compiler/main/HscTypes.hs +++ b/compiler/main/HscTypes.hs @@ -1402,12 +1402,11 @@ icPrintUnqual dflags InteractiveContext{ ic_rn_gbl_env = grenv } = -- to them (e.g. instances for classes or values of the type for TyCons), it's -- not clear whether removing them is even the appropriate behavior. extendInteractiveContext :: InteractiveContext - -> [Id] -> [TyCon] + -> [TyThing] -> [ClsInst] -> [FamInst] -> Maybe [Type] - -> [PatSyn] -> InteractiveContext -extendInteractiveContext ictxt ids tcs new_cls_insts new_fam_insts defaults new_patsyns +extendInteractiveContext ictxt new_tythings new_cls_insts new_fam_insts defaults = ictxt { ic_mod_index = ic_mod_index ictxt + 1 -- Always bump this; even instances should create -- a new mod_index (Trac #9426) @@ -1417,8 +1416,8 @@ extendInteractiveContext ictxt ids tcs new_cls_insts new_fam_insts defaults new_ , new_fam_insts ++ old_fam_insts ) , ic_default = defaults } where - new_tythings = map AnId ids ++ map ATyCon tcs ++ map (AConLike . PatSynCon) new_patsyns - old_tythings = filterOut (shadowed_by ids) (ic_tythings ictxt) + new_ids = [id | AnId id <- new_tythings] + old_tythings = filterOut (shadowed_by new_ids) (ic_tythings ictxt) -- Discard old instances that have been fully overrridden -- See Note [Override identical instances in GHCi] @@ -1427,14 +1426,15 @@ extendInteractiveContext ictxt ids tcs new_cls_insts new_fam_insts defaults new_ old_fam_insts = filterOut (\i -> any (identicalFamInstHead i) new_fam_insts) fam_insts extendInteractiveContextWithIds :: InteractiveContext -> [Id] -> InteractiveContext -extendInteractiveContextWithIds ictxt ids - | null ids = ictxt - | otherwise = ictxt { ic_mod_index = ic_mod_index ictxt + 1 - , ic_tythings = new_tythings ++ old_tythings - , ic_rn_gbl_env = ic_rn_gbl_env ictxt `icExtendGblRdrEnv` new_tythings } +-- Just a specialised version +extendInteractiveContextWithIds ictxt new_ids + | null new_ids = ictxt + | otherwise = ictxt { ic_mod_index = ic_mod_index ictxt + 1 + , ic_tythings = new_tythings ++ old_tythings + , ic_rn_gbl_env = ic_rn_gbl_env ictxt `icExtendGblRdrEnv` new_tythings } where - new_tythings = map AnId ids - old_tythings = filterOut (shadowed_by ids) (ic_tythings ictxt) + new_tythings = map AnId new_ids + old_tythings = filterOut (shadowed_by new_ids) (ic_tythings ictxt) shadowed_by :: [Id] -> TyThing -> Bool shadowed_by ids = shadowed @@ -1460,11 +1460,26 @@ icExtendGblRdrEnv env tythings -- the list shadow things at the back where -- One at a time, to ensure each shadows the previous ones - add thing env = foldl extendGlobalRdrEnv env1 (localGREsFromAvail avail) + add thing env + | is_sub_bndr thing + = env + | otherwise + = foldl extendGlobalRdrEnv env1 (localGREsFromAvail avail) where env1 = shadowNames env (availNames avail) avail = tyThingAvailInfo thing + -- Ugh! The new_tythings may include record selectors, since they + -- are not implicit-ids, and must appear in the TypeEnv. But they + -- will also be brought into scope by the corresponding (ATyCon + -- tc). And we want the latter, because that has the correct + -- parent (Trac #10520) + is_sub_bndr (AnId f) = case idDetails f of + RecSelId {} -> True + ClassOpId {} -> True + _ -> False + is_sub_bndr _ = False + substInteractiveContext :: InteractiveContext -> TvSubst -> InteractiveContext substInteractiveContext ictxt at InteractiveContext{ ic_tythings = tts } subst | isEmptyTvSubst subst = ictxt diff --git a/testsuite/tests/ghci/scripts/T10520.script b/testsuite/tests/ghci/scripts/T10520.script new file mode 100644 index 0000000..d72491c --- /dev/null +++ b/testsuite/tests/ghci/scripts/T10520.script @@ -0,0 +1,3 @@ +:set -XRecordWildCards +data Foo = Bar { baz :: Integer } deriving Show +Bar { baz = 42 } diff --git a/testsuite/tests/ghci/scripts/T10520.stdout b/testsuite/tests/ghci/scripts/T10520.stdout new file mode 100644 index 0000000..8fe2823 --- /dev/null +++ b/testsuite/tests/ghci/scripts/T10520.stdout @@ -0,0 +1 @@ +Bar {baz = 42} diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T index c2c75ec..4094a9e 100755 --- a/testsuite/tests/ghci/scripts/all.T +++ b/testsuite/tests/ghci/scripts/all.T @@ -222,3 +222,4 @@ test('T10322', normal, ghci_script, ['T10322.script']) test('T10466', normal, ghci_script, ['T10466.script']) test('T10501', normal, ghci_script, ['T10501.script']) test('T10508', normal, ghci_script, ['T10508.script']) +test('T10520', normal, ghci_script, ['T10520.script']) From git at git.haskell.org Mon Jun 15 13:23:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Jun 2015 13:23:32 +0000 (UTC) Subject: [commit: ghc] master: Spelling in comments (a6cbf41) Message-ID: <20150615132332.5C9B93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a6cbf414b15e31b75f08e830cffbd68ff397d174/ghc >--------------------------------------------------------------- commit a6cbf414b15e31b75f08e830cffbd68ff397d174 Author: Simon Peyton Jones Date: Mon Jun 15 13:33:36 2015 +0100 Spelling in comments >--------------------------------------------------------------- a6cbf414b15e31b75f08e830cffbd68ff397d174 compiler/rename/RnEnv.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/rename/RnEnv.hs b/compiler/rename/RnEnv.hs index 4ca3e5a..2bdf9b5 100644 --- a/compiler/rename/RnEnv.hs +++ b/compiler/rename/RnEnv.hs @@ -879,7 +879,7 @@ Note [Handling of deprecations] * We report deprecations at each *occurrence* of the deprecated thing (see Trac #5867) -* We do not report deprectations for locally-definded names. For a +* We do not report deprecations for locally-defined names. For a start, we may be exporting a deprecated thing. Also we may use a deprecated thing in the defn of another deprecated things. We may even use a deprecated thing in the defn of a non-deprecated thing, From git at git.haskell.org Mon Jun 15 13:23:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Jun 2015 13:23:35 +0000 (UTC) Subject: [commit: ghc] master: Improved peak_megabytes_allocated (855f56b) Message-ID: <20150615132335.18D6B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/855f56b6d3d09d2b9cf6de6ffcf09e3dabd05b36/ghc >--------------------------------------------------------------- commit 855f56b6d3d09d2b9cf6de6ffcf09e3dabd05b36 Author: Simon Peyton Jones Date: Mon Jun 15 14:23:32 2015 +0100 Improved peak_megabytes_allocated I have no idea why, but lower is good >--------------------------------------------------------------- 855f56b6d3d09d2b9cf6de6ffcf09e3dabd05b36 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 bc3e2f1..d3dc9a4 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -568,11 +568,12 @@ test('T9675', (wordsize(32), 11220552, 25) ]), compiler_stats_num_field('peak_megabytes_allocated', - [(wordsize(64), 53, 15), + [(wordsize(64), 44, 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 + # 2014-06-15 44 reduced for some reason (wordsize(32), 25, 15) ]), compiler_stats_num_field('bytes allocated', From git at git.haskell.org Mon Jun 15 14:22:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Jun 2015 14:22:17 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: UNREG: fix pprHexVal to emit zeros (#10518) (fa942e6) Message-ID: <20150615142217.5437F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/fa942e67727c7bb06199055d16d3ae16642181e7/ghc >--------------------------------------------------------------- commit fa942e67727c7bb06199055d16d3ae16642181e7 Author: Sergei Trofimovich Date: Sun Jun 14 16:42:03 2015 +0100 UNREG: fix pprHexVal to emit zeros (#10518) jakzale on #ghc reported a build failure when ported GHC on a new target. The code 'pprHexVal (2^32) W32' emits '0xU' which is invalid C. I've introduced bug in 43f1b2ecd1960fa7377cf55a2b97c66059a701ef when added literal truncation. That truncation is a new source of zeros. Signed-off-by: Sergei Trofimovich Test Plan: added test and tested on UNREG ghc Reviewers: austin Reviewed By: austin Subscribers: thomie, bgamari Differential Revision: https://phabricator.haskell.org/D987 GHC Trac Issues: #10518 (cherry picked from commit a5084557b0b30faf3f89386ee6ee5a308dae51b1) >--------------------------------------------------------------- fa942e67727c7bb06199055d16d3ae16642181e7 compiler/cmm/PprC.hs | 5 +++-- testsuite/tests/codeGen/should_compile/T10518.cmm | 5 +++++ testsuite/tests/codeGen/should_compile/all.T | 1 + 3 files changed, 9 insertions(+), 2 deletions(-) diff --git a/compiler/cmm/PprC.hs b/compiler/cmm/PprC.hs index a2c3abf..3c4c379 100644 --- a/compiler/cmm/PprC.hs +++ b/compiler/cmm/PprC.hs @@ -1219,7 +1219,6 @@ commafy xs = hsep $ punctuate comma xs -- Print in C hex format: 0x13fa pprHexVal :: Integer -> Width -> SDoc -pprHexVal 0 _ = ptext (sLit "0x0") pprHexVal w rep | w < 0 = parens (char '-' <> ptext (sLit "0x") <> intToDoc (-w) <> repsuffix rep) @@ -1239,7 +1238,9 @@ pprHexVal w rep repsuffix _ = char 'U' intToDoc :: Integer -> SDoc - intToDoc i = go (truncInt i) + intToDoc i = case truncInt i of + 0 -> char '0' + v -> go v -- We need to truncate value as Cmm backend does not drop -- redundant bits to ease handling of negative values. diff --git a/testsuite/tests/codeGen/should_compile/T10518.cmm b/testsuite/tests/codeGen/should_compile/T10518.cmm new file mode 100644 index 0000000..966cd4a --- /dev/null +++ b/testsuite/tests/codeGen/should_compile/T10518.cmm @@ -0,0 +1,5 @@ +foo() { + bits64 a; + a = 0x10000000000000000; // overflows 64 bits + return (a); +} diff --git a/testsuite/tests/codeGen/should_compile/all.T b/testsuite/tests/codeGen/should_compile/all.T index e06cead..c78f9ac 100644 --- a/testsuite/tests/codeGen/should_compile/all.T +++ b/testsuite/tests/codeGen/should_compile/all.T @@ -30,3 +30,4 @@ test('debug', extra_clean(['debug.cmm']), run_command, ['$MAKE -s --no-print-directory debug']) test('T9964', normal, compile, ['-O']) +test('T10518', [cmm_src], compile, ['']) From git at git.haskell.org Mon Jun 15 14:22:20 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Jun 2015 14:22:20 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Enable SMP and GHCi support for Aarch64 (91538a2) Message-ID: <20150615142220.054D13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/91538a2ac4202541a0499e6e37300ade7d0fb6aa/ghc >--------------------------------------------------------------- commit 91538a2ac4202541a0499e6e37300ade7d0fb6aa Author: Erik de Castro Lopo Date: Wed Apr 1 04:46:01 2015 +0000 Enable SMP and GHCi support for Aarch64 Signed-off-by: Erik de Castro Lopo Test Plan: Full build on Aarch64 Reviewers: rwbarton, bgamari, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D859 (cherry picked from commit 1e8c9b81a819da8eb54405a029fc33a9f5220321) >--------------------------------------------------------------- 91538a2ac4202541a0499e6e37300ade7d0fb6aa mk/config.mk.in | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/mk/config.mk.in b/mk/config.mk.in index 42720c8..10539ae 100644 --- a/mk/config.mk.in +++ b/mk/config.mk.in @@ -172,7 +172,7 @@ HaveLibDL = @HaveLibDL@ # ArchSupportsSMP should be set iff there is support for that arch in # includes/stg/SMP.h -ArchSupportsSMP=$(strip $(patsubst $(TargetArch_CPP), YES, $(findstring $(TargetArch_CPP), i386 x86_64 sparc powerpc arm))) +ArchSupportsSMP=$(strip $(patsubst $(TargetArch_CPP), YES, $(findstring $(TargetArch_CPP), i386 x86_64 sparc powerpc arm aarch64))) GhcWithSMP := $(strip $(if $(filter YESNO, $(ArchSupportsSMP)$(GhcUnregisterised)),YES,NO)) @@ -180,7 +180,7 @@ GhcWithSMP := $(strip $(if $(filter YESNO, $(ArchSupportsSMP)$(GhcUnregisterised # has support for this OS/ARCH combination. OsSupportsGHCi=$(strip $(patsubst $(TargetOS_CPP), YES, $(findstring $(TargetOS_CPP), mingw32 cygwin32 linux solaris2 freebsd dragonfly netbsd openbsd darwin kfreebsdgnu))) -ArchSupportsGHCi=$(strip $(patsubst $(TargetArch_CPP), YES, $(findstring $(TargetArch_CPP), i386 x86_64 powerpc sparc sparc64 arm))) +ArchSupportsGHCi=$(strip $(patsubst $(TargetArch_CPP), YES, $(findstring $(TargetArch_CPP), i386 x86_64 powerpc sparc sparc64 arm aarch64))) ifeq "$(OsSupportsGHCi)$(ArchSupportsGHCi)" "YESYES" GhcWithInterpreter=YES From git at git.haskell.org Mon Jun 15 14:23:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Jun 2015 14:23:36 +0000 (UTC) Subject: [commit: ghc] master: Testsuite: fix framework failure (2613271) Message-ID: <20150615142336.C9B7A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2613271ff2eee66c285fbfc5aa6ae22af44138fa/ghc >--------------------------------------------------------------- commit 2613271ff2eee66c285fbfc5aa6ae22af44138fa Author: Thomas Miedema Date: Mon Jun 15 16:19:42 2015 +0200 Testsuite: fix framework failure I forgot to rename this in 5ddd90415f307cac72d75d86da58e552b168ee30. >--------------------------------------------------------------- 2613271ff2eee66c285fbfc5aa6ae22af44138fa testsuite/driver/testlib.py | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index 3da01ce..033440b 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -1684,8 +1684,8 @@ def compare_outputs(way, kind, normaliser, expected_file, actual_file, # If for some reason there were no non-whitespace differences, # then do a full diff if r == 0: - r = os.system( 'diff -u ' + expected_file_for_diff + \ - ' ' + actual_file ) + r = os.system( 'diff -u ' + expected_normalised_file + \ + ' ' + actual_normalised_file ) if config.accept and (getTestOpts().expect == 'fail' or way in getTestOpts().expect_fail_for): From git at git.haskell.org Mon Jun 15 14:25:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 15 Jun 2015 14:25:41 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: relnotes: More notes, some wordsmithing (60016f7) Message-ID: <20150615142541.0367E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/60016f7fe503ee772bf87e888c323128d595bd3f/ghc >--------------------------------------------------------------- commit 60016f7fe503ee772bf87e888c323128d595bd3f Author: Austin Seipp Date: Mon Jun 15 09:26:04 2015 -0500 relnotes: More notes, some wordsmithing Signed-off-by: Austin Seipp >--------------------------------------------------------------- 60016f7fe503ee772bf87e888c323128d595bd3f docs/users_guide/7.10.2-notes.xml | 14 +++++++++++++- 1 file changed, 13 insertions(+), 1 deletion(-) diff --git a/docs/users_guide/7.10.2-notes.xml b/docs/users_guide/7.10.2-notes.xml index 88a9c2f..4289d98 100644 --- a/docs/users_guide/7.10.2-notes.xml +++ b/docs/users_guide/7.10.2-notes.xml @@ -112,6 +112,18 @@ + The SMP runtime is now enabled on AArch64 (issue #10525). + + + + + A bug in the code which caused GHC to emit invalid C code + when porting to a new platform has been fixed (issue + #10518). + + + + A bug which could cause GHC to generate incorrect code at runtime (generating an infinite loop exception) has been fixed (issue #10218). @@ -147,7 +159,7 @@ compiled programs now also specifically recognize ASCII encodings, and can bypass iconv in these cases. This allows statically compiled programs to exist inside an - initramfs, for example. (issues #10298, #7695). + initramfs, for example (issues #10298, #7695). From git at git.haskell.org Tue Jun 16 13:06:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Jun 2015 13:06:01 +0000 (UTC) Subject: [commit: packages/hpc] branch 'wip/T10529' created Message-ID: <20150616130602.000303A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hpc New branch : wip/T10529 Referencing: eaf1906f4456765becd3b52dee0188750feab2bf From git at git.haskell.org Tue Jun 16 13:06:04 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Jun 2015 13:06:04 +0000 (UTC) Subject: [commit: packages/hpc] wip/T10529: Improve error messages in readMix (#10529) (eaf1906) Message-ID: <20150616130604.077B43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hpc On branch : wip/T10529 Link : http://git.haskell.org/packages/hpc.git/commitdiff/eaf1906f4456765becd3b52dee0188750feab2bf >--------------------------------------------------------------- commit eaf1906f4456765becd3b52dee0188750feab2bf Author: Thomas Miedema Date: Tue Jun 16 14:48:19 2015 +0200 Improve error messages in readMix (#10529) >--------------------------------------------------------------- eaf1906f4456765becd3b52dee0188750feab2bf Trace/Hpc/Mix.hs | 44 ++++++++++++++-------- changelog.md | 4 ++ tests/simple/tixs/.hpc/NoParse.mix | 1 + tests/simple/tixs/T10529a.stderr | 1 + tests/simple/tixs/T10529b.stderr | 1 + tests/simple/tixs/T10529c.stderr | 1 + tests/simple/tixs/hpc_sample_incompatible_hash.tix | 1 + tests/simple/tixs/hpc_sample_no_parse.tix | 1 + .../simple/tixs/hpc_sample_non_existing_module.tix | 1 + tests/simple/tixs/test.T | 8 ++++ 10 files changed, 48 insertions(+), 15 deletions(-) diff --git a/Trace/Hpc/Mix.hs b/Trace/Hpc/Mix.hs index f4025d9..695791e 100644 --- a/Trace/Hpc/Mix.hs +++ b/Trace/Hpc/Mix.hs @@ -25,10 +25,18 @@ module Trace.Hpc.Mix import Data.Maybe (catMaybes) import Data.Time (UTCTime) import Data.Tree -import Data.Char import System.FilePath +#if MIN_VERSION_base(4,6,0) +import Text.Read (readMaybe) +#else +readMaybe :: Read a => String -> Maybe a +readMaybe s = case reads s of + [(x, s')] | all isSpace s' -> Just x + _ -> Nothing +#endif + -- a module index records the attributes of each tick-box that has -- been introduced in that module, accessed by tick-number position -- in the list @@ -89,20 +97,18 @@ readMix :: [String] -- ^ Dir Names -> Either String TixModule -- ^ module wanted -> IO Mix readMix dirNames mod' = do - let modName = case mod' of - Left str -> str - Right tix -> tixModuleName tix - res <- sequence [ (do contents <- readFile (mixName dirName modName) - case reads contents of - [(r@(Mix _ _ h _ _),cs)] - | all isSpace cs - && (case mod' of - Left _ -> True - Right tix -> h == tixModuleHash tix - ) -> return $ Just r - _ -> return $ Nothing) `catchIO` (\ _ -> return $ Nothing) - | dirName <- dirNames - ] + let modName = either id tixModuleName mod' + res <- sequence [ + (do let path = mixName dirName modName + contents <- readFile path + case readMaybe contents of + Just x | hashCheck mod' x -> return (Just x) + | otherwise -> error $ "hash in .tix file does " ++ + "not match hash in " ++ path + Nothing -> error $ "can not parse " ++ path) + `catchIO` (\ _ -> return $ Nothing) + | dirName <- dirNames + ] case catMaybes res of xs@(x:_:_) | any (/= x) (tail xs) -> -- Only complain if multiple *different* `Mix` files with the @@ -115,6 +121,14 @@ readMix dirNames mod' = do mixName :: FilePath -> String -> String mixName dirName name = dirName name <.> "mix" +-- | Check that hash in .tix and .mix file match. +hashCheck :: Either String TixModule -- ^ module wanted + -> Mix -- ^ Mix DataStructure + -> Bool +hashCheck mod' (Mix _ _ h _ _) = case mod' of + Left _ -> True -- Bypass hash check. This is a feature. See fab3cfb. + Right tix -> h == tixModuleHash tix + ------------------------------------------------------------------------------ type MixEntryDom a = Tree (HpcPos,a) diff --git a/changelog.md b/changelog.md index dfb36fd..6312fa8 100644 --- a/changelog.md +++ b/changelog.md @@ -1,5 +1,9 @@ # Changelog for [`hpc` package](http://hackage.haskell.org/package/hpc) +## 0.6.0.3 *Unreleased* + + * Improved error messages (#10529) + ## 0.6.0.2 *Mar 2015* * Bundled with GHC 7.10.1 diff --git a/tests/simple/tixs/.hpc/NoParse.mix b/tests/simple/tixs/.hpc/NoParse.mix new file mode 100644 index 0000000..28f54ff --- /dev/null +++ b/tests/simple/tixs/.hpc/NoParse.mix @@ -0,0 +1 @@ +NoParse diff --git a/tests/simple/tixs/T10529a.stderr b/tests/simple/tixs/T10529a.stderr new file mode 100644 index 0000000..945c633 --- /dev/null +++ b/tests/simple/tixs/T10529a.stderr @@ -0,0 +1 @@ +hpc: can not find NonExistingModule in ["./.hpc"] diff --git a/tests/simple/tixs/T10529b.stderr b/tests/simple/tixs/T10529b.stderr new file mode 100644 index 0000000..14591d0 --- /dev/null +++ b/tests/simple/tixs/T10529b.stderr @@ -0,0 +1 @@ +hpc: hash in .tix file does not match hash in ./.hpc/Main.mix diff --git a/tests/simple/tixs/T10529c.stderr b/tests/simple/tixs/T10529c.stderr new file mode 100644 index 0000000..5a0db11 --- /dev/null +++ b/tests/simple/tixs/T10529c.stderr @@ -0,0 +1 @@ +hpc: can not parse ./.hpc/NoParse.mix diff --git a/tests/simple/tixs/hpc_sample_incompatible_hash.tix b/tests/simple/tixs/hpc_sample_incompatible_hash.tix new file mode 100644 index 0000000..f9c335e --- /dev/null +++ b/tests/simple/tixs/hpc_sample_incompatible_hash.tix @@ -0,0 +1 @@ +Tix [ TixModule "Main" 1234567890 5 [1,0,1,1,1]] diff --git a/tests/simple/tixs/hpc_sample_no_parse.tix b/tests/simple/tixs/hpc_sample_no_parse.tix new file mode 100644 index 0000000..b2b2110 --- /dev/null +++ b/tests/simple/tixs/hpc_sample_no_parse.tix @@ -0,0 +1 @@ +Tix [ TixModule "NoParse" 2454134535 5 [1,0,1,1,1]] diff --git a/tests/simple/tixs/hpc_sample_non_existing_module.tix b/tests/simple/tixs/hpc_sample_non_existing_module.tix new file mode 100644 index 0000000..1fa93c5 --- /dev/null +++ b/tests/simple/tixs/hpc_sample_non_existing_module.tix @@ -0,0 +1 @@ +Tix [ TixModule "NonExistingModule" 2454134535 5 [1,0,1,1,1]] diff --git a/tests/simple/tixs/test.T b/tests/simple/tixs/test.T index 8e98d0e..da88911 100644 --- a/tests/simple/tixs/test.T +++ b/tests/simple/tixs/test.T @@ -71,3 +71,11 @@ test('hpc_bad_001', exit_code(1), run_command, ["{hpc} bad arguments"]) test('T9619', ignore_output, run_command, # Having the same mix file in two different hpcdirs should work. ["{hpc} report hpc_sample.tix --hpcdir=.hpc --hpcdir=.hpc.copy"]) + +# Show different error messages for different types of failures. +test('T10529a', exit_code(1), run_command, + ["{hpc} report hpc_sample_non_existing_module.tix"]) +test('T10529b', exit_code(1), run_command, + ["{hpc} report hpc_sample_incompatible_hash.tix"]) +test('T10529c', exit_code(1), run_command, + ["{hpc} report hpc_sample_no_parse.tix"]) From git at git.haskell.org Tue Jun 16 14:26:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Jun 2015 14:26:30 +0000 (UTC) Subject: [commit: ghc] master: Fix #10534 (89c7168) Message-ID: <20150616142630.4E1163A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/89c7168c150ccc38a2e6dd4a3aea555616722260/ghc >--------------------------------------------------------------- commit 89c7168c150ccc38a2e6dd4a3aea555616722260 Author: Richard Eisenberg Date: Mon Jun 15 21:55:52 2015 -0400 Fix #10534 Test case: typecheck/should_fail/T10534 >--------------------------------------------------------------- 89c7168c150ccc38a2e6dd4a3aea555616722260 compiler/types/TyCon.hs | 2 +- testsuite/tests/typecheck/should_fail/T10534.hs | 10 ++++++++++ .../tests/typecheck/should_fail/T10534.stderr | 22 ++++++++++++++++++++++ testsuite/tests/typecheck/should_fail/T10534a.hs | 10 ++++++++++ testsuite/tests/typecheck/should_fail/all.T | 2 ++ 5 files changed, 45 insertions(+), 1 deletion(-) diff --git a/compiler/types/TyCon.hs b/compiler/types/TyCon.hs index 827c076..94fba28 100644 --- a/compiler/types/TyCon.hs +++ b/compiler/types/TyCon.hs @@ -1228,7 +1228,7 @@ isDistinctTyCon _ = False isDistinctAlgRhs :: AlgTyConRhs -> Bool isDistinctAlgRhs (TupleTyCon {}) = True isDistinctAlgRhs (DataTyCon {}) = True -isDistinctAlgRhs (DataFamilyTyCon {}) = True +isDistinctAlgRhs (DataFamilyTyCon {}) = False isDistinctAlgRhs (AbstractTyCon distinct) = distinct isDistinctAlgRhs (NewTyCon {}) = False diff --git a/testsuite/tests/typecheck/should_fail/T10534.hs b/testsuite/tests/typecheck/should_fail/T10534.hs new file mode 100644 index 0000000..ce694b4 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T10534.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE TypeFamilies #-} + +module T10534 where + +import T10534a + +newtype instance DF a = MkDF () + +unsafeCoerce :: a -> b +unsafeCoerce = silly diff --git a/testsuite/tests/typecheck/should_fail/T10534.stderr b/testsuite/tests/typecheck/should_fail/T10534.stderr new file mode 100644 index 0000000..5f44426 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T10534.stderr @@ -0,0 +1,22 @@ + +T10534a.hs:9:10: error: + Could not deduce: a ~ b + from the context: Coercible (DF a) (DF b) + bound by the type signature for: + silly :: Coercible (DF a) (DF b) => a -> b + at T10534a.hs:9:10-42 + ?a? is a rigid type variable bound by + the type signature for: silly :: Coercible (DF a) (DF b) => a -> b + at T10534a.hs:9:10 + ?b? is a rigid type variable bound by + the type signature for: silly :: Coercible (DF a) (DF b) => a -> b + at T10534a.hs:9:10 + arising from trying to show that the representations of + ?DF a? and + ?DF b? are the same + Relevant role signatures: type role DF nominal + In the ambiguity check for the type signature for ?silly?: + silly :: forall a b. Coercible (DF a) (DF b) => a -> b + To defer the ambiguity check to use sites, enable AllowAmbiguousTypes + In the type signature for ?silly?: + silly :: Coercible (DF a) (DF b) => a -> b diff --git a/testsuite/tests/typecheck/should_fail/T10534a.hs b/testsuite/tests/typecheck/should_fail/T10534a.hs new file mode 100644 index 0000000..4f53ebe --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T10534a.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE TypeFamilies, FlexibleContexts #-} + +module T10534a where + +import Data.Coerce + +data family DF a + +silly :: Coercible (DF a) (DF b) => a -> b +silly = coerce diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index 4dfc220..eeb410f 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -365,3 +365,5 @@ test('T10285', extra_clean(['T10285a.hi', 'T10285a.o']), multimod_compile_fail, ['T10285', '-v0']) test('T10351', normal, compile_fail, ['']) +test('T10534', extra_clean(['T10534a.hi', 'T10534a.o']), + multimod_compile_fail, ['T10534', '-v0']) From git at git.haskell.org Tue Jun 16 17:59:12 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Jun 2015 17:59:12 +0000 (UTC) Subject: [commit: ghc] master: ghc.mk: Update instances of -auto-all (df63736) Message-ID: <20150616175912.C64FE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/df63736341d8b92c0f7f0012bf88929e32a1403f/ghc >--------------------------------------------------------------- commit df63736341d8b92c0f7f0012bf88929e32a1403f Author: Ben Gamari Date: Tue Jun 16 19:53:14 2015 +0200 ghc.mk: Update instances of -auto-all -auto-all is now -fprof-auto. Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D989 >--------------------------------------------------------------- df63736341d8b92c0f7f0012bf88929e32a1403f compiler/ghc.mk | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/compiler/ghc.mk b/compiler/ghc.mk index f6ed9c2..0c02f49 100644 --- a/compiler/ghc.mk +++ b/compiler/ghc.mk @@ -384,13 +384,13 @@ ifeq "$(GhcProfiled)" "YES" # everywhere tends to give a hard-to-read profile, and adds lots of # overhead. A better approach is to proceed top-down; identify the # parts of the compiler of interest, and then add further cost centres -# as necessary. Turn on -auto-all for individual modules like this: +# as necessary. Turn on -fprof-auto for individual modules like this: -# compiler/main/DriverPipeline_HC_OPTS += -auto-all -compiler/main/GhcMake_HC_OPTS += -auto-all -compiler/main/GHC_HC_OPTS += -auto-all +# compiler/main/DriverPipeline_HC_OPTS += -fprof-auto +compiler/main/GhcMake_HC_OPTS += -fprof-auto +compiler/main/GHC_HC_OPTS += -fprof-auto -# or alternatively add {-# OPTIONS_GHC -auto-all #-} to the top of +# or alternatively add {-# OPTIONS_GHC -fprof-auto #-} to the top of # modules you're interested in. # We seem to still build the vanilla libraries even if we say From git at git.haskell.org Tue Jun 16 18:03:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Jun 2015 18:03:40 +0000 (UTC) Subject: [commit: ghc] master: Lexer: Suggest adding 'let' on unexpected '=' token (1ff7f09) Message-ID: <20150616180340.530233A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1ff7f09b3abedb2a6daf384b55ad3d0134f0d174/ghc >--------------------------------------------------------------- commit 1ff7f09b3abedb2a6daf384b55ad3d0134f0d174 Author: Ben Gamari Date: Tue Jun 16 20:01:22 2015 +0200 Lexer: Suggest adding 'let' on unexpected '=' token Summary: I've heard numerous fledgling Haskeller's complain about the behavior of ghci regarding bindings. While most REPLs accept bindings of the form `x = 42`, GHCi is implicitly a `do` block, meaning that the user must know to use a `let` to introduce a binding. Here we suggest to the user that they may need a `let` and give them a small example in the event that we find an unexpected `=` token. Reviewers: austin Reviewed By: austin Subscribers: thomie, bgamari Differential Revision: https://phabricator.haskell.org/D980 >--------------------------------------------------------------- 1ff7f09b3abedb2a6daf384b55ad3d0134f0d174 compiler/parser/Lexer.x | 3 +++ testsuite/tests/ghci/should_run/T9915.stderr | 5 ++++- testsuite/tests/parser/should_fail/readFail011.stderr | 5 ++++- testsuite/tests/parser/should_fail/readFail034.stderr | 5 ++++- 4 files changed, 15 insertions(+), 3 deletions(-) diff --git a/compiler/parser/Lexer.x b/compiler/parser/Lexer.x index 1be7245..5839a41 100644 --- a/compiler/parser/Lexer.x +++ b/compiler/parser/Lexer.x @@ -2229,6 +2229,9 @@ srcParseErr dflags buf len (text "Perhaps you intended to use TemplateHaskell") $$ ppWhen (token == "<-") (text "Perhaps this statement should be within a 'do' block?") + $$ ppWhen (token == "=") + (text "Perhaps you need a 'let' in a 'do' block?" + $$ text "e.g. 'let x = 5' instead of 'x = 5'") where token = lexemeToString (offsetBytes (-len) buf) len th_enabled = xopt Opt_TemplateHaskell dflags diff --git a/testsuite/tests/ghci/should_run/T9915.stderr b/testsuite/tests/ghci/should_run/T9915.stderr index de2c5cb..333f17a 100644 --- a/testsuite/tests/ghci/should_run/T9915.stderr +++ b/testsuite/tests/ghci/should_run/T9915.stderr @@ -1,2 +1,5 @@ -:3:9: parse error on input ?=? +:3:9: error: + parse error on input ?=? + Perhaps you need a 'let' in a 'do' block? + e.g. 'let x = 5' instead of 'x = 5' diff --git a/testsuite/tests/parser/should_fail/readFail011.stderr b/testsuite/tests/parser/should_fail/readFail011.stderr index 5c5504b..25accd2 100644 --- a/testsuite/tests/parser/should_fail/readFail011.stderr +++ b/testsuite/tests/parser/should_fail/readFail011.stderr @@ -1,2 +1,5 @@ -readFail011.hs:7:10: parse error on input ?=? +readFail011.hs:7:10: error: + parse error on input ?=? + Perhaps you need a 'let' in a 'do' block? + e.g. 'let x = 5' instead of 'x = 5' diff --git a/testsuite/tests/parser/should_fail/readFail034.stderr b/testsuite/tests/parser/should_fail/readFail034.stderr index 027d0ca..75156c9 100644 --- a/testsuite/tests/parser/should_fail/readFail034.stderr +++ b/testsuite/tests/parser/should_fail/readFail034.stderr @@ -1,2 +1,5 @@ -readFail034.hs:4:6: parse error on input ?=? +readFail034.hs:4:6: error: + parse error on input ?=? + Perhaps you need a 'let' in a 'do' block? + e.g. 'let x = 5' instead of 'x = 5' From git at git.haskell.org Tue Jun 16 18:03:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Jun 2015 18:03:43 +0000 (UTC) Subject: [commit: ghc] master: Lexer: Suggest adding 'let' on unexpected '=' token (0d6c97b) Message-ID: <20150616180343.3DA203A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0d6c97ba1267a53825809f3c99364f7aa38f0847/ghc >--------------------------------------------------------------- commit 0d6c97ba1267a53825809f3c99364f7aa38f0847 Merge: df63736 1ff7f09 Author: Ben Gamari Date: Tue Jun 16 20:04:02 2015 +0200 Lexer: Suggest adding 'let' on unexpected '=' token Summary: I've heard numerous fledgling Haskeller's complain about the behavior of ghci regarding bindings. While most REPLs accept bindings of the form `x = 42`, GHCi is implicitly a `do` block, meaning that the user must know to use a `let` to introduce a binding. Here we suggest to the user that they may need a `let` and give them a small example in the event that we find an unexpected `=` token. Reviewers: austin Reviewed By: austin Subscribers: thomie, bgamari Differential Revision: https://phabricator.haskell.org/D980 >--------------------------------------------------------------- 0d6c97ba1267a53825809f3c99364f7aa38f0847 compiler/parser/Lexer.x | 3 +++ testsuite/tests/ghci/should_run/T9915.stderr | 5 ++++- testsuite/tests/parser/should_fail/readFail011.stderr | 5 ++++- testsuite/tests/parser/should_fail/readFail034.stderr | 5 ++++- 4 files changed, 15 insertions(+), 3 deletions(-) From git at git.haskell.org Tue Jun 16 18:05:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Jun 2015 18:05:38 +0000 (UTC) Subject: [commit: ghc] master: users_guide: Various spelling fixes (a90712b) Message-ID: <20150616180538.17F953A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a90712b47a9439f3edb904ba7d7509181aa42bb7/ghc >--------------------------------------------------------------- commit a90712b47a9439f3edb904ba7d7509181aa42bb7 Author: Ben Gamari Date: Tue Jun 16 20:05:43 2015 +0200 users_guide: Various spelling fixes Summary: Today when reading through the users manual I noticed a few spelling issues. This prompted me to run the document through ispell which turned up even more issues. I've tried to be conservative here; most of the corrections are misspellings and typos but in a few cases I've moved from American to British orthography. Test Plan: Read. Reviewers: austin Reviewed By: austin Subscribers: bgamari, thomie Differential Revision: https://phabricator.haskell.org/D925 >--------------------------------------------------------------- a90712b47a9439f3edb904ba7d7509181aa42bb7 docs/users_guide/bugs.xml | 1 + docs/users_guide/extending_ghc.xml | 1 + docs/users_guide/flags.xml | 9 +++-- docs/users_guide/glasgow_exts.xml | 66 +++++++++++++++---------------- docs/users_guide/gone_wrong.xml | 3 +- docs/users_guide/intro.xml | 3 +- docs/users_guide/lang.xml | 1 + docs/users_guide/packages.xml | 5 ++- docs/users_guide/parallel.xml | 1 + docs/users_guide/phases.xml | 3 +- docs/users_guide/profiling.xml | 1 + docs/users_guide/runghc.xml | 3 +- docs/users_guide/runtime_control.xml | 1 + docs/users_guide/safe_haskell.xml | 1 + docs/users_guide/separate_compilation.xml | 1 + docs/users_guide/shared_libs.xml | 7 ++++ docs/users_guide/sooner.xml | 3 +- docs/users_guide/using.xml | 17 ++++---- docs/users_guide/utils.xml | 1 + docs/users_guide/win32-dlls.xml | 1 + 20 files changed, 78 insertions(+), 51 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a90712b47a9439f3edb904ba7d7509181aa42bb7 From git at git.haskell.org Tue Jun 16 18:05:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Jun 2015 18:05:41 +0000 (UTC) Subject: [commit: ghc] master: users_guide: Various spelling fixes (d46fdf2) Message-ID: <20150616180541.23A383A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d46fdf25888e624e78eefed64bd13dc205ed5fef/ghc >--------------------------------------------------------------- commit d46fdf25888e624e78eefed64bd13dc205ed5fef Merge: 0d6c97b a90712b Author: Ben Gamari Date: Tue Jun 16 20:06:00 2015 +0200 users_guide: Various spelling fixes Summary: Today when reading through the users manual I noticed a few spelling issues. This prompted me to run the document through ispell which turned up even more issues. I've tried to be conservative here; most of the corrections are misspellings and typos but in a few cases I've moved from American to British orthography. Test Plan: Read. Reviewers: austin Reviewed By: austin Subscribers: bgamari, thomie Differential Revision: https://phabricator.haskell.org/D925 >--------------------------------------------------------------- d46fdf25888e624e78eefed64bd13dc205ed5fef docs/users_guide/bugs.xml | 1 + docs/users_guide/extending_ghc.xml | 1 + docs/users_guide/flags.xml | 9 +++-- docs/users_guide/glasgow_exts.xml | 66 +++++++++++++++---------------- docs/users_guide/gone_wrong.xml | 3 +- docs/users_guide/intro.xml | 3 +- docs/users_guide/lang.xml | 1 + docs/users_guide/packages.xml | 5 ++- docs/users_guide/parallel.xml | 1 + docs/users_guide/phases.xml | 3 +- docs/users_guide/profiling.xml | 1 + docs/users_guide/runghc.xml | 3 +- docs/users_guide/runtime_control.xml | 1 + docs/users_guide/safe_haskell.xml | 1 + docs/users_guide/separate_compilation.xml | 1 + docs/users_guide/shared_libs.xml | 7 ++++ docs/users_guide/sooner.xml | 3 +- docs/users_guide/using.xml | 17 ++++---- docs/users_guide/utils.xml | 1 + docs/users_guide/win32-dlls.xml | 1 + 20 files changed, 78 insertions(+), 51 deletions(-) From git at git.haskell.org Tue Jun 16 18:06:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Jun 2015 18:06:59 +0000 (UTC) Subject: [commit: packages/hpc] wip/T10529: Improve error messages in readMix (#10529) (74d8a4e) Message-ID: <20150616180659.600FE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hpc On branch : wip/T10529 Link : http://git.haskell.org/packages/hpc.git/commitdiff/74d8a4e35bf73757e78c6377af9830f0dc8db807 >--------------------------------------------------------------- commit 74d8a4e35bf73757e78c6377af9830f0dc8db807 Author: Thomas Miedema Date: Tue Jun 16 14:48:19 2015 +0200 Improve error messages in readMix (#10529) >--------------------------------------------------------------- 74d8a4e35bf73757e78c6377af9830f0dc8db807 Trace/Hpc/Mix.hs | 48 ++++++++++++++-------- changelog.md | 4 ++ tests/simple/tixs/.hpc/NoParse.mix | 1 + tests/simple/tixs/T10529a.stderr | 1 + tests/simple/tixs/T10529b.stderr | 2 + tests/simple/tixs/T10529c.stderr | 1 + tests/simple/tixs/hpc_sample_incompatible_hash.tix | 1 + tests/simple/tixs/hpc_sample_no_parse.tix | 1 + .../simple/tixs/hpc_sample_non_existing_module.tix | 1 + tests/simple/tixs/test.T | 8 ++++ 10 files changed, 52 insertions(+), 16 deletions(-) diff --git a/Trace/Hpc/Mix.hs b/Trace/Hpc/Mix.hs index f4025d9..6322c99 100644 --- a/Trace/Hpc/Mix.hs +++ b/Trace/Hpc/Mix.hs @@ -22,13 +22,21 @@ module Trace.Hpc.Mix ) where -import Data.Maybe (catMaybes) +import Data.Maybe (catMaybes, fromMaybe) import Data.Time (UTCTime) import Data.Tree -import Data.Char import System.FilePath +#if MIN_VERSION_base(4,6,0) +import Text.Read (readMaybe) +#else +readMaybe :: Read a => String -> Maybe a +readMaybe s = case reads s of + [(x, s')] | all isSpace s' -> Just x + _ -> Nothing +#endif + -- a module index records the attributes of each tick-box that has -- been introduced in that module, accessed by tick-number position -- in the list @@ -89,20 +97,17 @@ readMix :: [String] -- ^ Dir Names -> Either String TixModule -- ^ module wanted -> IO Mix readMix dirNames mod' = do - let modName = case mod' of - Left str -> str - Right tix -> tixModuleName tix - res <- sequence [ (do contents <- readFile (mixName dirName modName) - case reads contents of - [(r@(Mix _ _ h _ _),cs)] - | all isSpace cs - && (case mod' of - Left _ -> True - Right tix -> h == tixModuleHash tix - ) -> return $ Just r - _ -> return $ Nothing) `catchIO` (\ _ -> return $ Nothing) - | dirName <- dirNames - ] + let modName = either id tixModuleName mod' + res <- sequence [ + (do let mixpath = mixName dirName modName + let parse = fromMaybe (error $ "can not parse" ++ mixpath) . readMaybe + mix <- parse `fmap` readFile mixpath + case mod' of + Left _ -> return $ Just mix -- Bypass hash check (fab3cfb) + Right tix -> return $ checkHash tix mix mixpath) + `catchIO` (\ _ -> return $ Nothing) + | dirName <- dirNames + ] case catMaybes res of xs@(x:_:_) | any (/= x) (tail xs) -> -- Only complain if multiple *different* `Mix` files with the @@ -115,6 +120,17 @@ readMix dirNames mod' = do mixName :: FilePath -> String -> String mixName dirName name = dirName name <.> "mix" +-- | Check that hash in .tix and .mix file match. +checkHash :: TixModule -> Mix -> FilePath -> Maybe Mix +checkHash tix mix@(Mix _ _ mixHash _ _) mixpath + | modHash == mixHash = Just mix + | otherwise = error $ + "hash in tix file for module " ++ modName ++ " (" ++ show modHash ++ ")\n" + ++ "does not match hash in " ++ mixpath ++ " (" ++ show mixHash ++ ")" + where + modName = tixModuleName tix + modHash = tixModuleHash tix + ------------------------------------------------------------------------------ type MixEntryDom a = Tree (HpcPos,a) diff --git a/changelog.md b/changelog.md index dfb36fd..6312fa8 100644 --- a/changelog.md +++ b/changelog.md @@ -1,5 +1,9 @@ # Changelog for [`hpc` package](http://hackage.haskell.org/package/hpc) +## 0.6.0.3 *Unreleased* + + * Improved error messages (#10529) + ## 0.6.0.2 *Mar 2015* * Bundled with GHC 7.10.1 diff --git a/tests/simple/tixs/.hpc/NoParse.mix b/tests/simple/tixs/.hpc/NoParse.mix new file mode 100644 index 0000000..28f54ff --- /dev/null +++ b/tests/simple/tixs/.hpc/NoParse.mix @@ -0,0 +1 @@ +NoParse diff --git a/tests/simple/tixs/T10529a.stderr b/tests/simple/tixs/T10529a.stderr new file mode 100644 index 0000000..945c633 --- /dev/null +++ b/tests/simple/tixs/T10529a.stderr @@ -0,0 +1 @@ +hpc: can not find NonExistingModule in ["./.hpc"] diff --git a/tests/simple/tixs/T10529b.stderr b/tests/simple/tixs/T10529b.stderr new file mode 100644 index 0000000..4035997 --- /dev/null +++ b/tests/simple/tixs/T10529b.stderr @@ -0,0 +1,2 @@ +hpc: hash in tix file for module Main (1234567890) +does not match hash in ./.hpc/Main.mix (2454134535) diff --git a/tests/simple/tixs/T10529c.stderr b/tests/simple/tixs/T10529c.stderr new file mode 100644 index 0000000..5a0db11 --- /dev/null +++ b/tests/simple/tixs/T10529c.stderr @@ -0,0 +1 @@ +hpc: can not parse ./.hpc/NoParse.mix diff --git a/tests/simple/tixs/hpc_sample_incompatible_hash.tix b/tests/simple/tixs/hpc_sample_incompatible_hash.tix new file mode 100644 index 0000000..f9c335e --- /dev/null +++ b/tests/simple/tixs/hpc_sample_incompatible_hash.tix @@ -0,0 +1 @@ +Tix [ TixModule "Main" 1234567890 5 [1,0,1,1,1]] diff --git a/tests/simple/tixs/hpc_sample_no_parse.tix b/tests/simple/tixs/hpc_sample_no_parse.tix new file mode 100644 index 0000000..b2b2110 --- /dev/null +++ b/tests/simple/tixs/hpc_sample_no_parse.tix @@ -0,0 +1 @@ +Tix [ TixModule "NoParse" 2454134535 5 [1,0,1,1,1]] diff --git a/tests/simple/tixs/hpc_sample_non_existing_module.tix b/tests/simple/tixs/hpc_sample_non_existing_module.tix new file mode 100644 index 0000000..1fa93c5 --- /dev/null +++ b/tests/simple/tixs/hpc_sample_non_existing_module.tix @@ -0,0 +1 @@ +Tix [ TixModule "NonExistingModule" 2454134535 5 [1,0,1,1,1]] diff --git a/tests/simple/tixs/test.T b/tests/simple/tixs/test.T index 8e98d0e..da88911 100644 --- a/tests/simple/tixs/test.T +++ b/tests/simple/tixs/test.T @@ -71,3 +71,11 @@ test('hpc_bad_001', exit_code(1), run_command, ["{hpc} bad arguments"]) test('T9619', ignore_output, run_command, # Having the same mix file in two different hpcdirs should work. ["{hpc} report hpc_sample.tix --hpcdir=.hpc --hpcdir=.hpc.copy"]) + +# Show different error messages for different types of failures. +test('T10529a', exit_code(1), run_command, + ["{hpc} report hpc_sample_non_existing_module.tix"]) +test('T10529b', exit_code(1), run_command, + ["{hpc} report hpc_sample_incompatible_hash.tix"]) +test('T10529c', exit_code(1), run_command, + ["{hpc} report hpc_sample_no_parse.tix"]) From git at git.haskell.org Tue Jun 16 18:13:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Jun 2015 18:13:13 +0000 (UTC) Subject: [commit: packages/hpc] wip/T10529: Improve error messages in readMix (#10529) (b6efe54) Message-ID: <20150616181313.3FAF63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hpc On branch : wip/T10529 Link : http://git.haskell.org/packages/hpc.git/commitdiff/b6efe544dfee9e1e5822979a9df4d05f4c319cf8 >--------------------------------------------------------------- commit b6efe544dfee9e1e5822979a9df4d05f4c319cf8 Author: Thomas Miedema Date: Tue Jun 16 14:48:19 2015 +0200 Improve error messages in readMix (#10529) >--------------------------------------------------------------- b6efe544dfee9e1e5822979a9df4d05f4c319cf8 Trace/Hpc/Mix.hs | 48 ++++++++++++++-------- changelog.md | 4 ++ tests/simple/tixs/.hpc/NoParse.mix | 1 + tests/simple/tixs/T10529a.stderr | 1 + tests/simple/tixs/T10529b.stderr | 2 + tests/simple/tixs/T10529c.stderr | 1 + tests/simple/tixs/hpc_sample_incompatible_hash.tix | 1 + tests/simple/tixs/hpc_sample_no_parse.tix | 1 + .../simple/tixs/hpc_sample_non_existing_module.tix | 1 + tests/simple/tixs/test.T | 8 ++++ 10 files changed, 52 insertions(+), 16 deletions(-) diff --git a/Trace/Hpc/Mix.hs b/Trace/Hpc/Mix.hs index f4025d9..b4471a8 100644 --- a/Trace/Hpc/Mix.hs +++ b/Trace/Hpc/Mix.hs @@ -22,13 +22,21 @@ module Trace.Hpc.Mix ) where -import Data.Maybe (catMaybes) +import Data.Maybe (catMaybes, fromMaybe) import Data.Time (UTCTime) import Data.Tree -import Data.Char import System.FilePath +#if MIN_VERSION_base(4,6,0) +import Text.Read (readMaybe) +#else +readMaybe :: Read a => String -> Maybe a +readMaybe s = case reads s of + [(x, s')] | all isSpace s' -> Just x + _ -> Nothing +#endif + -- a module index records the attributes of each tick-box that has -- been introduced in that module, accessed by tick-number position -- in the list @@ -89,20 +97,17 @@ readMix :: [String] -- ^ Dir Names -> Either String TixModule -- ^ module wanted -> IO Mix readMix dirNames mod' = do - let modName = case mod' of - Left str -> str - Right tix -> tixModuleName tix - res <- sequence [ (do contents <- readFile (mixName dirName modName) - case reads contents of - [(r@(Mix _ _ h _ _),cs)] - | all isSpace cs - && (case mod' of - Left _ -> True - Right tix -> h == tixModuleHash tix - ) -> return $ Just r - _ -> return $ Nothing) `catchIO` (\ _ -> return $ Nothing) - | dirName <- dirNames - ] + let modName = either id tixModuleName mod' + res <- sequence [ + (do let mixPath = mixName dirName modName + let parse = fromMaybe (error $ "can not parse" ++ mixPath) . readMaybe + mix <- parse `fmap` readFile mixPath + case mod' of + Left _ -> return $ Just mix -- Bypass hash check (fab3cfb) + Right tix -> return $ checkHash tix mix mixPath) + `catchIO` (\ _ -> return $ Nothing) + | dirName <- dirNames + ] case catMaybes res of xs@(x:_:_) | any (/= x) (tail xs) -> -- Only complain if multiple *different* `Mix` files with the @@ -115,6 +120,17 @@ readMix dirNames mod' = do mixName :: FilePath -> String -> String mixName dirName name = dirName name <.> "mix" +-- | Check that hash in .tix and .mix file match. +checkHash :: TixModule -> Mix -> FilePath -> Maybe Mix +checkHash tix mix@(Mix _ _ mixHash _ _) mixPath + | modHash == mixHash = Just mix + | otherwise = error $ + "hash in tix file for module " ++ modName ++ " (" ++ show modHash ++ ")\n" + ++ "does not match hash in " ++ mixPath ++ " (" ++ show mixHash ++ ")" + where + modName = tixModuleName tix + modHash = tixModuleHash tix + ------------------------------------------------------------------------------ type MixEntryDom a = Tree (HpcPos,a) diff --git a/changelog.md b/changelog.md index dfb36fd..6312fa8 100644 --- a/changelog.md +++ b/changelog.md @@ -1,5 +1,9 @@ # Changelog for [`hpc` package](http://hackage.haskell.org/package/hpc) +## 0.6.0.3 *Unreleased* + + * Improved error messages (#10529) + ## 0.6.0.2 *Mar 2015* * Bundled with GHC 7.10.1 diff --git a/tests/simple/tixs/.hpc/NoParse.mix b/tests/simple/tixs/.hpc/NoParse.mix new file mode 100644 index 0000000..28f54ff --- /dev/null +++ b/tests/simple/tixs/.hpc/NoParse.mix @@ -0,0 +1 @@ +NoParse diff --git a/tests/simple/tixs/T10529a.stderr b/tests/simple/tixs/T10529a.stderr new file mode 100644 index 0000000..945c633 --- /dev/null +++ b/tests/simple/tixs/T10529a.stderr @@ -0,0 +1 @@ +hpc: can not find NonExistingModule in ["./.hpc"] diff --git a/tests/simple/tixs/T10529b.stderr b/tests/simple/tixs/T10529b.stderr new file mode 100644 index 0000000..4035997 --- /dev/null +++ b/tests/simple/tixs/T10529b.stderr @@ -0,0 +1,2 @@ +hpc: hash in tix file for module Main (1234567890) +does not match hash in ./.hpc/Main.mix (2454134535) diff --git a/tests/simple/tixs/T10529c.stderr b/tests/simple/tixs/T10529c.stderr new file mode 100644 index 0000000..5a0db11 --- /dev/null +++ b/tests/simple/tixs/T10529c.stderr @@ -0,0 +1 @@ +hpc: can not parse ./.hpc/NoParse.mix diff --git a/tests/simple/tixs/hpc_sample_incompatible_hash.tix b/tests/simple/tixs/hpc_sample_incompatible_hash.tix new file mode 100644 index 0000000..f9c335e --- /dev/null +++ b/tests/simple/tixs/hpc_sample_incompatible_hash.tix @@ -0,0 +1 @@ +Tix [ TixModule "Main" 1234567890 5 [1,0,1,1,1]] diff --git a/tests/simple/tixs/hpc_sample_no_parse.tix b/tests/simple/tixs/hpc_sample_no_parse.tix new file mode 100644 index 0000000..b2b2110 --- /dev/null +++ b/tests/simple/tixs/hpc_sample_no_parse.tix @@ -0,0 +1 @@ +Tix [ TixModule "NoParse" 2454134535 5 [1,0,1,1,1]] diff --git a/tests/simple/tixs/hpc_sample_non_existing_module.tix b/tests/simple/tixs/hpc_sample_non_existing_module.tix new file mode 100644 index 0000000..1fa93c5 --- /dev/null +++ b/tests/simple/tixs/hpc_sample_non_existing_module.tix @@ -0,0 +1 @@ +Tix [ TixModule "NonExistingModule" 2454134535 5 [1,0,1,1,1]] diff --git a/tests/simple/tixs/test.T b/tests/simple/tixs/test.T index 8e98d0e..da88911 100644 --- a/tests/simple/tixs/test.T +++ b/tests/simple/tixs/test.T @@ -71,3 +71,11 @@ test('hpc_bad_001', exit_code(1), run_command, ["{hpc} bad arguments"]) test('T9619', ignore_output, run_command, # Having the same mix file in two different hpcdirs should work. ["{hpc} report hpc_sample.tix --hpcdir=.hpc --hpcdir=.hpc.copy"]) + +# Show different error messages for different types of failures. +test('T10529a', exit_code(1), run_command, + ["{hpc} report hpc_sample_non_existing_module.tix"]) +test('T10529b', exit_code(1), run_command, + ["{hpc} report hpc_sample_incompatible_hash.tix"]) +test('T10529c', exit_code(1), run_command, + ["{hpc} report hpc_sample_no_parse.tix"]) From git at git.haskell.org Tue Jun 16 18:15:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Jun 2015 18:15:55 +0000 (UTC) Subject: [commit: ghc] master: Encode alignment in MO_Memcpy and friends (681973c) Message-ID: <20150616181555.BAB573A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/681973c31c614185229bdae4f6b7ab4f6e64753d/ghc >--------------------------------------------------------------- commit 681973c31c614185229bdae4f6b7ab4f6e64753d Author: Ben Gamari Date: Tue Jun 16 20:16:08 2015 +0200 Encode alignment in MO_Memcpy and friends Summary: Alignment needs to be a compile-time constant. Previously the code generators had to jump through hoops to ensure this was the case as the alignment was passed as a CmmExpr in the arguments list. Now we take care of this up front. This fixes #8131. Authored-by: Reid Barton Dusted-off-by: Ben Gamari Tests for T8131 Test Plan: Validate Reviewers: rwbarton, austin Reviewed By: rwbarton, austin Subscribers: bgamari, carter, thomie Differential Revision: https://phabricator.haskell.org/D624 GHC Trac Issues: #8131 >--------------------------------------------------------------- 681973c31c614185229bdae4f6b7ab4f6e64753d compiler/cmm/CmmMachOp.hs | 29 ++++++++----- compiler/cmm/CmmParse.y | 37 +++++++++++----- compiler/cmm/PprC.hs | 12 +++--- compiler/codeGen/StgCmmPrim.hs | 49 +++++++++++----------- compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 43 +++++++++---------- compiler/nativeGen/PPC/CodeGen.hs | 20 +++------ compiler/nativeGen/SPARC/CodeGen.hs | 21 +++------- compiler/nativeGen/X86/CodeGen.hs | 25 ++++------- includes/Cmm.h | 6 +-- rts/PrimOps.cmm | 8 ++-- .../should_fail}/Makefile | 0 .../should_fail}/T8131.cmm | 0 testsuite/tests/codeGen/should_fail/all.T | 3 ++ .../should_gen_asm/memcpy-unroll-conprop.cmm | 2 +- .../tests/codeGen/should_run/cgrun069_cmm.cmm | 20 ++++----- testsuite/tests/llvm/should_compile/T8131b.hs | 9 ++++ testsuite/tests/llvm/should_compile/all.T | 2 +- 17 files changed, 145 insertions(+), 141 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 681973c31c614185229bdae4f6b7ab4f6e64753d From git at git.haskell.org Tue Jun 16 18:16:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Jun 2015 18:16:00 +0000 (UTC) Subject: [commit: ghc] master: Encode alignment in MO_Memcpy and friends (a0d158f) Message-ID: <20150616181600.3327B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a0d158fdd1db6b8f586bcbc1acd317d9836fb9dc/ghc >--------------------------------------------------------------- commit a0d158fdd1db6b8f586bcbc1acd317d9836fb9dc Merge: d46fdf2 681973c Author: Ben Gamari Date: Tue Jun 16 20:16:16 2015 +0200 Encode alignment in MO_Memcpy and friends Summary: Alignment needs to be a compile-time constant. Previously the code generators had to jump through hoops to ensure this was the case as the alignment was passed as a CmmExpr in the arguments list. Now we take care of this up front. This fixes #8131. Authored-by: Reid Barton Dusted-off-by: Ben Gamari Tests for T8131 Test Plan: Validate Reviewers: rwbarton, austin Reviewed By: rwbarton, austin Subscribers: bgamari, carter, thomie Differential Revision: https://phabricator.haskell.org/D624 GHC Trac Issues: #8131 >--------------------------------------------------------------- a0d158fdd1db6b8f586bcbc1acd317d9836fb9dc compiler/cmm/CmmMachOp.hs | 29 ++++++++----- compiler/cmm/CmmParse.y | 37 +++++++++++----- compiler/cmm/PprC.hs | 12 +++--- compiler/codeGen/StgCmmPrim.hs | 49 +++++++++++----------- compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 43 +++++++++---------- compiler/nativeGen/PPC/CodeGen.hs | 20 +++------ compiler/nativeGen/SPARC/CodeGen.hs | 21 +++------- compiler/nativeGen/X86/CodeGen.hs | 25 ++++------- includes/Cmm.h | 6 +-- rts/PrimOps.cmm | 8 ++-- .../should_fail}/Makefile | 0 .../should_fail}/T8131.cmm | 0 testsuite/tests/codeGen/should_fail/all.T | 3 ++ .../should_gen_asm/memcpy-unroll-conprop.cmm | 2 +- .../tests/codeGen/should_run/cgrun069_cmm.cmm | 20 ++++----- testsuite/tests/llvm/should_compile/T8131b.hs | 9 ++++ testsuite/tests/llvm/should_compile/all.T | 2 +- 17 files changed, 145 insertions(+), 141 deletions(-) From git at git.haskell.org Tue Jun 16 18:22:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Jun 2015 18:22:41 +0000 (UTC) Subject: [commit: ghc] master: Fix #10495. (0de0b14) Message-ID: <20150616182241.9B22D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0de0b14691e0b0789988332ad5addc2a31b09ba6/ghc >--------------------------------------------------------------- commit 0de0b14691e0b0789988332ad5addc2a31b09ba6 Author: Richard Eisenberg Date: Mon Jun 8 15:57:33 2015 -0400 Fix #10495. This change means that the intricate reasoning in TcErrors around getting messages just right for nominal equalities is skipped for representational equalities. >--------------------------------------------------------------- 0de0b14691e0b0789988332ad5addc2a31b09ba6 compiler/typecheck/TcErrors.hs | 13 ++++++++++--- testsuite/tests/typecheck/should_fail/T10495.hs | 5 +++++ testsuite/tests/typecheck/should_fail/T10495.stderr | 6 ++++++ testsuite/tests/typecheck/should_fail/all.T | 1 + 4 files changed, 22 insertions(+), 3 deletions(-) diff --git a/compiler/typecheck/TcErrors.hs b/compiler/typecheck/TcErrors.hs index a4c4703..415ac26 100644 --- a/compiler/typecheck/TcErrors.hs +++ b/compiler/typecheck/TcErrors.hs @@ -919,6 +919,7 @@ mkTyVarEqErr dflags ctxt extra ct oriented tv1 ty2 -- be oriented the other way round; -- see TcCanonical.canEqTyVarTyVar || isSigTyVar tv1 && not (isTyVarTy ty2) + || ctEqRel ct == ReprEq -- the cases below don't really apply to ReprEq = mkErrorMsgFromCt ctxt ct (vcat [ misMatchOrCND ctxt ct oriented ty1 ty2 , extraTyVarInfo ctxt tv1 ty2 , extra ]) @@ -1042,13 +1043,19 @@ misMatchOrCND ctxt ct oriented ty1 ty2 isGivenCt ct -- If the equality is unconditionally insoluble -- or there is no context, don't report the context - = misMatchMsg oriented (ctEqRel ct) ty1 ty2 + = misMatchMsg oriented eq_rel ty1 ty2 | otherwise - = couldNotDeduce givens ([mkTcEqPred ty1 ty2], orig) + = couldNotDeduce givens ([eq_pred], orig) where + eq_rel = ctEqRel ct givens = [ given | given@(_, _, no_eqs, _) <- getUserGivens ctxt, not no_eqs] -- Keep only UserGivens that have some equalities - orig = TypeEqOrigin { uo_actual = ty1, uo_expected = ty2 } + + (eq_pred, orig) = case eq_rel of + NomEq -> ( mkTcEqPred ty1 ty2 + , TypeEqOrigin { uo_actual = ty1, uo_expected = ty2 }) + ReprEq -> ( mkCoerciblePred ty1 ty2 + , CoercibleOrigin ty1 ty2 ) couldNotDeduce :: [UserGiven] -> (ThetaType, CtOrigin) -> SDoc couldNotDeduce givens (wanteds, orig) diff --git a/testsuite/tests/typecheck/should_fail/T10495.hs b/testsuite/tests/typecheck/should_fail/T10495.hs new file mode 100644 index 0000000..2573f51 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T10495.hs @@ -0,0 +1,5 @@ +module T10495 where + +import Data.Coerce + +foo = coerce diff --git a/testsuite/tests/typecheck/should_fail/T10495.stderr b/testsuite/tests/typecheck/should_fail/T10495.stderr new file mode 100644 index 0000000..6e92505 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T10495.stderr @@ -0,0 +1,6 @@ + +T10495.hs:5:7: error: + Couldn't match representation of type ?a0? with that of ?b0? + Relevant bindings include foo :: a0 -> b0 (bound at T10495.hs:5:1) + In the expression: coerce + In an equation for ?foo?: foo = coerce diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index eeb410f..7b0f5fb 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -367,3 +367,4 @@ test('T10285', test('T10351', normal, compile_fail, ['']) test('T10534', extra_clean(['T10534a.hi', 'T10534a.o']), multimod_compile_fail, ['T10534', '-v0']) +test('T10495', normal, compile_fail, ['']) From git at git.haskell.org Tue Jun 16 18:22:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Jun 2015 18:22:44 +0000 (UTC) Subject: [commit: ghc] master: Fix #10493. (ace8d4f) Message-ID: <20150616182244.CC7573A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ace8d4fcfd798b70c34e325c562878b0a8f5e2cb/ghc >--------------------------------------------------------------- commit ace8d4fcfd798b70c34e325c562878b0a8f5e2cb Author: Richard Eisenberg Date: Mon Jun 8 16:46:46 2015 -0400 Fix #10493. Now, a Coercible (T1 ...) (T2 ...) constraint is insoluble only when both T1 and T2 say "yes" to isDistinctTyCon. Several comments also updated in this patch. >--------------------------------------------------------------- ace8d4fcfd798b70c34e325c562878b0a8f5e2cb compiler/typecheck/TcCanonical.hs | 11 +++++++++-- compiler/types/TyCon.hs | 2 +- compiler/types/Unify.hs | 11 +++++++++-- testsuite/tests/typecheck/should_compile/T10493.hs | 9 +++++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 5 files changed, 29 insertions(+), 5 deletions(-) diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index ab9d2c2..e69f12d 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -665,7 +665,7 @@ canDecomposableTyConApp ev eq_rel tc1 tys1 tc2 tys2 -- Fail straight away for better error messages -- See Note [Use canEqFailure in canDecomposableTyConApp] - | isDataFamilyTyCon tc1 || isDataFamilyTyCon tc2 + | eq_rel == ReprEq && not (isDistinctTyCon tc1 && isDistinctTyCon tc2) = canEqFailure ev eq_rel ty1 ty2 | otherwise = canEqHardFailure ev eq_rel ty1 ty2 @@ -678,7 +678,7 @@ Note [Use canEqFailure in canDecomposableTyConApp] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ We must use canEqFailure, not canEqHardFailure here, because there is the possibility of success if working with a representational equality. -Here is the case: +Here is one case: type family TF a where TF Char = Bool data family DF a @@ -688,6 +688,13 @@ Suppose we are canonicalising (Int ~R DF (T a)), where we don't yet know `a`. This is *not* a hard failure, because we might soon learn that `a` is, in fact, Char, and then the equality succeeds. +Here is another case: + + [G] Coercible Age Int + +where Age's constructor is not in scope. We don't want to report +an "inaccessible code" error in the context of this Given! + Note [Decomposing newtypes] ~~~~~~~~~~~~~~~~~~~~~~~~~~~ As explained in Note [NthCo and newtypes] in Coercion, we can't use diff --git a/compiler/types/TyCon.hs b/compiler/types/TyCon.hs index 94fba28..71111c0 100644 --- a/compiler/types/TyCon.hs +++ b/compiler/types/TyCon.hs @@ -1211,7 +1211,7 @@ isDataTyCon (AlgTyCon {algTcRhs = rhs}) isDataTyCon _ = False -- | 'isDistinctTyCon' is true of 'TyCon's that are equal only to --- themselves, even via coercions (except for unsafeCoerce). +-- themselves, even via representational coercions (except for unsafeCoerce). -- This excludes newtypes, type functions, type synonyms. -- It relates directly to the FC consistency story: -- If the axioms are consistent, diff --git a/compiler/types/Unify.hs b/compiler/types/Unify.hs index 0bfcfab..218dc99 100644 --- a/compiler/types/Unify.hs +++ b/compiler/types/Unify.hs @@ -280,8 +280,8 @@ to 'Bool', in which case x::T Int, so Suppose x::T X. Then *in Haskell* it's impossible to construct a (non-bottom) value of type (T X) using T1. But *in FC* it's quite possible. The newtype gives a coercion - CoX :: X ~ Int -So (T CoX) :: T X ~ T Int; hence (T1 `cast` sym (T CoX)) is a non-bottom value + CoX :: X ~R Int +So (T CoX)_R :: T X ~R T Int; hence (T1 `cast` sym (T CoX)) is a non-bottom value of type (T X) constructed with T1. Hence ANSWER = NO we can't prune the T1 branch (surprisingly) @@ -317,6 +317,13 @@ drop more and more dead code. For now we implement a very simple test: type variables match anything, type functions (incl newtypes) match anything, and only distinct data types fail to match. We can elaborate later. + +NB: typesCantMatch is subtly different than the apartness checks +elsewhere in this module. It reasons over *representational* equality +(saying that a newtype is not distinct from its representation) whereas +the checks in, say, tcUnifyTysFG are about *nominal* equality. tcUnifyTysFG +also assumes that its inputs are type-family-free, whereas no such assumption +is in play here. -} typesCantMatch :: [(Type,Type)] -> Bool diff --git a/testsuite/tests/typecheck/should_compile/T10493.hs b/testsuite/tests/typecheck/should_compile/T10493.hs new file mode 100644 index 0000000..3e3caae --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T10493.hs @@ -0,0 +1,9 @@ +{-# LANGUAGE FlexibleContexts #-} + +module T10493 where + +import Data.Coerce +import Data.Ord (Down) -- no constructor + +foo :: Coercible (Down Int) Int => Down Int -> Int +foo = coerce diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index 1f5623d..e26d27a 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -460,3 +460,4 @@ test('T10423', normal, compile, ['']) test('T10489', normal, compile, ['']) test('T10348', normal, compile, ['']) test('T10494', normal, compile, ['']) +test('T10493', normal, compile, ['']) From git at git.haskell.org Tue Jun 16 18:22:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Jun 2015 18:22:48 +0000 (UTC) Subject: [commit: ghc] master: Fix #10494 (c772f57) Message-ID: <20150616182248.07B8D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c772f57e128e04415949f91f299ec9bcc60c4caf/ghc >--------------------------------------------------------------- commit c772f57e128e04415949f91f299ec9bcc60c4caf Author: Richard Eisenberg Date: Fri Jun 5 16:54:21 2015 -0400 Fix #10494 Now representational AppTys are just IrredEvCans, as they should be. Test case: typecheck/should_compile/T10494 >--------------------------------------------------------------- c772f57e128e04415949f91f299ec9bcc60c4caf compiler/typecheck/TcCanonical.hs | 23 ++++++++++++++-------- testsuite/tests/typecheck/should_compile/T10494.hs | 6 ++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 3 files changed, 22 insertions(+), 8 deletions(-) diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index f295e95..ab9d2c2 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -497,14 +497,13 @@ can_eq_nc' _flat _rdr_env _envs ev eq_rel pprEq s1 s2 -- See Note [Do not decompose given polytype equalities] ; stopWith ev "Discard given polytype equality" } --- AppTys only decompose for nominal equality -- See Note [Canonicalising type applications] about why we require flat types -can_eq_nc' True _rdr_env _envs ev NomEq (AppTy t1 s1) _ ty2 _ +can_eq_nc' True _rdr_env _envs ev eq_rel (AppTy t1 s1) _ ty2 _ | Just (t2, s2) <- tcSplitAppTy_maybe ty2 - = can_eq_app ev t1 s1 t2 s2 -can_eq_nc' True _rdr_env _envs ev NomEq ty1 _ (AppTy t2 s2) _ + = can_eq_app ev eq_rel t1 s1 t2 s2 +can_eq_nc' True _rdr_env _envs ev eq_rel ty1 _ (AppTy t2 s2) _ | Just (t1, s1) <- tcSplitAppTy_maybe ty1 - = can_eq_app ev t1 s1 t2 s2 + = can_eq_app ev eq_rel t1 s1 t2 s2 -- No similarity in type structure detected. Flatten and try again! can_eq_nc' False rdr_env envs ev eq_rel _ ps_ty1 _ ps_ty2 @@ -612,13 +611,21 @@ markDataConsAsUsed rdr_env tc = addUsedRdrNamesTcS , not (isLocalGRE gre) ] --------- --- ^ Decompose a type application. Nominal equality only! +-- ^ Decompose a type application. -- All input types must be flat. See Note [Canonicalising type applications] -can_eq_app :: CtEvidence -- :: s1 t1 ~N s2 t2 +can_eq_app :: CtEvidence -- :: s1 t1 ~r s2 t2 + -> EqRel -- r -> Xi -> Xi -- s1 t1 -> Xi -> Xi -- s2 t2 -> TcS (StopOrContinue Ct) -can_eq_app ev s1 t1 s2 t2 + +-- AppTys only decompose for nominal equality, so this case just leads +-- to an irreducible constraint +can_eq_app ev ReprEq _ _ _ _ + = do { traceTcS "failing to decompose representational AppTy equality" (ppr ev) + ; continueWith (CIrredEvCan { cc_ev = ev }) } + +can_eq_app ev NomEq s1 t1 s2 t2 | CtDerived { ctev_loc = loc } <- ev = do { emitNewDerivedEq loc (mkTcEqPred t1 t2) ; canEqNC ev NomEq s1 s2 } diff --git a/testsuite/tests/typecheck/should_compile/T10494.hs b/testsuite/tests/typecheck/should_compile/T10494.hs new file mode 100644 index 0000000..483a07e --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T10494.hs @@ -0,0 +1,6 @@ +module App where + +import Data.Coerce + +foo :: Coercible (a b) (c d) => a b -> c d +foo = coerce diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index 8f42129..1f5623d 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -459,3 +459,4 @@ test('T8799', normal, compile, ['']) test('T10423', normal, compile, ['']) test('T10489', normal, compile, ['']) test('T10348', normal, compile, ['']) +test('T10494', normal, compile, ['']) From git at git.haskell.org Tue Jun 16 18:22:50 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Jun 2015 18:22:50 +0000 (UTC) Subject: [commit: ghc] master: Decompose wanted repr. eqs. when no matchable givens. (ff82387) Message-ID: <20150616182250.CA9B53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ff82387d6fe61762fe4f507e8f9799f5bdc3c43a/ghc >--------------------------------------------------------------- commit ff82387d6fe61762fe4f507e8f9799f5bdc3c43a Author: Richard Eisenberg Date: Mon Jun 8 22:32:40 2015 -0400 Decompose wanted repr. eqs. when no matchable givens. This is pursuant to a conversion with SPJ, where we agreed that the logic behind Note [Instance and Given overlap] in TcInteract applied to newtype decomposition for representational equality. There is no bug report or test case, as tickling this kind of thing is quite hard to do! >--------------------------------------------------------------- ff82387d6fe61762fe4f507e8f9799f5bdc3c43a compiler/typecheck/TcCanonical.hs | 37 ++++++++++++++++----------- compiler/typecheck/TcInteract.hs | 37 +++------------------------ compiler/typecheck/TcSMonad.hs | 53 ++++++++++++++++++++++++++++++++++++++- 3 files changed, 79 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 ff82387d6fe61762fe4f507e8f9799f5bdc3c43a From git at git.haskell.org Tue Jun 16 18:22:53 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Jun 2015 18:22:53 +0000 (UTC) Subject: [commit: ghc] master: Test case for #10428. (6644039) Message-ID: <20150616182253.ED6F23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/66440396bef30e5d6c7b536b552cc4f557d70691/ghc >--------------------------------------------------------------- commit 66440396bef30e5d6c7b536b552cc4f557d70691 Author: Richard Eisenberg Date: Mon Jun 8 16:52:59 2015 -0400 Test case for #10428. >--------------------------------------------------------------- 66440396bef30e5d6c7b536b552cc4f557d70691 testsuite/tests/typecheck/should_compile/T10428.hs | 5 +++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 2 files changed, 6 insertions(+) diff --git a/testsuite/tests/typecheck/should_compile/T10428.hs b/testsuite/tests/typecheck/should_compile/T10428.hs new file mode 100644 index 0000000..2b5201b --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T10428.hs @@ -0,0 +1,5 @@ +module T10428 where + +import Data.Coerce +coerceNewtype :: (Coercible (o r) (n m' r)) => [o r] -> [n m' r] +coerceNewtype = coerce diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index e26d27a..17a3918 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -461,3 +461,4 @@ test('T10489', normal, compile, ['']) test('T10348', normal, compile, ['']) test('T10494', normal, compile, ['']) test('T10493', normal, compile, ['']) +test('T10428', normal, compile, ['']) From git at git.haskell.org Tue Jun 16 18:22:56 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Jun 2015 18:22:56 +0000 (UTC) Subject: [commit: ghc] master: (mostly) Comments only (93f97be) Message-ID: <20150616182256.B87BD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/93f97be75a095b60a7e995cae26caa68961d1fe4/ghc >--------------------------------------------------------------- commit 93f97be75a095b60a7e995cae26caa68961d1fe4 Author: Richard Eisenberg Date: Tue Jun 9 12:14:10 2015 -0400 (mostly) Comments only The one non-comment change is a small refactoring/simplification in TcCanonical that should have no impact: avoiding flattening twice. >--------------------------------------------------------------- 93f97be75a095b60a7e995cae26caa68961d1fe4 compiler/typecheck/TcCanonical.hs | 62 ++++++++++++++++++++++++++++++++------- compiler/types/TyCon.hs | 6 ++-- 2 files changed, 53 insertions(+), 15 deletions(-) diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index 164aed7..9b272cd 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -621,10 +621,12 @@ can_eq_app :: CtEvidence -- :: s1 t1 ~r s2 t2 -> TcS (StopOrContinue Ct) -- AppTys only decompose for nominal equality, so this case just leads --- to an irreducible constraint +-- to an irreducible constraint; see typecheck/should_compile/T10494 can_eq_app ev ReprEq _ _ _ _ = do { traceTcS "failing to decompose representational AppTy equality" (ppr ev) ; continueWith (CIrredEvCan { cc_ev = ev }) } + -- no need to call canEqFailure, because that flattens, and the + -- types involved here are already flat can_eq_app ev NomEq s1 t1 s2 t2 | CtDerived { ctev_loc = loc } <- ev @@ -697,18 +699,44 @@ that `a` is, in fact, Char, and then the equality succeeds. Here is another case: - [G] Coercible Age Int + [G] Age ~R Int where Age's constructor is not in scope. We don't want to report an "inaccessible code" error in the context of this Given! +For example, see typecheck/should_compile/T10493, repeated here: + + import Data.Ord (Down) -- no constructor + + foo :: Coercible (Down Int) Int => Down Int -> Int + foo = coerce + +That should compile, but only because we use canEqFailure and not +canEqHardFailure. + Note [Decomposing newtypes] ~~~~~~~~~~~~~~~~~~~~~~~~~~~ -As explained in Note [NthCo and newtypes] in Coercion, we can't use -NthCo on representational coercions over newtypes. So we avoid doing -so. +Decomposing newtypes is a dangerous business. Here is a representative example +of why: + + newtype Nt a = Mk Bool -- NB: a is not used in the RHS, + type role Nt representational -- but the user gives it an R role anyway + +If we have [W] Nt alpha ~R Nt beta, we *don't* want to decompose to +[W] alpha ~R beta, because it's possible that alpha and beta aren't +representationally equal. So we really want to unwrap newtypes first, +which is what is done in can_eq_nc'. +It all comes from the fact that newtypes aren't necessarily injective w.r.t. +representational equality. + +Furthermore, as explained in Note [NthCo and newtypes] in Coercion, we can't use +NthCo on representational coercions over newtypes. NthCo comes into play +only when decomposing givens. So we avoid decomposing representational given +equalities over newtypes. -But is it sensible to decompose *Wanted* constraints over newtypes? Yes, as +(NB: isNewTyCon tc == True ===> isDistinctTyCon tc == False) + +But is it ever sensible to decompose *Wanted* constraints over newtypes? Yes, as long as there are no Givens that might (later) influence Coercible solving. (See Note [Instance and Given overlap] in TcInteract.) By the time we reach canDecomposableTyConApp, we know that any newtypes that can be unwrapped have @@ -717,6 +745,20 @@ forward other than decomposition. So we take the one route we have available. This *does* mean that importing a newtype's constructor might make code that previously compiled fail to do so. (If that newtype is perversely recursive, say.) + +Example of how a given might influence this decision-making: + + [G] alpha ~R beta + [W] Nt Int ~R Nt gamma + +where Nt is a newtype whose constructor is not in scope, and its parameter +is representational. Decomposing to [W] Int ~R gamma seems sensible, but it's +just possible that the given above will become informative and that we shouldn't +decompose. If we have `newtype Nt a = Mk Bool`, then there might be well-formed +evidence that (Nt Int ~R Nt Char), even if we can't form that evidence in this +module (because Mk is not in scope). Creating this scenario in source Haskell +is challenging; there is no test case. + -} canDecomposableTyConAppOK :: CtEvidence -> EqRel @@ -754,11 +796,9 @@ canEqFailure ev ReprEq ty1 ty2 ; (xi2, co2) <- flatten FM_FlattenAll ev ty2 ; traceTcS "canEqFailure with ReprEq" $ vcat [ ppr ev, ppr ty1, ppr ty2, ppr xi1, ppr xi2 ] - ; if isTcReflCo co1 && isTcReflCo co2 - then continueWith (CIrredEvCan { cc_ev = ev }) - else rewriteEqEvidence ev ReprEq NotSwapped xi1 xi2 co1 co2 - `andWhenContinue` \ new_ev -> - can_eq_nc True new_ev ReprEq xi1 xi1 xi2 xi2 } + ; rewriteEqEvidence ev ReprEq NotSwapped xi1 xi2 co1 co2 + `andWhenContinue` \ new_ev -> + continueWith (CIrredEvCan { cc_ev = new_ev }) } canEqFailure ev NomEq ty1 ty2 = canEqHardFailure ev NomEq ty1 ty2 -- | Call when canonicalizing an equality fails with utterly no hope. diff --git a/compiler/types/TyCon.hs b/compiler/types/TyCon.hs index 71111c0..197e8a1 100644 --- a/compiler/types/TyCon.hs +++ b/compiler/types/TyCon.hs @@ -1215,7 +1215,7 @@ isDataTyCon _ = False -- This excludes newtypes, type functions, type synonyms. -- It relates directly to the FC consistency story: -- If the axioms are consistent, --- and co : S tys ~ T tys, and S,T are "distinct" TyCons, +-- and co : S tys ~R T tys, and S,T are "distinct" TyCons, -- then S=T. -- Cf Note [Pruning dead case alternatives] in Unify isDistinctTyCon :: TyCon -> Bool @@ -1319,10 +1319,8 @@ isTypeSynonymTyCon _ = False isDecomposableTyCon :: TyCon -> Bool -- True iff we can decompose (T a b c) into ((T a b) c) --- I.e. is it injective? +-- I.e. is it injective and generative w.r.t nominal equality? -- Specifically NOT true of synonyms (open and otherwise) --- Ultimately we may have injective associated types --- in which case this test will become more interesting -- -- It'd be unusual to call isDecomposableTyCon on a regular H98 -- type synonym, because you should probably have expanded it first From git at git.haskell.org Tue Jun 16 18:22:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Jun 2015 18:22:59 +0000 (UTC) Subject: [commit: ghc] master: Testsuite wibble around decomposing newtypes. (f108003) Message-ID: <20150616182259.74ED73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f1080035c6ca959f3bf261133ab256f72d56c997/ghc >--------------------------------------------------------------- commit f1080035c6ca959f3bf261133ab256f72d56c997 Author: Richard Eisenberg Date: Tue Jun 9 16:52:40 2015 -0400 Testsuite wibble around decomposing newtypes. This is actually an improvement. Yay! >--------------------------------------------------------------- f1080035c6ca959f3bf261133ab256f72d56c997 testsuite/tests/typecheck/should_fail/T10285.stderr | 5 ++++- testsuite/tests/typecheck/should_fail/T10534.stderr | 20 +++++++++----------- 2 files changed, 13 insertions(+), 12 deletions(-) diff --git a/testsuite/tests/typecheck/should_fail/T10285.stderr b/testsuite/tests/typecheck/should_fail/T10285.stderr index b56f124..1ed2046 100644 --- a/testsuite/tests/typecheck/should_fail/T10285.stderr +++ b/testsuite/tests/typecheck/should_fail/T10285.stderr @@ -1,6 +1,9 @@ T10285.hs:8:17: error: - Could not deduce: a ~ b + Could not deduce: Coercible a b + arising from trying to show that the representations of + ?a? and + ?b? are the same from the context: Coercible (N a) (N b) bound by a pattern with constructor: Coercion :: forall (k :: BOX) (a :: k) (b :: k). diff --git a/testsuite/tests/typecheck/should_fail/T10534.stderr b/testsuite/tests/typecheck/should_fail/T10534.stderr index 5f44426..ab2cde1 100644 --- a/testsuite/tests/typecheck/should_fail/T10534.stderr +++ b/testsuite/tests/typecheck/should_fail/T10534.stderr @@ -1,6 +1,9 @@ -T10534a.hs:9:10: error: - Could not deduce: a ~ b +T10534a.hs:10:9: error: + Could not deduce: Coercible a b + arising from trying to show that the representations of + ?a? and + ?b? are the same from the context: Coercible (DF a) (DF b) bound by the type signature for: silly :: Coercible (DF a) (DF b) => a -> b @@ -11,12 +14,7 @@ T10534a.hs:9:10: error: ?b? is a rigid type variable bound by the type signature for: silly :: Coercible (DF a) (DF b) => a -> b at T10534a.hs:9:10 - arising from trying to show that the representations of - ?DF a? and - ?DF b? are the same - Relevant role signatures: type role DF nominal - In the ambiguity check for the type signature for ?silly?: - silly :: forall a b. Coercible (DF a) (DF b) => a -> b - To defer the ambiguity check to use sites, enable AllowAmbiguousTypes - In the type signature for ?silly?: - silly :: Coercible (DF a) (DF b) => a -> b + Relevant bindings include + silly :: a -> b (bound at T10534a.hs:10:1) + In the expression: coerce + In an equation for ?silly?: silly = coerce From git at git.haskell.org Tue Jun 16 18:23:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Jun 2015 18:23:03 +0000 (UTC) Subject: [commit: ghc] master: Refactor handling of decomposition. (7eceffb) Message-ID: <20150616182303.21F113A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7eceffb3dd1e9c99218630b94ba97da483cec32d/ghc >--------------------------------------------------------------- commit 7eceffb3dd1e9c99218630b94ba97da483cec32d Author: Richard Eisenberg Date: Mon Jun 15 17:02:36 2015 -0400 Refactor handling of decomposition. This adds the significant Note [Decomposing equalities] to TcCanonical, trying to sort out the various cases involved. The only functional change this commit should make is a different treatment of data families, which were wrong before (they could be decomposed at role R, which is wrong). >--------------------------------------------------------------- 7eceffb3dd1e9c99218630b94ba97da483cec32d compiler/coreSyn/CoreLint.hs | 2 +- compiler/typecheck/TcCanonical.hs | 130 +++++++++++++++++---- compiler/typecheck/TcErrors.hs | 2 +- compiler/typecheck/TcUnify.hs | 6 +- compiler/types/Coercion.hs | 2 +- compiler/types/OptCoercion.hs | 2 +- compiler/types/TyCon.hs | 56 +++++---- compiler/types/Type.hs | 6 +- .../tests/typecheck/should_compile/RepArrow.hs | 9 ++ 9 files changed, 160 insertions(+), 55 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 7eceffb3dd1e9c99218630b94ba97da483cec32d From git at git.haskell.org Tue Jun 16 18:23:05 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Jun 2015 18:23:05 +0000 (UTC) Subject: [commit: ghc] master: Clarify some comments around injectivity. (daf1eee) Message-ID: <20150616182305.D67833A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/daf1eee4cdfeba6af77dafe3561fe178b9f30f11/ghc >--------------------------------------------------------------- commit daf1eee4cdfeba6af77dafe3561fe178b9f30f11 Author: Richard Eisenberg Date: Tue Jun 16 08:45:04 2015 -0400 Clarify some comments around injectivity. >--------------------------------------------------------------- daf1eee4cdfeba6af77dafe3561fe178b9f30f11 compiler/typecheck/TcCanonical.hs | 21 +++++++++++++++++++-- compiler/typecheck/TcRnDriver.hs | 2 +- compiler/types/TyCon.hs | 22 +++++++++++++--------- 3 files changed, 33 insertions(+), 12 deletions(-) diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index 7512e42..ee5b6dd 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -720,7 +720,9 @@ NthCo on representational coercions over newtypes. NthCo comes into play only when decomposing givens. So we avoid decomposing representational given equalities over newtypes. -But is it ever sensible to decompose *Wanted* constraints over newtypes? Yes, as +But is it ever sensible to decompose *Wanted* constraints over newtypes? Yes -- +it's the only way we could ever prove (IO Int ~R IO Age), recalling that IO +is a newtype. However, we must decompose wanteds only as long as there are no Givens that might (later) influence Coercible solving. (See Note [Instance and Given overlap] in TcInteract.) By the time we reach canDecomposableTyConApp, we know that any newtypes that can be unwrapped have @@ -743,6 +745,20 @@ evidence that (Nt Int ~R Nt Char), even if we can't form that evidence in this module (because Mk is not in scope). Creating this scenario in source Haskell is challenging; there is no test case. +Example of how decomposing a wanted newtype is wrong, if it's not the only +possibility: + + newtype Nt a = MkNt (Id a) + type family Id a where Id a = a + + [W] Nt Int ~R Nt Age + +Because of its use of a type family, Nt's parameter will get inferred to have +a nominal role. Thus, decomposing the wanted will yield [W] Int ~N Age, which +is unsatisfiable. Unwrapping, though, leads to a solution. + +In summary, decomposing a wanted is always sound, but it might not be complete. +So we do it when it's the only possible way forward. Note [Decomposing equality] ~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -814,7 +830,8 @@ implementation is indeed merged.) {2}: See Note [Decomposing newtypes] {3}: Because of the possibility of newtype instances, we must treat data families -like newtypes. See also Note [Decomposing newtypes]. +like newtypes. See also Note [Decomposing newtypes]. See #10534 and test case +typecheck/should_fail/T10534. {4}: Because type variables can stand in for newtypes, we conservatively do not decompose AppTys over representational equality. diff --git a/compiler/typecheck/TcRnDriver.hs b/compiler/typecheck/TcRnDriver.hs index b260418..0e3ee2d 100644 --- a/compiler/typecheck/TcRnDriver.hs +++ b/compiler/typecheck/TcRnDriver.hs @@ -996,7 +996,7 @@ checkBootTyCon tc1 tc2 quotes (text "representational") <+> text "in boot files.") eqAlgRhs tc (AbstractTyCon dis1) rhs2 - | dis1 = check (isDistinctAlgRhs rhs2) --Check compatibility + | dis1 = check (isGenInjAlgRhs rhs2) --Check compatibility (text "The natures of the declarations for" <+> quotes (ppr tc) <+> text "are different") | otherwise = checkSuccess diff --git a/compiler/types/TyCon.hs b/compiler/types/TyCon.hs index 11f0c42..0a7ba63 100644 --- a/compiler/types/TyCon.hs +++ b/compiler/types/TyCon.hs @@ -49,7 +49,7 @@ module TyCon( isOpenTypeFamilyTyCon, isClosedSynFamilyTyConWithAxiom_maybe, isBuiltInSynFamTyCon_maybe, isUnLiftedTyCon, - isGadtSyntaxTyCon, isInjectiveTyCon, isGenerativeTyCon, isDistinctAlgRhs, + isGadtSyntaxTyCon, isInjectiveTyCon, isGenerativeTyCon, isGenInjAlgRhs, isTyConAssoc, tyConAssoc_maybe, isRecursiveTyCon, isImplicitTyCon, @@ -1165,7 +1165,7 @@ isAbstractTyCon _ = False -- algebraic makeTyConAbstract :: TyCon -> TyCon makeTyConAbstract tc@(AlgTyCon { algTcRhs = rhs }) - = tc { algTcRhs = AbstractTyCon (isDistinctAlgRhs rhs) } + = tc { algTcRhs = AbstractTyCon (isGenInjAlgRhs rhs) } makeTyConAbstract tc = pprPanic "makeTyConAbstract" (ppr tc) -- | Does this 'TyCon' represent something that cannot be defined in Haskell? @@ -1214,12 +1214,13 @@ isDataTyCon _ = False -- (where X is the role passed in): -- If (T a1 b1 c1) ~X (T a2 b2 c2), then (a1 ~X1 a2), (b1 ~X2 b2), and (c1 ~X3 c2) -- (where X1, X2, and X3, are the roles given by tyConRolesX tc X) +-- See also Note [Decomposing equalities] in TcCanonical isInjectiveTyCon :: TyCon -> Role -> Bool isInjectiveTyCon _ Phantom = False isInjectiveTyCon (FunTyCon {}) _ = True isInjectiveTyCon (AlgTyCon {}) Nominal = True isInjectiveTyCon (AlgTyCon {algTcRhs = rhs}) Representational - = isDistinctAlgRhs rhs + = isGenInjAlgRhs rhs isInjectiveTyCon (SynonymTyCon {}) _ = False isInjectiveTyCon (FamilyTyCon {}) _ = False isInjectiveTyCon (PrimTyCon {}) _ = True @@ -1230,6 +1231,7 @@ isInjectiveTyCon (PromotedTyCon {ty_con = tc}) r -- | 'isGenerativeTyCon' is true of 'TyCon's for which this property holds -- (where X is the role passed in): -- If (T tys ~X t), then (t's head ~X T). +-- See also Note [Decomposing equalities] in TcCanonical isGenerativeTyCon :: TyCon -> Role -> Bool isGenerativeTyCon = isInjectiveTyCon -- as it happens, generativity and injectivity coincide, but there's @@ -1237,12 +1239,12 @@ isGenerativeTyCon = isInjectiveTyCon -- | Is this an 'AlgTyConRhs' of a 'TyCon' that is generative and injective -- with respect to representational equality? -isDistinctAlgRhs :: AlgTyConRhs -> Bool -isDistinctAlgRhs (TupleTyCon {}) = True -isDistinctAlgRhs (DataTyCon {}) = True -isDistinctAlgRhs (DataFamilyTyCon {}) = False -isDistinctAlgRhs (AbstractTyCon distinct) = distinct -isDistinctAlgRhs (NewTyCon {}) = False +isGenInjAlgRhs :: AlgTyConRhs -> Bool +isGenInjAlgRhs (TupleTyCon {}) = True +isGenInjAlgRhs (DataTyCon {}) = True +isGenInjAlgRhs (DataFamilyTyCon {}) = False +isGenInjAlgRhs (AbstractTyCon distinct) = distinct +isGenInjAlgRhs (NewTyCon {}) = False -- | Is this 'TyCon' that for a @newtype@ isNewTyCon :: TyCon -> Bool @@ -1332,6 +1334,8 @@ isTypeSynonymTyCon _ = False mightBeUnsaturatedTyCon :: TyCon -> Bool -- True iff we can decompose (T a b c) into ((T a b) c) -- I.e. is it injective and generative w.r.t nominal equality? +-- That is, if (T a b) ~N d e f, is it always the case that +-- (T ~N d), (a ~N e) and (b ~N f)? -- Specifically NOT true of synonyms (open and otherwise) -- -- It'd be unusual to call mightBeUnsaturatedTyCon on a regular H98 From git at git.haskell.org Tue Jun 16 18:23:08 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Jun 2015 18:23:08 +0000 (UTC) Subject: [commit: ghc] master: Fix typo in comment (a6b8b9c) Message-ID: <20150616182308.9A1AA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a6b8b9c210e0d66b0a975f29fbfb1e753b50e28e/ghc >--------------------------------------------------------------- commit a6b8b9c210e0d66b0a975f29fbfb1e753b50e28e Author: Richard Eisenberg Date: Mon Jun 15 21:01:26 2015 -0400 Fix typo in comment >--------------------------------------------------------------- a6b8b9c210e0d66b0a975f29fbfb1e753b50e28e compiler/typecheck/TcCanonical.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index 47be054..7512e42 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -679,7 +679,7 @@ Here is one case: data family DF a newtype instance DF Bool = MkDF Int -Suppose we are canonicalising (Int ~R DF (T a)), where we don't yet +Suppose we are canonicalising (Int ~R DF (TF a)), where we don't yet know `a`. This is *not* a hard failure, because we might soon learn that `a` is, in fact, Char, and then the equality succeeds. From git at git.haskell.org Tue Jun 16 18:23:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Jun 2015 18:23:11 +0000 (UTC) Subject: [commit: ghc] master: Treat funTyCon like any other TyCon in can_eq_nc. (298c424) Message-ID: <20150616182311.63ACB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/298c4244022546842390e51c04b08760d884a6dc/ghc >--------------------------------------------------------------- commit 298c4244022546842390e51c04b08760d884a6dc Author: Richard Eisenberg Date: Mon Jun 15 20:49:10 2015 -0400 Treat funTyCon like any other TyCon in can_eq_nc. Custom treatment of FunTys in can_eq_nc' interfered with the new handling of decomposing equalities. >--------------------------------------------------------------- 298c4244022546842390e51c04b08760d884a6dc compiler/typecheck/TcCanonical.hs | 28 ++++------------------ .../tests/typecheck/should_compile/RepArrow.hs | 4 ++-- testsuite/tests/typecheck/should_compile/all.T | 1 + 3 files changed, 8 insertions(+), 25 deletions(-) diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index 2db2c71..47be054 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -455,32 +455,14 @@ can_eq_nc' _flat _rdr_env _envs ev eq_rel ty1@(LitTy l1) _ (LitTy l2) _ ; stopWith ev "Equal LitTy" } -- Decomposable type constructor applications --- Synonyms and type functions (which are not decomposable) --- have already been dealt with -can_eq_nc' _flat _rdr_env _envs ev eq_rel - (TyConApp tc1 tys1) _ (TyConApp tc2 tys2) _ - | mightBeUnsaturatedTyCon tc1 - , mightBeUnsaturatedTyCon tc2 +can_eq_nc' _flat _rdr_env _envs ev eq_rel ty1 _ ty2 _ + | Just (tc1, tys1) <- tcSplitTyConApp_maybe ty1 + , Just (tc2, tys2) <- tcSplitTyConApp_maybe ty2 + , not (isTypeFamilyTyCon tc1) + , not (isTypeFamilyTyCon tc2) = canTyConApp ev eq_rel tc1 tys1 tc2 tys2 can_eq_nc' _flat _rdr_env _envs ev eq_rel - (TyConApp tc1 _) ps_ty1 (FunTy {}) ps_ty2 - | mightBeUnsaturatedTyCon tc1 - -- The guard is important - -- e.g. (x -> y) ~ (F x y) where F has arity 1 - -- should not fail, but get the app/app case - = canEqHardFailure ev eq_rel ps_ty1 ps_ty2 - -can_eq_nc' _flat _rdr_env _envs ev eq_rel (FunTy s1 t1) _ (FunTy s2 t2) _ - = do { canDecomposableTyConAppOK ev eq_rel funTyCon [s1,t1] [s2,t2] - ; stopWith ev "Decomposed FunTyCon" } - -can_eq_nc' _flat _rdr_env _envs ev eq_rel - (FunTy {}) ps_ty1 (TyConApp tc2 _) ps_ty2 - | mightBeUnsaturatedTyCon tc2 - = canEqHardFailure ev eq_rel ps_ty1 ps_ty2 - -can_eq_nc' _flat _rdr_env _envs ev eq_rel s1@(ForAllTy {}) _ s2@(ForAllTy {}) _ | CtWanted { ctev_loc = loc, ctev_evar = orig_ev } <- ev = do { let (tvs1,body1) = tcSplitForAllTys s1 diff --git a/testsuite/tests/typecheck/should_compile/RepArrow.hs b/testsuite/tests/typecheck/should_compile/RepArrow.hs index d891387..6a9df79 100644 --- a/testsuite/tests/typecheck/should_compile/RepArrow.hs +++ b/testsuite/tests/typecheck/should_compile/RepArrow.hs @@ -5,5 +5,5 @@ module RepArrow where import Data.Ord ( Down ) -- convenient "Id" newtype, without its constructor import Data.Coerce -foo :: Coercible (Down (Int -> Int)) (Int -> Int) => () -foo = () +foo :: Coercible (Down (Int -> Int)) (Int -> Int) => Down (Int -> Int) -> Int -> Int +foo = coerce diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index 17a3918..8165087 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -462,3 +462,4 @@ test('T10348', normal, compile, ['']) test('T10494', normal, compile, ['']) test('T10493', normal, compile, ['']) test('T10428', normal, compile, ['']) +test('RepArrow', normal, compile, ['']) From git at git.haskell.org Tue Jun 16 18:23:14 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Jun 2015 18:23:14 +0000 (UTC) Subject: [commit: ghc] master: Reimplement Unify.typesCantMatch in terms of apartness. (9b105c6) Message-ID: <20150616182314.24D9A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9b105c6d3597ab9b0157ed831d5445d2b619130f/ghc >--------------------------------------------------------------- commit 9b105c6d3597ab9b0157ed831d5445d2b619130f Author: Richard Eisenberg Date: Tue Jun 16 08:57:52 2015 -0400 Reimplement Unify.typesCantMatch in terms of apartness. Because typesCantMatch must also work with type functions, this requires teaching the unifier about type functions and injectivity. Also, some refactoring to use the UM monad more. >--------------------------------------------------------------- 9b105c6d3597ab9b0157ed831d5445d2b619130f compiler/types/Unify.hs | 266 +++++++++++++++++++----------------------------- 1 file changed, 102 insertions(+), 164 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 9b105c6d3597ab9b0157ed831d5445d2b619130f From git at git.haskell.org Tue Jun 16 18:48:10 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Jun 2015 18:48:10 +0000 (UTC) Subject: [commit: packages/hpc] wip/T10529: Improve error messages in readMix (#10529) (6b88e91) Message-ID: <20150616184810.639C33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hpc On branch : wip/T10529 Link : http://git.haskell.org/packages/hpc.git/commitdiff/6b88e91c8a0e7806d44d999616983c60a0b8eb78 >--------------------------------------------------------------- commit 6b88e91c8a0e7806d44d999616983c60a0b8eb78 Author: Thomas Miedema Date: Tue Jun 16 14:48:19 2015 +0200 Improve error messages in readMix (#10529) >--------------------------------------------------------------- 6b88e91c8a0e7806d44d999616983c60a0b8eb78 Trace/Hpc/Mix.hs | 44 +++++++++++++++------- changelog.md | 4 ++ tests/simple/tixs/.hpc/NoParse.mix | 1 + tests/simple/tixs/T10529a.stderr | 1 + tests/simple/tixs/T10529b.stderr | 2 + tests/simple/tixs/T10529c.stderr | 1 + tests/simple/tixs/hpc_sample_incompatible_hash.tix | 1 + tests/simple/tixs/hpc_sample_no_parse.tix | 1 + .../simple/tixs/hpc_sample_non_existing_module.tix | 1 + tests/simple/tixs/test.T | 8 ++++ 10 files changed, 50 insertions(+), 14 deletions(-) diff --git a/Trace/Hpc/Mix.hs b/Trace/Hpc/Mix.hs index f4025d9..0a5f054 100644 --- a/Trace/Hpc/Mix.hs +++ b/Trace/Hpc/Mix.hs @@ -22,13 +22,21 @@ module Trace.Hpc.Mix ) where -import Data.Maybe (catMaybes) +import Data.Maybe (catMaybes, fromMaybe) import Data.Time (UTCTime) import Data.Tree -import Data.Char import System.FilePath +#if MIN_VERSION_base(4,6,0) +import Text.Read (readMaybe) +#else +readMaybe :: Read a => String -> Maybe a +readMaybe s = case reads s of + [(x, s')] | all isSpace s' -> Just x + _ -> Nothing +#endif + -- a module index records the attributes of each tick-box that has -- been introduced in that module, accessed by tick-number position -- in the list @@ -89,18 +97,15 @@ readMix :: [String] -- ^ Dir Names -> Either String TixModule -- ^ module wanted -> IO Mix readMix dirNames mod' = do - let modName = case mod' of - Left str -> str - Right tix -> tixModuleName tix - res <- sequence [ (do contents <- readFile (mixName dirName modName) - case reads contents of - [(r@(Mix _ _ h _ _),cs)] - | all isSpace cs - && (case mod' of - Left _ -> True - Right tix -> h == tixModuleHash tix - ) -> return $ Just r - _ -> return $ Nothing) `catchIO` (\ _ -> return $ Nothing) + let modName = either id tixModuleName mod' + res <- sequence [ (do let mixPath = mixName dirName modName + parseError = error ("can not parse " ++ mixPath) + parse = fromMaybe parseError . readMaybe + mix <- parse `fmap` readFile mixPath + case mod' of + Left _ -> return $ Just mix -- Bypass hash check + Right tix -> return $ checkHash tix mix mixPath) + `catchIO` (\ _ -> return $ Nothing) | dirName <- dirNames ] case catMaybes res of @@ -115,6 +120,17 @@ readMix dirNames mod' = do mixName :: FilePath -> String -> String mixName dirName name = dirName name <.> "mix" +-- | Check that hash in .tix and .mix file match. +checkHash :: TixModule -> Mix -> FilePath -> Maybe Mix +checkHash tix mix@(Mix _ _ mixHash _ _) mixPath + | modHash == mixHash = Just mix + | otherwise = error $ + "hash in tix file for module " ++ modName ++ " (" ++ show modHash ++ ")\n" + ++ "does not match hash in " ++ mixPath ++ " (" ++ show mixHash ++ ")" + where + modName = tixModuleName tix + modHash = tixModuleHash tix + ------------------------------------------------------------------------------ type MixEntryDom a = Tree (HpcPos,a) diff --git a/changelog.md b/changelog.md index dfb36fd..6312fa8 100644 --- a/changelog.md +++ b/changelog.md @@ -1,5 +1,9 @@ # Changelog for [`hpc` package](http://hackage.haskell.org/package/hpc) +## 0.6.0.3 *Unreleased* + + * Improved error messages (#10529) + ## 0.6.0.2 *Mar 2015* * Bundled with GHC 7.10.1 diff --git a/tests/simple/tixs/.hpc/NoParse.mix b/tests/simple/tixs/.hpc/NoParse.mix new file mode 100644 index 0000000..28f54ff --- /dev/null +++ b/tests/simple/tixs/.hpc/NoParse.mix @@ -0,0 +1 @@ +NoParse diff --git a/tests/simple/tixs/T10529a.stderr b/tests/simple/tixs/T10529a.stderr new file mode 100644 index 0000000..945c633 --- /dev/null +++ b/tests/simple/tixs/T10529a.stderr @@ -0,0 +1 @@ +hpc: can not find NonExistingModule in ["./.hpc"] diff --git a/tests/simple/tixs/T10529b.stderr b/tests/simple/tixs/T10529b.stderr new file mode 100644 index 0000000..4035997 --- /dev/null +++ b/tests/simple/tixs/T10529b.stderr @@ -0,0 +1,2 @@ +hpc: hash in tix file for module Main (1234567890) +does not match hash in ./.hpc/Main.mix (2454134535) diff --git a/tests/simple/tixs/T10529c.stderr b/tests/simple/tixs/T10529c.stderr new file mode 100644 index 0000000..5a0db11 --- /dev/null +++ b/tests/simple/tixs/T10529c.stderr @@ -0,0 +1 @@ +hpc: can not parse ./.hpc/NoParse.mix diff --git a/tests/simple/tixs/hpc_sample_incompatible_hash.tix b/tests/simple/tixs/hpc_sample_incompatible_hash.tix new file mode 100644 index 0000000..f9c335e --- /dev/null +++ b/tests/simple/tixs/hpc_sample_incompatible_hash.tix @@ -0,0 +1 @@ +Tix [ TixModule "Main" 1234567890 5 [1,0,1,1,1]] diff --git a/tests/simple/tixs/hpc_sample_no_parse.tix b/tests/simple/tixs/hpc_sample_no_parse.tix new file mode 100644 index 0000000..b2b2110 --- /dev/null +++ b/tests/simple/tixs/hpc_sample_no_parse.tix @@ -0,0 +1 @@ +Tix [ TixModule "NoParse" 2454134535 5 [1,0,1,1,1]] diff --git a/tests/simple/tixs/hpc_sample_non_existing_module.tix b/tests/simple/tixs/hpc_sample_non_existing_module.tix new file mode 100644 index 0000000..1fa93c5 --- /dev/null +++ b/tests/simple/tixs/hpc_sample_non_existing_module.tix @@ -0,0 +1 @@ +Tix [ TixModule "NonExistingModule" 2454134535 5 [1,0,1,1,1]] diff --git a/tests/simple/tixs/test.T b/tests/simple/tixs/test.T index 8e98d0e..da88911 100644 --- a/tests/simple/tixs/test.T +++ b/tests/simple/tixs/test.T @@ -71,3 +71,11 @@ test('hpc_bad_001', exit_code(1), run_command, ["{hpc} bad arguments"]) test('T9619', ignore_output, run_command, # Having the same mix file in two different hpcdirs should work. ["{hpc} report hpc_sample.tix --hpcdir=.hpc --hpcdir=.hpc.copy"]) + +# Show different error messages for different types of failures. +test('T10529a', exit_code(1), run_command, + ["{hpc} report hpc_sample_non_existing_module.tix"]) +test('T10529b', exit_code(1), run_command, + ["{hpc} report hpc_sample_incompatible_hash.tix"]) +test('T10529c', exit_code(1), run_command, + ["{hpc} report hpc_sample_no_parse.tix"]) From git at git.haskell.org Tue Jun 16 21:40:28 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Jun 2015 21:40:28 +0000 (UTC) Subject: [commit: ghc] master: Add `Monoid` instance for `IO` (65d4b89) Message-ID: <20150616214028.E7DED3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/65d4b895d8331ff9e7df6aaf0a0de898c857201c/ghc >--------------------------------------------------------------- commit 65d4b895d8331ff9e7df6aaf0a0de898c857201c Author: Gabriel Gonzalez Date: Tue Jun 16 16:38:18 2015 -0500 Add `Monoid` instance for `IO` See original proposal at https://mail.haskell.org/pipermail/libraries/2014-November/024310.html for more details Reviewed By: hvr, austin Differential Revision: https://phabricator.haskell.org/D988 GHC Trac Issues: #10523 >--------------------------------------------------------------- 65d4b895d8331ff9e7df6aaf0a0de898c857201c libraries/base/GHC/Base.hs | 4 ++++ libraries/base/changelog.md | 2 ++ 2 files changed, 6 insertions(+) diff --git a/libraries/base/GHC/Base.hs b/libraries/base/GHC/Base.hs index 79942d8..e15519d 100644 --- a/libraries/base/GHC/Base.hs +++ b/libraries/base/GHC/Base.hs @@ -312,6 +312,10 @@ instance Monoid a => Monad ((,) a) where return x = (mempty, x) (u, a) >>= k = case k a of (v, b) -> (u `mappend` v, b) +instance Monoid a => Monoid (IO a) where + mempty = pure mempty + mappend = liftA2 mappend + {- | The 'Functor' class is used for types that can be mapped over. Instances of 'Functor' should satisfy the following laws: diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index ad3a74d..df691e3 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -35,6 +35,8 @@ * `Data.Version.Version` now has a `Generic` instance + * `IO` now has a `Monoid` instance + ## 4.8.1.0 *TBA* * Bundled with GHC 7.10.2 From git at git.haskell.org Tue Jun 16 21:40:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Jun 2015 21:40:31 +0000 (UTC) Subject: [commit: ghc] master: Fix ghc-pkg reports cache out date (#10205) (f063656) Message-ID: <20150616214031.A2BB43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f0636562908236f6ce9bf91796bc952534074a61/ghc >--------------------------------------------------------------- commit f0636562908236f6ce9bf91796bc952534074a61 Author: Thomas Miedema Date: Tue Jun 16 16:38:38 2015 -0500 Fix ghc-pkg reports cache out date (#10205) See Note [writeAtomic leaky abstraction]. GHC on Linux already received a patch for this bug in e0801a0fb342eea9a312906eab72874d631271cf. On Windows several cabal tests were hitting the bug, causing validate failures, but we never noticed because of all the other tests that were failing on Windows. And it didn't start happening till `getModificationTime` received sub-second resolution support on Windows in 5cf76186d373842bf64d49cecb09e0a9ddce3203. Since there are regression tests already, I am not adding another one. But for good measure, here is a script that shows the bug without needing to do a full validate run: DB=/tmp/package.conf.d.test GHC_PKG=ghc-pkg #utils/ghc-pkg/dist/build/tmp/ghc-pkg LOCAL_GHC_PKG="${GHC_PKG} --no-user-package-db --global-package-db=${DB}" while true; do rm -rf ${DB} ${LOCAL_GHC_PKG} init "${DB}" ${LOCAL_GHC_PKG} list done If you see "WARNING: cache is out of date" after a few seconds, the bug is not fixed. Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D990 GHC Trac Issues: #10205 >--------------------------------------------------------------- f0636562908236f6ce9bf91796bc952534074a61 utils/ghc-pkg/Main.hs | 48 ++++++++++++++++++++++++++++++++++++++++++++---- 1 file changed, 44 insertions(+), 4 deletions(-) diff --git a/utils/ghc-pkg/Main.hs b/utils/ghc-pkg/Main.hs index b7e617e..f3017a2 100644 --- a/utils/ghc-pkg/Main.hs +++ b/utils/ghc-pkg/Main.hs @@ -1077,10 +1077,15 @@ updateDBCache verbosity db = do if isPermissionError e then die (filename ++ ": you don't have permission to modify this file") else ioError e -#ifndef mingw32_HOST_OS - status <- getFileStatus filename - setFileTimes (location db) (accessTime status) (modificationTime status) -#endif + -- See Note [writeAtomic leaky abstraction] + -- Cross-platform "touch". This only works if filename is not empty, and not + -- open for writing already. + -- TODO. When the Win32 or directory packages have either a touchFile or a + -- setModificationTime function, use one of those. + withBinaryFile filename ReadWriteMode $ \handle -> do + c <- hGetChar handle + hSeek handle AbsoluteSeek 0 + hPutChar handle c type PackageCacheFormat = GhcPkg.InstalledPackageInfo String -- installed package id @@ -2045,3 +2050,38 @@ removeFileSafe fn = -- absolute path. absolutePath :: FilePath -> IO FilePath absolutePath path = return . normalise . ( path) =<< getCurrentDirectory + + +{- Note [writeAtomic leaky abstraction] +GhcPkg.writePackageDb calls writeAtomic, which first writes to a temp file, +and then moves the tempfile to its final destination. This all happens in the +same directory (package.conf.d). +Moving a file doesn't change its modification time, but it *does* change the +modification time of the directory it is placed in. Since we compare the +modification time of the cache file to that of the directory it is in to +decide whether the cache is out-of-date, it will be instantly out-of-date +after creation, if the renaming takes longer than the smallest time difference +that the getModificationTime can measure. + +The solution we opt for is a "touch" of the cache file right after it is +created. This resets the modification time of the cache file and the directory +to the current time. + +Other possible solutions: + * backdate the modification time of the directory to the modification time + of the cachefile. This is what we used to do on posix platforms. An + observer of the directory would see the modification time of the directory + jump back in time. Not nice, although in practice probably not a problem. + Also note that a cross-platform implementation of setModificationTime is + currently not available. + * set the modification time of the cache file to the modification time of + the directory (instead of the curent time). This could also work, + given that we are the only ones writing to this directory. It would also + require a high-precision getModificationTime (lower precision times get + rounded down it seems), or the cache would still be out-of-date. + * change writeAtomic to create the tempfile outside of the target file's + directory. + * create the cachefile outside of the package.conf.d directory in the first + place. But there are tests and there might be tools that currently rely on + the package.conf.d/package.cache format. +-} From git at git.haskell.org Tue Jun 16 21:40:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Jun 2015 21:40:34 +0000 (UTC) Subject: [commit: ghc] master: Update foreign export docs, fixes #10467 (0760b84) Message-ID: <20150616214034.64CDF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0760b84e62d216cbd0ba08a46331bed7c45c88bb/ghc >--------------------------------------------------------------- commit 0760b84e62d216cbd0ba08a46331bed7c45c88bb Author: Edward Z. Yang Date: Tue Jun 16 16:38:59 2015 -0500 Update foreign export docs, fixes #10467 Signed-off-by: Edward Z. Yang Reviewed By: rwbarton, austin Differential Revision: https://phabricator.haskell.org/D951 GHC Trac Issues: #10467 >--------------------------------------------------------------- 0760b84e62d216cbd0ba08a46331bed7c45c88bb docs/users_guide/ffi-chap.xml | 29 ++++++++--------------------- 1 file changed, 8 insertions(+), 21 deletions(-) diff --git a/docs/users_guide/ffi-chap.xml b/docs/users_guide/ffi-chap.xml index 38db2bf..8417ef5 100644 --- a/docs/users_guide/ffi-chap.xml +++ b/docs/users_guide/ffi-chap.xml @@ -271,16 +271,12 @@ void hs_thread_done(void); When GHC compiles a module (say M.hs) which uses foreign export or - foreign import "wrapper", it generates two - additional files, M_stub.c and - M_stub.h. GHC will automatically compile - M_stub.c to generate - M_stub.o at the same time. + foreign import "wrapper", it generates + a M_stub.h for use by C programs. For a plain foreign export, the file M_stub.h contains a C prototype for the - foreign exported function, and M_stub.c - contains its definition. For example, if we compile the + foreign exported function. For example, if we compile the following module: @@ -302,23 +298,14 @@ f n = n:(f (n-1)) #include "HsFFI.h" extern HsInt foo(HsInt a0); - and Foo_stub.c contains the - compiler-generated definition of foo(). To - invoke foo() from C, just #include + To invoke foo() from C, just #include "Foo_stub.h" and call foo(). - The foo_stub.c and - foo_stub.h files can be redirected using the + The + Foo_stub.h file can be redirected using the option; see . - When linking the program, remember to include - M_stub.o in the final link command line, or - you'll get link errors for the missing function(s) (this isn't - necessary when building your program with ghc - --make, as GHC will automatically link in the - correct bits). - Using your own <literal>main()</literal> @@ -338,7 +325,7 @@ extern HsInt foo(HsInt a0); #include "HsFFI.h" #ifdef __GLASGOW_HASKELL__ -#include "foo_stub.h" +#include "Foo_stub.h" #endif int main(int argc, char *argv[]) @@ -411,7 +398,7 @@ int main(int argc, char *argv[]) #include "HsFFI.h" #ifdef __GLASGOW_HASKELL__ -#include "foo_stub.h" +#include "Foo_stub.h" #include "Rts.h" #endif From git at git.haskell.org Tue Jun 16 21:40:37 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Jun 2015 21:40:37 +0000 (UTC) Subject: [commit: ghc] master: Make enum01/enum02/enum03 tests clang-compatible (b98ca17) Message-ID: <20150616214037.6D68D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b98ca17e12c7efdc906f4901f25e6263a5399be1/ghc >--------------------------------------------------------------- commit b98ca17e12c7efdc906f4901f25e6263a5399be1 Author: Reid Barton Date: Tue Jun 16 16:39:15 2015 -0500 Make enum01/enum02/enum03 tests clang-compatible ... by entirely replacing the use of CPP by a custom preprocessor; clang -E -traditional has no stringification mechanism at all. Reviewed By: thomie, austin Differential Revision: https://phabricator.haskell.org/D957 GHC Trac Issues: #9399 >--------------------------------------------------------------- b98ca17e12c7efdc906f4901f25e6263a5399be1 libraries/base/tests/all.T | 6 +++--- libraries/base/tests/enum01.hs | 7 +++++-- libraries/base/tests/enum02.hs | 7 +++++-- libraries/base/tests/enum03.hs | 7 +++++-- libraries/base/tests/enum_processor.py | 24 ++++++++++++++++++++++++ 5 files changed, 42 insertions(+), 9 deletions(-) diff --git a/libraries/base/tests/all.T b/libraries/base/tests/all.T index 1154a53..1c90d14 100644 --- a/libraries/base/tests/all.T +++ b/libraries/base/tests/all.T @@ -77,9 +77,9 @@ test('dynamic002', normal, compile_and_run, ['']) test('dynamic003', extra_run_opts('+RTS -K32m -RTS'), compile_and_run, ['']) test('dynamic004', omit_ways(['normal', 'threaded1', 'ghci']), compile_and_run, ['']) test('dynamic005', normal, compile_and_run, ['']) -test('enum01', when(fast(), skip), compile_and_run, ['-cpp']) -test('enum02', when(fast(), skip), compile_and_run, ['-cpp']) -test('enum03', when(fast(), skip), compile_and_run, ['-cpp']) +test('enum01', when(fast(), skip), compile_and_run, ['']) +test('enum02', when(fast(), skip), compile_and_run, ['']) +test('enum03', when(fast(), skip), compile_and_run, ['']) test('enum04', normal, compile_and_run, ['']) test('exceptionsrun001', normal, compile_and_run, ['']) test('exceptionsrun002', normal, compile_and_run, ['']) diff --git a/libraries/base/tests/enum01.hs b/libraries/base/tests/enum01.hs index 0f26173..0ae39b1 100644 --- a/libraries/base/tests/enum01.hs +++ b/libraries/base/tests/enum01.hs @@ -1,5 +1,9 @@ -- !!! Testing the Prelude's Enum instances. -{-# LANGUAGE CPP #-} +{-# OPTIONS_GHC -F -pgmF ./enum_processor.py #-} +-- The processor is a non-CPP-based equivalent of +-- #define printTest(x) (do{ putStr ( " " ++ "x" ++ " = " ) ; print (x) }) +-- which is not portable to clang + module Main(main) where import Control.Exception @@ -82,7 +86,6 @@ main = do OK - on with the regression testing. -} -#define printTest(x) (do{ putStr ( " " ++ "x" ++ " = " ) ; print (x) }) testEnumInt :: IO () diff --git a/libraries/base/tests/enum02.hs b/libraries/base/tests/enum02.hs index 23de6eb..f7e843c 100644 --- a/libraries/base/tests/enum02.hs +++ b/libraries/base/tests/enum02.hs @@ -1,5 +1,9 @@ -- !!! Testing the Int Enum instances. -{-# LANGUAGE CPP #-} +{-# OPTIONS_GHC -F -pgmF ./enum_processor.py #-} +-- The processor is a non-CPP-based equivalent of +-- #define printTest(x) (do{ putStr ( " " ++ "x" ++ " = " ) ; print (x) }) +-- which is not portable to clang + module Main(main) where import Control.Exception @@ -15,7 +19,6 @@ main = do putStrLn "Testing Enum Int64:" testEnumInt64 -#define printTest(x) (do{ putStr ( " " ++ "x" ++ " = " ) ; print (x) }) testEnumInt8 :: IO () testEnumInt8 = do diff --git a/libraries/base/tests/enum03.hs b/libraries/base/tests/enum03.hs index 1cbe309..181354a 100644 --- a/libraries/base/tests/enum03.hs +++ b/libraries/base/tests/enum03.hs @@ -1,5 +1,9 @@ -- !!! Testing the Word Enum instances. -{-# LANGUAGE CPP #-} +{-# OPTIONS_GHC -F -pgmF ./enum_processor.py #-} +-- The processor is a non-CPP-based equivalent of +-- #define printTest(x) (do{ putStr ( " " ++ "x" ++ " = " ) ; print (x) }) +-- which is not portable to clang + module Main(main) where import Control.Exception @@ -17,7 +21,6 @@ main = do testEnumWord64 -#define printTest(x) (do{ putStr ( " " ++ "x" ++ " = " ) ; print (x) }) testEnumWord8 :: IO () testEnumWord8 = do diff --git a/libraries/base/tests/enum_processor.py b/libraries/base/tests/enum_processor.py new file mode 100755 index 0000000..86c3d6c --- /dev/null +++ b/libraries/base/tests/enum_processor.py @@ -0,0 +1,24 @@ +#!/usr/bin/env python + +import sys + +def process(s): + while True: + start = s.find('printTest') + if start == -1: + return s + j0 = j = s.index('(', start) + 1 + depth = 1 + while depth > 0: + if s[j] == '(': + depth += 1 + if s[j] == ')': + depth -= 1 + j += 1 + argument = s[j0:j-1] + expansion = '(do{ putStr ( " " ++ "%s" ++ " = " ) ; print (%s) })' \ + % (argument, argument) + s = s[:start] + expansion + s[j:] + +_, _, inputFile, outputFile = sys.argv +open(outputFile, 'w').write(process(open(inputFile, 'r').read())) From git at git.haskell.org Tue Jun 16 21:43:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 16 Jun 2015 21:43:13 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Fix #10534 (3670f33) Message-ID: <20150616214313.A70863A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/3670f338cef41aaa2c4c3585fd1aa1f81c65fef8/ghc >--------------------------------------------------------------- commit 3670f338cef41aaa2c4c3585fd1aa1f81c65fef8 Author: Richard Eisenberg Date: Mon Jun 15 21:55:52 2015 -0400 Fix #10534 Test case: typecheck/should_fail/T10534 (cherry picked from commit 89c7168c150ccc38a2e6dd4a3aea555616722260) >--------------------------------------------------------------- 3670f338cef41aaa2c4c3585fd1aa1f81c65fef8 compiler/types/TyCon.hs | 2 +- testsuite/tests/typecheck/should_fail/T10534.hs | 10 ++++++++++ .../tests/typecheck/should_fail/T10534.stderr | 22 ++++++++++++++++++++++ testsuite/tests/typecheck/should_fail/T10534a.hs | 10 ++++++++++ testsuite/tests/typecheck/should_fail/all.T | 2 ++ 5 files changed, 45 insertions(+), 1 deletion(-) diff --git a/compiler/types/TyCon.hs b/compiler/types/TyCon.hs index 4283545..4b912f7 100644 --- a/compiler/types/TyCon.hs +++ b/compiler/types/TyCon.hs @@ -1237,7 +1237,7 @@ isDistinctTyCon _ = False isDistinctAlgRhs :: AlgTyConRhs -> Bool isDistinctAlgRhs (DataTyCon {}) = True -isDistinctAlgRhs (DataFamilyTyCon {}) = True +isDistinctAlgRhs (DataFamilyTyCon {}) = False isDistinctAlgRhs (AbstractTyCon distinct) = distinct isDistinctAlgRhs (NewTyCon {}) = False diff --git a/testsuite/tests/typecheck/should_fail/T10534.hs b/testsuite/tests/typecheck/should_fail/T10534.hs new file mode 100644 index 0000000..ce694b4 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T10534.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE TypeFamilies #-} + +module T10534 where + +import T10534a + +newtype instance DF a = MkDF () + +unsafeCoerce :: a -> b +unsafeCoerce = silly diff --git a/testsuite/tests/typecheck/should_fail/T10534.stderr b/testsuite/tests/typecheck/should_fail/T10534.stderr new file mode 100644 index 0000000..5f44426 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T10534.stderr @@ -0,0 +1,22 @@ + +T10534a.hs:9:10: error: + Could not deduce: a ~ b + from the context: Coercible (DF a) (DF b) + bound by the type signature for: + silly :: Coercible (DF a) (DF b) => a -> b + at T10534a.hs:9:10-42 + ?a? is a rigid type variable bound by + the type signature for: silly :: Coercible (DF a) (DF b) => a -> b + at T10534a.hs:9:10 + ?b? is a rigid type variable bound by + the type signature for: silly :: Coercible (DF a) (DF b) => a -> b + at T10534a.hs:9:10 + arising from trying to show that the representations of + ?DF a? and + ?DF b? are the same + Relevant role signatures: type role DF nominal + In the ambiguity check for the type signature for ?silly?: + silly :: forall a b. Coercible (DF a) (DF b) => a -> b + To defer the ambiguity check to use sites, enable AllowAmbiguousTypes + In the type signature for ?silly?: + silly :: Coercible (DF a) (DF b) => a -> b diff --git a/testsuite/tests/typecheck/should_fail/T10534a.hs b/testsuite/tests/typecheck/should_fail/T10534a.hs new file mode 100644 index 0000000..4f53ebe --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T10534a.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE TypeFamilies, FlexibleContexts #-} + +module T10534a where + +import Data.Coerce + +data family DF a + +silly :: Coercible (DF a) (DF b) => a -> b +silly = coerce diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index ad036b3..31b6a5f 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -362,3 +362,5 @@ test('T10285', test('T9858a', normal, compile_fail, ['']) test('T9858b', normal, compile_fail, ['']) test('T9858e', normal, compile_fail, ['']) +test('T10534', extra_clean(['T10534a.hi', 'T10534a.o']), + multimod_compile_fail, ['T10534', '-v0']) From git at git.haskell.org Wed Jun 17 11:52:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 17 Jun 2015 11:52:39 +0000 (UTC) Subject: [commit: ghc] branch 'wip/impredicativity' created Message-ID: <20150617115239.436053A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/impredicativity Referencing: 06820b45707e6df02f5df20564acc3b8dee5acb6 From git at git.haskell.org Wed Jun 17 11:52:42 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 17 Jun 2015 11:52:42 +0000 (UTC) Subject: [commit: ghc] wip/impredicativity: Initial support for new InstanceOf constraint (d1073f8) Message-ID: <20150617115242.200A33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/impredicativity Link : http://ghc.haskell.org/trac/ghc/changeset/d1073f81abfccb40895e20194a661e673395997f/ghc >--------------------------------------------------------------- commit d1073f81abfccb40895e20194a661e673395997f Author: Alejandro Serrano Date: Tue Jun 16 13:58:06 2015 +0200 Initial support for new InstanceOf constraint As (~) and Coercible, InstanceOf has a kind * -> * -> Constraint which cannot be expressed directly in Haskell. Thus, we have to include its type wired-in. - Add definition to GHC.Types - Add custom kind in compiler/prelude/TysWiredIn. - Add new canonical InstanceOf constraints. >--------------------------------------------------------------- d1073f81abfccb40895e20194a661e673395997f compiler/prelude/PrelNames.hs | 6 ++++++ compiler/prelude/TysWiredIn.hs | 32 ++++++++++++++++++++++++++++--- compiler/prelude/TysWiredIn.hs-boot | 2 +- compiler/typecheck/TcRnTypes.hs | 13 +++++++++++++ compiler/typecheck/TcType.hs | 3 ++- compiler/typecheck/TcValidity.hs | 3 +-- compiler/types/Type.hs | 38 ++++++++++++++++++++++++++++++++----- libraries/ghc-prim/GHC/Types.hs | 8 ++++++-- 8 files changed, 91 insertions(+), 14 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d1073f81abfccb40895e20194a661e673395997f From git at git.haskell.org Wed Jun 17 11:52:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 17 Jun 2015 11:52:44 +0000 (UTC) Subject: [commit: ghc] wip/impredicativity: Implement first rule for InstanceOf canon. (165c139) Message-ID: <20150617115244.F0C5C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/impredicativity Link : http://ghc.haskell.org/trac/ghc/changeset/165c1398f635dade43031edd332652beb1af388d/ghc >--------------------------------------------------------------- commit 165c1398f635dade43031edd332652beb1af388d Author: Alejandro Serrano Date: Wed Jun 17 11:20:02 2015 +0200 Implement first rule for InstanceOf canon. Rule InstanceOf sigma (T ...) --> sigma ~ (T ...) >--------------------------------------------------------------- 165c1398f635dade43031edd332652beb1af388d compiler/typecheck/Inst.hs | 13 ++++++----- compiler/typecheck/TcCanonical.hs | 47 +++++++++++++++++++++++++++++++++++++++ compiler/typecheck/TcEvidence.hs | 28 +++++++++++++++++++++++ compiler/typecheck/TcMType.hs | 1 + compiler/typecheck/TcRnTypes.hs | 26 +++++++++------------- compiler/typecheck/TcSMonad.hs | 7 +++--- 6 files changed, 98 insertions(+), 24 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 165c1398f635dade43031edd332652beb1af388d From git at git.haskell.org Wed Jun 17 11:52:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 17 Jun 2015 11:52:47 +0000 (UTC) Subject: [commit: ghc] wip/impredicativity: Implement second rule for InstanceOf canon. (06820b4) Message-ID: <20150617115247.C6FF43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/impredicativity Link : http://ghc.haskell.org/trac/ghc/changeset/06820b45707e6df02f5df20564acc3b8dee5acb6/ghc >--------------------------------------------------------------- commit 06820b45707e6df02f5df20564acc3b8dee5acb6 Author: Alejandro Serrano Date: Wed Jun 17 13:42:31 2015 +0200 Implement second rule for InstanceOf canon. Rule InstanceOf (T ...) (forall a. Q => ty) --> [a/alpha]Q /\ T ... ~ [a/alpha]ty >--------------------------------------------------------------- 06820b45707e6df02f5df20564acc3b8dee5acb6 compiler/typecheck/TcCanonical.hs | 20 +++++++++++++++++++- compiler/typecheck/TcEvidence.hs | 11 +++++++---- compiler/typecheck/TcSMonad.hs | 12 +++++++++++- compiler/typecheck/TcSimplify.hs | 1 + 4 files changed, 38 insertions(+), 6 deletions(-) diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index 3159cb8..d1c56cf 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -1665,8 +1665,26 @@ can_instance_of ct@(CInstanceOfCan { cc_ev = ev, cc_lhs = lhs, cc_rhs = rhs }) CtDerived {} -> canEqNC (ev { ctev_pred = eq }) NomEq lhs rhs CtGiven {ctev_loc = loc } -> do { emitNewDerivedEq loc eq - ; stopWith ev "Given instance equality" } + ; stopWith ev "Given instanceOf equality" } CtWanted { ctev_evar = evar, ctev_loc = loc } -> do { new_ev <- newWantedEvVarNC loc eq ; setWantedEvBind evar (mkInstanceOfEq (ctEvCoercion new_ev)) ; canEqNC new_ev NomEq lhs rhs } } + + -- case InstanceOf (T ...) (forall qvars. Q => ty) + | Nothing <- getTyVar_maybe lhs, Nothing <- splitForAllTy_maybe lhs + , Just _ <- splitForAllTy_maybe rhs + = case ev of + CtWanted { ctev_evar = evar, ctev_loc = loc } -> + do { (_qvars, q, ty) <- splitInst rhs + -- generate new constraints + ; new_ev_qs <- mapM (newWantedEvVarNC loc) q + ; let eq = mkTcEqPredRole Nominal lhs ty + ; new_ev_ty <- newWantedEvVarNC loc eq + -- compute the evidence for the instantiation + ; setWantedEvBind evar (mkInstanceOfInst (ctEvCoercion new_ev_ty) + (map ctev_evar new_ev_qs)) + -- emit new work + ; emitWorkNC new_ev_qs + ; canEqNC new_ev_ty NomEq lhs ty } + _ -> stopWith ev "Given/Derived instanceOf instantiation" diff --git a/compiler/typecheck/TcEvidence.hs b/compiler/typecheck/TcEvidence.hs index 904e9fd..2400a18 100644 --- a/compiler/typecheck/TcEvidence.hs +++ b/compiler/typecheck/TcEvidence.hs @@ -18,7 +18,7 @@ module TcEvidence ( EvLit(..), evTermCoercion, EvCallStack(..), EvTypeable(..), - EvInstanceOf(..), mkInstanceOfEq, + EvInstanceOf(..), mkInstanceOfEq, mkInstanceOfInst, -- TcCoercion TcCoercion(..), LeftOrRight(..), pickLR, @@ -767,13 +767,16 @@ data EvCallStack -- Evidence for instantiation / InstanceOf constraints data EvInstanceOf = EvInstanceOfEq TcCoercion -- ^ term witnessing equality - | EvInstanceOfInst TcCoercion EvTerm + | EvInstanceOfInst TcCoercion [EvTerm] | EvInstanceOfLet TcEvBinds EvInstanceOf deriving ( Data.Data, Data.Typeable ) mkInstanceOfEq :: TcCoercion -> EvTerm mkInstanceOfEq = EvInstanceOf . EvInstanceOfEq +mkInstanceOfInst :: TcCoercion -> [EvVar] -> EvTerm +mkInstanceOfInst co q = EvInstanceOf (EvInstanceOfInst co (map EvId q)) + {- Note [Coercion evidence terms] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -1037,8 +1040,8 @@ evVarsOfTypeable ev = evVarsOfInstanceOf :: EvInstanceOf -> VarSet evVarsOfInstanceOf ev = case ev of - EvInstanceOfEq co -> coVarsOfTcCo co - EvInstanceOfInst co t -> coVarsOfTcCo co `unionVarSet` evVarsOfTerm t + EvInstanceOfEq co -> coVarsOfTcCo co + EvInstanceOfInst co q -> coVarsOfTcCo co `unionVarSet` evVarsOfTerms q EvInstanceOfLet _ _ -> emptyVarSet {- diff --git a/compiler/typecheck/TcSMonad.hs b/compiler/typecheck/TcSMonad.hs index 231f94a..c0c213c 100644 --- a/compiler/typecheck/TcSMonad.hs +++ b/compiler/typecheck/TcSMonad.hs @@ -15,7 +15,7 @@ module TcSMonad ( TcS, runTcS, runTcSWithEvBinds, failTcS, tryTcS, nestTcS, nestImplicTcS, recoverTcS, - runTcPluginTcS, addUsedRdrNamesTcS, deferTcSForAllEq, + runTcPluginTcS, addUsedRdrNamesTcS, deferTcSForAllEq, splitInst, -- Tracing etc panicTcS, traceTcS, @@ -2869,3 +2869,13 @@ deferTcSForAllEq role loc (tvs1,body1) (tvs2,body2) ; return (TcLetCo ev_binds new_co) } ; return $ EvCoercion (foldr mkTcForAllCo coe_inside skol_tvs) } + +-- Split a sigma type and instantiate its variables +splitInst :: Type -> TcS ([TyVar], ThetaType, Type) +splitInst sigma + = do { let (qvars, q, ty) = tcSplitSigmaTy sigma + -- instantiate variables for q and ty + ; (subst, inst_vars) <- wrapTcS $ TcM.tcInstTyVars qvars + ; let q_subst = map (Type.substTy subst) q + ty_subst = Type.substTy subst ty + ; return (inst_vars, q_subst, ty_subst) } diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs index 2bcf5eb..5b35437 100644 --- a/compiler/typecheck/TcSimplify.hs +++ b/compiler/typecheck/TcSimplify.hs @@ -616,6 +616,7 @@ pickQuantifiablePreds qtvs theta EqPred NomEq ty1 ty2 -> quant_fun ty1 || quant_fun ty2 IrredPred ty -> tyVarsOfType ty `intersectsVarSet` qtvs + InstanceOfPred ty1 ty2 -> quant_fun ty1 || quant_fun ty2 pick_cls_pred flex_ctxt tys = tyVarsOfTypes tys `intersectsVarSet` qtvs From git at git.haskell.org Wed Jun 17 11:58:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 17 Jun 2015 11:58:54 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Update Cabal submodule to Cabal-v1.22.4.0 rls tag (007274e) Message-ID: <20150617115854.E9C2E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/007274e43e96b64bdabb013dd1d984d7f9d9e8b3/ghc >--------------------------------------------------------------- commit 007274e43e96b64bdabb013dd1d984d7f9d9e8b3 Author: Herbert Valerio Riedel Date: Wed Jun 17 13:56:51 2015 +0200 Update Cabal submodule to Cabal-v1.22.4.0 rls tag This only fixes the version number, no code is changed >--------------------------------------------------------------- 007274e43e96b64bdabb013dd1d984d7f9d9e8b3 libraries/Cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Cabal b/libraries/Cabal index 8402899..4f6e9a5 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit 8402899d220e0ad034944470ae86819b5f711801 +Subproject commit 4f6e9a5b63640f4203560f3c7a89131fc66fdd7e From git at git.haskell.org Wed Jun 17 14:28:08 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 17 Jun 2015 14:28:08 +0000 (UTC) Subject: [commit: ghc] wip/impredicativity: Add a flavor to ids in the environment (40831be) Message-ID: <20150617142808.927373A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/impredicativity Link : http://ghc.haskell.org/trac/ghc/changeset/40831bebcf857e16b814fe3a9876ceb4834659c6/ghc >--------------------------------------------------------------- commit 40831bebcf857e16b814fe3a9876ceb4834659c6 Author: Alejandro Serrano Date: Wed Jun 17 16:27:09 2015 +0200 Add a flavor to ids in the environment This flag is needed to implement the new constraint generation and propagation for impredicativity. >--------------------------------------------------------------- 40831bebcf857e16b814fe3a9876ceb4834659c6 compiler/typecheck/TcArrows.hs | 5 +++-- compiler/typecheck/TcBinds.hs | 15 +++++++++------ compiler/typecheck/TcEnv.hs | 32 +++++++++++++++++--------------- compiler/typecheck/TcInstDcls.hs | 3 ++- compiler/typecheck/TcMatches.hs | 13 ++++++++----- compiler/typecheck/TcPat.hs | 6 +++--- compiler/typecheck/TcRnDriver.hs | 4 +++- compiler/typecheck/TcRnTypes.hs | 7 ++++++- compiler/typecheck/TcRules.hs | 6 +++--- 9 files changed, 54 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 40831bebcf857e16b814fe3a9876ceb4834659c6 From git at git.haskell.org Wed Jun 17 17:57:08 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 17 Jun 2015 17:57:08 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Fix ghc-pkg reports cache out date (#10205) (4a87fe4) Message-ID: <20150617175708.407F73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/4a87fe4d09b863103bc6bc2ff3af906c890096b6/ghc >--------------------------------------------------------------- commit 4a87fe4d09b863103bc6bc2ff3af906c890096b6 Author: Thomas Miedema Date: Tue Jun 16 16:38:38 2015 -0500 Fix ghc-pkg reports cache out date (#10205) See Note [writeAtomic leaky abstraction]. GHC on Linux already received a patch for this bug in e0801a0fb342eea9a312906eab72874d631271cf. On Windows several cabal tests were hitting the bug, causing validate failures, but we never noticed because of all the other tests that were failing on Windows. And it didn't start happening till `getModificationTime` received sub-second resolution support on Windows in 5cf76186d373842bf64d49cecb09e0a9ddce3203. Since there are regression tests already, I am not adding another one. But for good measure, here is a script that shows the bug without needing to do a full validate run: DB=/tmp/package.conf.d.test GHC_PKG=ghc-pkg #utils/ghc-pkg/dist/build/tmp/ghc-pkg LOCAL_GHC_PKG="${GHC_PKG} --no-user-package-db --global-package-db=${DB}" while true; do rm -rf ${DB} ${LOCAL_GHC_PKG} init "${DB}" ${LOCAL_GHC_PKG} list done If you see "WARNING: cache is out of date" after a few seconds, the bug is not fixed. Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D990 GHC Trac Issues: #10205 (cherry picked from commit f0636562908236f6ce9bf91796bc952534074a61) >--------------------------------------------------------------- 4a87fe4d09b863103bc6bc2ff3af906c890096b6 utils/ghc-pkg/Main.hs | 48 ++++++++++++++++++++++++++++++++++++++++++++---- 1 file changed, 44 insertions(+), 4 deletions(-) diff --git a/utils/ghc-pkg/Main.hs b/utils/ghc-pkg/Main.hs index 8a6d712..decdb38 100644 --- a/utils/ghc-pkg/Main.hs +++ b/utils/ghc-pkg/Main.hs @@ -1003,10 +1003,15 @@ updateDBCache verbosity db = do if isPermissionError e then die (filename ++ ": you don't have permission to modify this file") else ioError e -#ifndef mingw32_HOST_OS - status <- getFileStatus filename - setFileTimes (location db) (accessTime status) (modificationTime status) -#endif + -- See Note [writeAtomic leaky abstraction] + -- Cross-platform "touch". This only works if filename is not empty, and not + -- open for writing already. + -- TODO. When the Win32 or directory packages have either a touchFile or a + -- setModificationTime function, use one of those. + withBinaryFile filename ReadWriteMode $ \handle -> do + c <- hGetChar handle + hSeek handle AbsoluteSeek 0 + hPutChar handle c type PackageCacheFormat = GhcPkg.InstalledPackageInfo String -- installed package id @@ -2042,3 +2047,38 @@ removeFileSafe fn = absolutePath :: FilePath -> IO FilePath absolutePath path = return . normalise . ( path) =<< getCurrentDirectory + + +{- Note [writeAtomic leaky abstraction] +GhcPkg.writePackageDb calls writeAtomic, which first writes to a temp file, +and then moves the tempfile to its final destination. This all happens in the +same directory (package.conf.d). +Moving a file doesn't change its modification time, but it *does* change the +modification time of the directory it is placed in. Since we compare the +modification time of the cache file to that of the directory it is in to +decide whether the cache is out-of-date, it will be instantly out-of-date +after creation, if the renaming takes longer than the smallest time difference +that the getModificationTime can measure. + +The solution we opt for is a "touch" of the cache file right after it is +created. This resets the modification time of the cache file and the directory +to the current time. + +Other possible solutions: + * backdate the modification time of the directory to the modification time + of the cachefile. This is what we used to do on posix platforms. An + observer of the directory would see the modification time of the directory + jump back in time. Not nice, although in practice probably not a problem. + Also note that a cross-platform implementation of setModificationTime is + currently not available. + * set the modification time of the cache file to the modification time of + the directory (instead of the curent time). This could also work, + given that we are the only ones writing to this directory. It would also + require a high-precision getModificationTime (lower precision times get + rounded down it seems), or the cache would still be out-of-date. + * change writeAtomic to create the tempfile outside of the target file's + directory. + * create the cachefile outside of the package.conf.d directory in the first + place. But there are tests and there might be tools that currently rely on + the package.conf.d/package.cache format. +-} From git at git.haskell.org Thu Jun 18 13:14:50 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 Jun 2015 13:14:50 +0000 (UTC) Subject: [commit: ghc] master: Care with impossible-cons in combineIdenticalAlts (023a0ba) Message-ID: <20150618131450.CCC753A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/023a0ba938b69bbb89cb2ce48a07459b07783391/ghc >--------------------------------------------------------------- commit 023a0ba938b69bbb89cb2ce48a07459b07783391 Author: Simon Peyton Jones Date: Thu Jun 18 08:51:08 2015 +0100 Care with impossible-cons in combineIdenticalAlts This was a nasty, long-standing bug exposed in Trac #10538. Symptoms were that we had an empty case case (x :: Either a) of {} Core Lint correctly picked this bogus code up. Here is what happened * In SimplUtils.prepareAlts, we call filterAlts then combineIdenticalAlts * We had case x of { Left _ -> e1; Right _ -> e1 } * filterAlts did nothing, but correctly retuned imposs_deflt_cons saying that 'x' cannot be {Left, Right} in the DEFAULT branch, if any (there isn't one.) * combineIdentialAlts correctly combines the identical alts, to give case x of { DEFAULT -> e1 } * BUT combineIdenticalAlts did no adjust imposs_deft_cons * Result: when compiling e1 we did so in the belief that 'x' could not be {Left,Right}. Disaster. Easily fixed. (It is hard to trigger; I can't construct a simple test case.) >--------------------------------------------------------------- 023a0ba938b69bbb89cb2ce48a07459b07783391 compiler/simplCore/SimplUtils.hs | 59 +++++++++++++++++++++++++++++----------- 1 file changed, 43 insertions(+), 16 deletions(-) diff --git a/compiler/simplCore/SimplUtils.hs b/compiler/simplCore/SimplUtils.hs index 10b2acd..dbb501e 100644 --- a/compiler/simplCore/SimplUtils.hs +++ b/compiler/simplCore/SimplUtils.hs @@ -62,6 +62,7 @@ import MonadUtils import Outputable import FastString import Pair +import ListSetOps ( minusList ) import Control.Monad ( when ) import Data.List ( partition ) @@ -1672,23 +1673,23 @@ prepareAlts scrut case_bndr' alts -- OutId, it has maximum information; this is important. -- Test simpl013 is an example = do { us <- getUniquesM - ; let (imposs_deflt_cons, refined_deflt, alts') + ; let (imposs_deflt_cons', refined_deflt, alts') = filterAlts us (varType case_bndr') imposs_cons alts - ; when refined_deflt $ tick (FillInCaseDefault case_bndr') - - ; alts'' <- combineIdenticalAlts case_bndr' alts' - ; return (imposs_deflt_cons, alts'') } + (combining_done, imposs_deflt_cons'', alts'') + = combineIdenticalAlts imposs_deflt_cons' alts' + ; when refined_deflt $ tick (FillInCaseDefault case_bndr') + ; when combining_done $ tick (AltMerge case_bndr') + ; return (imposs_deflt_cons'', alts'') } where imposs_cons = case scrut of Var v -> otherCons (idUnfolding v) _ -> [] -{- -Note [Combine identical alternatives] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ - If several alternatives are identical, merge them into - a single DEFAULT alternative. I've occasionally seen this - making a big difference: +{- Note [Combine identical alternatives] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +If several alternatives are identical, merge them into a single +DEFAULT alternative. I've occasionally seen this making a big +difference: case e of =====> case e of C _ -> f x D v -> ....v.... @@ -1726,23 +1727,49 @@ NB: it's important that all this is done in [InAlt], *before* we work on the alternatives themselves, because Simpify.simplAlt may zap the occurrence info on the binders in the alternatives, which in turn defeats combineIdenticalAlts (see Trac #7360). + +Note [Care with impossible-constructors when combining alternatives] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Suppose we have (Trac #10538) + data T = A | B | C + + ... case x::T of + DEFAULT -> e1 + A -> e2 + B -> e1 + +When calling combineIdentialAlts, we'll have computed that the "impossible +constructors" for the DEFAULT alt is {A,B}, since if x is A or B we'll +take the other alternatives. But suppose we combine B into the DEFAULT, +to get + ... case x::T of + DEFAULT -> e1 + A -> e2 +Then we must be careful to trim the impossible constructors to just {A}, +else we risk compiling 'e1' wrong! -} -combineIdenticalAlts :: OutId -> [InAlt] -> SimplM [InAlt] + +combineIdenticalAlts :: [AltCon] -> [InAlt] -> (Bool, [AltCon], [InAlt]) -- See Note [Combine identical alternatives] -combineIdenticalAlts case_bndr ((_con1,bndrs1,rhs1) : con_alts) +-- See Note [Care with impossible-constructors when combining alternatives] +-- True <=> we did some combining, result is a single DEFAULT alternative +combineIdenticalAlts imposs_cons ((_con1,bndrs1,rhs1) : con_alts) | all isDeadBinder bndrs1 -- Remember the default , not (null eliminated_alts) -- alternative comes first - = do { tick (AltMerge case_bndr) - ; return ((DEFAULT, [], mkTicks (concat tickss) rhs1) : filtered_alts) } + = (True, imposs_cons', deflt_alt : filtered_alts) where (eliminated_alts, filtered_alts) = partition identical_to_alt1 con_alts + deflt_alt = (DEFAULT, [], mkTicks (concat tickss) rhs1) + imposs_cons' = imposs_cons `minusList` map fstOf3 eliminated_alts + cheapEqTicked e1 e2 = cheapEqExpr' tickishFloatable e1 e2 identical_to_alt1 (_con,bndrs,rhs) = all isDeadBinder bndrs && rhs `cheapEqTicked` rhs1 tickss = map (stripTicksT tickishFloatable . thirdOf3) eliminated_alts -combineIdenticalAlts _ alts = return alts +combineIdenticalAlts imposs_cons alts + = (False, imposs_cons, alts) {- ************************************************************************ From git at git.haskell.org Thu Jun 18 13:14:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 Jun 2015 13:14:54 +0000 (UTC) Subject: [commit: ghc] master: Report arity errors correctly despite kinds (5879d5a) Message-ID: <20150618131454.4554B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5879d5aab929e9959d48e03dad456b824160b3bf/ghc >--------------------------------------------------------------- commit 5879d5aab929e9959d48e03dad456b824160b3bf Author: Simon Peyton Jones Date: Thu Jun 18 08:54:11 2015 +0100 Report arity errors correctly despite kinds Trac #10516 pointed out that when reporting arity errors (like "T needs 2 arguments but has been given 1"), we should not count kind arguments, since they are implicit. If we include kind args in the count, we get very confusing error messages indeed. I did a little bit of refactoring which make some error messages wobble around. But the payload of this fix is in TcValidity.tyConArityErr >--------------------------------------------------------------- 5879d5aab929e9959d48e03dad456b824160b3bf compiler/typecheck/TcPat.hs | 4 +- compiler/typecheck/TcTyClsDecls.hs | 9 +--- compiler/typecheck/TcValidity.hs | 51 +++++++++++++--------- compiler/types/TyCon.hs | 19 ++++++++ testsuite/tests/gadt/T3163.stderr | 4 +- testsuite/tests/gadt/gadt11.stderr | 4 +- testsuite/tests/gadt/gadtSyntaxFail001.stderr | 4 +- testsuite/tests/gadt/gadtSyntaxFail002.stderr | 4 +- testsuite/tests/gadt/gadtSyntaxFail003.stderr | 4 +- testsuite/tests/gadt/records-fail1.stderr | 4 +- testsuite/tests/ghci/scripts/T9293.stderr | 10 ++--- testsuite/tests/ghci/scripts/ghci057.stderr | 10 ++--- .../tests/indexed-types/should_fail/BadSock.stderr | 4 +- .../tests/indexed-types/should_fail/T2157.stderr | 4 +- .../tests/indexed-types/should_fail/T9433.stderr | 4 +- testsuite/tests/module/mod60.stderr | 4 +- .../should_fail/ParserNoBinaryLiterals2.stderr | 4 +- .../should_fail/ParserNoBinaryLiterals3.stderr | 4 +- testsuite/tests/polykinds/T10516.hs | 9 ++++ testsuite/tests/polykinds/T10516.stderr | 4 ++ testsuite/tests/polykinds/T9222.stderr | 4 +- testsuite/tests/polykinds/all.T | 1 + .../tests/typecheck/should_compile/T7050.stderr | 4 +- .../tests/typecheck/should_compile/T7562.stderr | 4 +- testsuite/tests/typecheck/should_fail/T3966.stderr | 6 +-- testsuite/tests/typecheck/should_fail/T7175.stderr | 4 +- .../tests/typecheck/should_fail/tcfail100.stderr | 6 +-- .../tests/typecheck/should_fail/tcfail101.stderr | 4 +- .../tests/typecheck/should_fail/tcfail107.stderr | 4 +- .../tests/typecheck/should_fail/tcfail129.stderr | 8 ++-- .../tests/typecheck/should_fail/tcfail140.stderr | 12 ++--- .../tests/typecheck/should_fail/tcfail155.stderr | 4 +- .../tests/typecheck/should_fail/tcfail187.stderr | 4 +- .../tests/typecheck/should_fail/tcfail195.stderr | 4 +- .../tests/typecheck/should_fail/tcfail209.stderr | 4 +- 35 files changed, 137 insertions(+), 100 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 5879d5aab929e9959d48e03dad456b824160b3bf From git at git.haskell.org Thu Jun 18 14:18:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 Jun 2015 14:18:09 +0000 (UTC) Subject: [commit: ghc] master: Comments only (f4370c6) Message-ID: <20150618141809.E57C73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f4370c6109e221649bf1e45ce6e30fc683aac97e/ghc >--------------------------------------------------------------- commit f4370c6109e221649bf1e45ce6e30fc683aac97e Author: Simon Peyton Jones Date: Wed Jun 17 12:31:26 2015 +0100 Comments only Rewording in Note [Decomposing equality] Note [Decomposing newtypes at representational role] Richard you may want to check, but I think it's fine. >--------------------------------------------------------------- f4370c6109e221649bf1e45ce6e30fc683aac97e compiler/typecheck/TcCanonical.hs | 139 ++++++++++++++++++++------------------ 1 file changed, 73 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 f4370c6109e221649bf1e45ce6e30fc683aac97e From git at git.haskell.org Thu Jun 18 14:18:12 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 Jun 2015 14:18:12 +0000 (UTC) Subject: [commit: ghc] master: Rename getCtLoc, setCtLoc (4a7a6c3) Message-ID: <20150618141812.A03D43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4a7a6c3ac869f74dfe1c9af09c48faadc0ecba16/ghc >--------------------------------------------------------------- commit 4a7a6c3ac869f74dfe1c9af09c48faadc0ecba16 Author: Simon Peyton Jones Date: Thu Jun 18 13:55:41 2015 +0100 Rename getCtLoc, setCtLoc getCtLoc -> getCtLocM setCtLoc -> setCtLocM These operations are monadic, and I want to introduce a pure version of setCtLoc :: Ct -> CtLoc -> Ct >--------------------------------------------------------------- 4a7a6c3ac869f74dfe1c9af09c48faadc0ecba16 compiler/typecheck/Inst.hs | 6 +++--- compiler/typecheck/TcErrors.hs | 4 ++-- compiler/typecheck/TcExpr.hs | 2 +- compiler/typecheck/TcRnMonad.hs | 10 +++++----- compiler/typecheck/TcSMonad.hs | 2 +- compiler/typecheck/TcUnify.hs | 2 +- 6 files changed, 13 insertions(+), 13 deletions(-) diff --git a/compiler/typecheck/Inst.hs b/compiler/typecheck/Inst.hs index 07d7e0a..fecb11a 100644 --- a/compiler/typecheck/Inst.hs +++ b/compiler/typecheck/Inst.hs @@ -70,7 +70,7 @@ import Data.Maybe( isJust ) newWanted :: CtOrigin -> PredType -> TcM CtEvidence newWanted orig pty - = do loc <- getCtLoc orig + = do loc <- getCtLocM orig v <- newEvVar pty return $ CtWanted { ctev_evar = v , ctev_pred = pty @@ -84,7 +84,7 @@ emitWanteds origin theta = mapM (emitWanted origin) theta emitWanted :: CtOrigin -> TcPredType -> TcM EvVar emitWanted origin pred - = do { loc <- getCtLoc origin + = do { loc <- getCtLocM origin ; ev <- newEvVar pred ; emitSimple $ mkNonCanonical $ CtWanted { ctev_pred = pred, ctev_evar = ev, ctev_loc = loc } @@ -403,7 +403,7 @@ tcSyntaxName orig ty (std_nm, user_nm_expr) = do syntaxNameCtxt :: HsExpr Name -> CtOrigin -> Type -> TidyEnv -> TcRn (TidyEnv, SDoc) syntaxNameCtxt name orig ty tidy_env - = do { inst_loc <- getCtLoc orig + = do { inst_loc <- getCtLocM orig ; let msg = vcat [ ptext (sLit "When checking that") <+> quotes (ppr name) <+> ptext (sLit "(needed by a syntactic construct)") , nest 2 (ptext (sLit "has the required type:") diff --git a/compiler/typecheck/TcErrors.hs b/compiler/typecheck/TcErrors.hs index 36b7947..946ecde 100644 --- a/compiler/typecheck/TcErrors.hs +++ b/compiler/typecheck/TcErrors.hs @@ -1688,7 +1688,7 @@ warnDefaulting wanteds default_ty warn_msg = hang (ptext (sLit "Defaulting the following constraint(s) to type") <+> quotes (ppr default_ty)) 2 ppr_wanteds - ; setCtLoc loc $ warnTc warn_default warn_msg } + ; setCtLocM loc $ warnTc warn_default warn_msg } {- Note [Runtime skolems] @@ -1707,7 +1707,7 @@ are created by in RtClosureInspect.zonkRTTIType. solverDepthErrorTcS :: CtLoc -> TcType -> TcM a solverDepthErrorTcS loc ty - = setCtLoc loc $ + = setCtLocM loc $ do { ty <- zonkTcType ty ; env0 <- tcInitTidyEnv ; let tidy_env = tidyFreeTyVars env0 (tyVarsOfType ty) diff --git a/compiler/typecheck/TcExpr.hs b/compiler/typecheck/TcExpr.hs index a962258..7b47fcf 100644 --- a/compiler/typecheck/TcExpr.hs +++ b/compiler/typecheck/TcExpr.hs @@ -131,7 +131,7 @@ tcHole occ res_ty = do { ty <- newFlexiTyVarTy liftedTypeKind ; name <- newSysName occ ; let ev = mkLocalId name ty - ; loc <- getCtLoc HoleOrigin + ; loc <- getCtLocM HoleOrigin ; let can = CHoleCan { cc_ev = CtWanted ty ev loc, cc_occ = occ , cc_hole = ExprHole } ; emitInsoluble can diff --git a/compiler/typecheck/TcRnMonad.hs b/compiler/typecheck/TcRnMonad.hs index 3c69b95..0e44c4c 100644 --- a/compiler/typecheck/TcRnMonad.hs +++ b/compiler/typecheck/TcRnMonad.hs @@ -956,16 +956,16 @@ updCtxt upd = updLclEnv (\ env@(TcLclEnv { tcl_ctxt = ctxt }) -> popErrCtxt :: TcM a -> TcM a popErrCtxt = updCtxt (\ msgs -> case msgs of { [] -> []; (_ : ms) -> ms }) -getCtLoc :: CtOrigin -> TcM CtLoc -getCtLoc origin +getCtLocM :: CtOrigin -> TcM CtLoc +getCtLocM origin = do { env <- getLclEnv ; return (CtLoc { ctl_origin = origin , ctl_env = env , ctl_depth = initialSubGoalDepth }) } -setCtLoc :: CtLoc -> TcM a -> TcM a +setCtLocM :: CtLoc -> TcM a -> TcM a -- Set the SrcSpan and error context from the CtLoc -setCtLoc (CtLoc { ctl_env = lcl }) thing_inside +setCtLocM (CtLoc { ctl_env = lcl }) thing_inside = updLclEnv (\env -> env { tcl_loc = tcl_loc lcl , tcl_bndrs = tcl_bndrs lcl , tcl_ctxt = tcl_ctxt lcl }) @@ -1241,7 +1241,7 @@ traceTcConstraints msg emitWildcardHoleConstraints :: [(Name, TcTyVar)] -> TcM () emitWildcardHoleConstraints wcs - = do { ctLoc <- getCtLoc HoleOrigin + = do { ctLoc <- getCtLocM HoleOrigin ; forM_ wcs $ \(name, tv) -> do { ; let real_span = case nameSrcSpan name of RealSrcSpan span -> span diff --git a/compiler/typecheck/TcSMonad.hs b/compiler/typecheck/TcSMonad.hs index f78cdc6..c131f61 100644 --- a/compiler/typecheck/TcSMonad.hs +++ b/compiler/typecheck/TcSMonad.hs @@ -2468,7 +2468,7 @@ addUsedRdrNamesTcS names = wrapTcS $ addUsedRdrNames names checkWellStagedDFun :: PredType -> DFunId -> CtLoc -> TcS () checkWellStagedDFun pred dfun_id loc - = wrapTcS $ TcM.setCtLoc loc $ + = wrapTcS $ TcM.setCtLocM loc $ do { use_stage <- TcM.getStage ; TcM.checkWellStaged pp_thing bind_lvl (thLevel use_stage) } where diff --git a/compiler/typecheck/TcUnify.hs b/compiler/typecheck/TcUnify.hs index b2f31be..3f540f5 100644 --- a/compiler/typecheck/TcUnify.hs +++ b/compiler/typecheck/TcUnify.hs @@ -667,7 +667,7 @@ uType, uType_defer -- See Note [Deferred unification] uType_defer origin ty1 ty2 = do { eqv <- newEq ty1 ty2 - ; loc <- getCtLoc origin + ; loc <- getCtLocM origin ; emitSimple $ mkNonCanonical $ CtWanted { ctev_evar = eqv , ctev_pred = mkTcEqPred ty1 ty2 From git at git.haskell.org Thu Jun 18 14:18:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 Jun 2015 14:18:15 +0000 (UTC) Subject: [commit: ghc] master: Remove some horrible munging of origins for Coercible (02bac02) Message-ID: <20150618141815.74DF33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/02bac0254182def11029e2f7373ba8d2ba9ebe44/ghc >--------------------------------------------------------------- commit 02bac0254182def11029e2f7373ba8d2ba9ebe44 Author: Simon Peyton Jones Date: Thu Jun 18 14:12:54 2015 +0100 Remove some horrible munging of origins for Coercible I just didn't think it was buying enough for all the cruft it caused. We can put some back if people start complaining about poor error messages. I forget quite how I tripped over this but I got sucked in. * Lots of tidying up in TcErrors * Rename pprArisingAt to pprCtLoc, by analogy with pprCtOrigin * Remove CoercibleOrigin data constructor from CtOrigin * Make relevantBindings return a Ct with a zonked and tidied CtOrigin * Add to TcRnTypes ctOrigin :: Ct -> CtOrigin ctEvOrigin :: CtEvidence -> CtOrigin setCtLoc :: Ct -> CtLoc -> Ct >--------------------------------------------------------------- 02bac0254182def11029e2f7373ba8d2ba9ebe44 compiler/typecheck/Inst.hs | 17 +- compiler/typecheck/TcErrors.hs | 228 +++++++++++---------- compiler/typecheck/TcMType.hs | 4 - compiler/typecheck/TcRnTypes.hs | 49 +++-- testsuite/tests/deriving/should_fail/T4846.stderr | 7 +- testsuite/tests/deriving/should_fail/T5498.stderr | 9 +- testsuite/tests/deriving/should_fail/T6147.stderr | 7 +- testsuite/tests/deriving/should_fail/T7148.stderr | 22 +- testsuite/tests/deriving/should_fail/T7148a.stderr | 18 +- testsuite/tests/deriving/should_fail/T8851.stderr | 21 +- testsuite/tests/deriving/should_fail/T8984.stderr | 8 +- testsuite/tests/gadt/CasePrune.stderr | 7 +- testsuite/tests/ghci/scripts/Defer02.stderr | 64 +++--- testsuite/tests/ghci/scripts/T8649.stderr | 6 +- testsuite/tests/ghci/scripts/ghci050.stderr | 6 +- testsuite/tests/ghci/scripts/ghci051.stderr | 6 +- testsuite/tests/ghci/scripts/ghci052.stderr | 24 +-- testsuite/tests/ghci/scripts/ghci053.stderr | 12 +- .../tests/indexed-types/should_fail/T6088.stderr | 3 +- .../tests/indexed-types/should_fail/T9580.stderr | 4 +- testsuite/tests/module/mod180.stderr | 6 +- testsuite/tests/polykinds/T7438.stderr | 10 +- testsuite/tests/roles/should_fail/Roles10.stderr | 7 +- .../tests/roles/should_fail/RolesIArray.stderr | 114 ++++------- testsuite/tests/typecheck/bug1465/bug1465.stderr | 6 +- .../tests/typecheck/should_compile/FD3.stderr | 11 +- .../tests/typecheck/should_fail/T10285.stderr | 5 +- .../tests/typecheck/should_fail/T10495.stderr | 1 + .../tests/typecheck/should_fail/T10534.stderr | 5 +- testsuite/tests/typecheck/should_fail/T5853.stderr | 2 +- .../typecheck/should_fail/TcCoercibleFail.stderr | 20 +- .../typecheck/should_fail/TcCoercibleFail3.stderr | 10 +- .../tests/typecheck/should_fail/tcfail182.stderr | 7 +- 33 files changed, 332 insertions(+), 394 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 02bac0254182def11029e2f7373ba8d2ba9ebe44 From git at git.haskell.org Thu Jun 18 14:18:18 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 Jun 2015 14:18:18 +0000 (UTC) Subject: [commit: ghc] master: A bit more tracing (760b079) Message-ID: <20150618141818.4516C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/760b079dfe8cad65c341c21cee395ad4835543f0/ghc >--------------------------------------------------------------- commit 760b079dfe8cad65c341c21cee395ad4835543f0 Author: Simon Peyton Jones Date: Thu Jun 18 14:13:24 2015 +0100 A bit more tracing >--------------------------------------------------------------- 760b079dfe8cad65c341c21cee395ad4835543f0 compiler/typecheck/TcSMonad.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/compiler/typecheck/TcSMonad.hs b/compiler/typecheck/TcSMonad.hs index c131f61..d537328 100644 --- a/compiler/typecheck/TcSMonad.hs +++ b/compiler/typecheck/TcSMonad.hs @@ -1420,7 +1420,7 @@ Note [Kick out insolubles] ~~~~~~~~~~~~~~~~~~~~~~~~~~ Suppose we have an insoluble alpha ~ [alpha], which is insoluble because an occurs check. And then we unify alpha := [Int]. -Then we really want to rewrite the insouluble to [Int] ~ [[Int]]. +Then we really want to rewrite the insoluble to [Int] ~ [[Int]]. Now it can be decomposed. Otherwise we end up with a "Can't match [Int] ~ [[Int]]" which is true, but a bit confusing because the outer type constructors match. @@ -2378,7 +2378,7 @@ emitWorkCt ct emitInsoluble :: Ct -> TcS () -- Emits a non-canonical constraint that will stand for a frozen error in the inerts. emitInsoluble ct - = do { traceTcS "Emit insoluble" (ppr ct) + = do { traceTcS "Emit insoluble" (ppr ct $$ pprCtLoc (ctLoc ct)) ; updInertTcS add_insol } where this_pred = ctPred ct @@ -2748,6 +2748,7 @@ newWantedEvVarNC :: CtLoc -> TcPredType -> TcS CtEvidence newWantedEvVarNC loc pty = do { -- checkReductionDepth loc pty ; new_ev <- newEvVar pty + ; traceTcS "Emitting new wanted" (ppr new_ev $$ pprCtLoc loc) ; return (CtWanted { ctev_pred = pty, ctev_evar = new_ev, ctev_loc = loc })} newWantedEvVar :: CtLoc -> TcPredType -> TcS (CtEvidence, Freshness) @@ -2759,7 +2760,6 @@ newWantedEvVar loc pty -> do { traceTcS "newWantedEvVar/cache hit" $ ppr ctev ; return (ctev, Cached) } _ -> do { ctev <- newWantedEvVarNC loc pty - ; traceTcS "newWantedEvVar/cache miss" $ ppr ctev ; return (ctev, Fresh) } } emitNewDerived :: CtLoc -> TcPredType -> TcS () @@ -2782,7 +2782,7 @@ emitNewDerivedEq :: CtLoc -> TcPredType -> TcS () -- There's no caching, no lookupInInerts emitNewDerivedEq loc pred = do { ev <- newDerivedNC loc pred - ; traceTcS "Emitting new derived equality" (ppr ev) + ; traceTcS "Emitting new derived equality" (ppr ev $$ pprCtLoc loc) ; updWorkListTcS (extendWorkListDerived loc ev) } newDerivedNC :: CtLoc -> TcPredType -> TcS CtEvidence From git at git.haskell.org Thu Jun 18 14:18:20 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 Jun 2015 14:18:20 +0000 (UTC) Subject: [commit: ghc] master: Comments plus tiny refactoring (0899911) Message-ID: <20150618141821.0056B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0899911cf65142552848c18dd86bc0a4db8a26a1/ghc >--------------------------------------------------------------- commit 0899911cf65142552848c18dd86bc0a4db8a26a1 Author: Simon Peyton Jones Date: Thu Jun 18 14:14:01 2015 +0100 Comments plus tiny refactoring >--------------------------------------------------------------- 0899911cf65142552848c18dd86bc0a4db8a26a1 compiler/typecheck/TcCanonical.hs | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index be07401..9bd2f70 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -882,15 +882,19 @@ canDecomposableTyConAppOK ev eq_rel tc tys1 tys2 -- Examples in Note [Use canEqFailure in canDecomposableTyConApp] canEqFailure :: CtEvidence -> EqRel -> TcType -> TcType -> TcS (StopOrContinue Ct) +canEqFailure ev NomEq ty1 ty2 + = canEqHardFailure ev NomEq ty1 ty2 canEqFailure ev ReprEq ty1 ty2 = do { (xi1, co1) <- flatten FM_FlattenAll ev ty1 ; (xi2, co2) <- flatten FM_FlattenAll ev ty2 + -- We must flatten the types before putting them in the + -- inert set, so that we are sure to kick them out when + -- new equalities become available ; traceTcS "canEqFailure with ReprEq" $ vcat [ ppr ev, ppr ty1, ppr ty2, ppr xi1, ppr xi2 ] ; rewriteEqEvidence ev ReprEq NotSwapped xi1 xi2 co1 co2 `andWhenContinue` \ new_ev -> continueWith (CIrredEvCan { cc_ev = new_ev }) } -canEqFailure ev NomEq ty1 ty2 = canEqHardFailure ev NomEq ty1 ty2 -- | Call when canonicalizing an equality fails with utterly no hope. canEqHardFailure :: CtEvidence -> EqRel @@ -948,7 +952,7 @@ When an equality fails, we still want to rewrite the equality all the way down, so that it accurately reflects (a) the mutable reference substitution in force at start of solving (b) any ty-binds in force at this point in solving -See Note [Kick out insolubles] in TcInteract. +See Note [Kick out insolubles] in TcSMonad. And if we don't do this there is a bad danger that TcSimplify.applyTyVarDefaulting will find a variable that has in fact been substituted. From git at git.haskell.org Thu Jun 18 14:18:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 Jun 2015 14:18:23 +0000 (UTC) Subject: [commit: ghc] master: Refactor filterAlts into two parts (ee64369) Message-ID: <20150618141823.CBD283A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ee64369828f505fd6f53ddcbbb9ad4e08aa78800/ghc >--------------------------------------------------------------- commit ee64369828f505fd6f53ddcbbb9ad4e08aa78800 Author: Simon Peyton Jones Date: Thu Jun 18 15:16:59 2015 +0100 Refactor filterAlts into two parts This splits filterAlts into two: - filterAlts - refineDefaultAlt No change in functionality >--------------------------------------------------------------- ee64369828f505fd6f53ddcbbb9ad4e08aa78800 compiler/coreSyn/CoreUtils.hs | 247 ++++++++++++++++++++++++++------------- compiler/simplCore/SimplUtils.hs | 106 ++--------------- 2 files changed, 177 insertions(+), 176 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ee64369828f505fd6f53ddcbbb9ad4e08aa78800 From git at git.haskell.org Thu Jun 18 14:18:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 Jun 2015 14:18:26 +0000 (UTC) Subject: [commit: ghc] master: Trac #4945 is working again (5d98b68) Message-ID: <20150618141826.87CDA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5d98b6828f65ce6eea45e93880928b7031955d38/ghc >--------------------------------------------------------------- commit 5d98b6828f65ce6eea45e93880928b7031955d38 Author: Simon Peyton Jones Date: Thu Jun 18 15:18:19 2015 +0100 Trac #4945 is working again This test greps in the ouput of -ddump-simpl, so it's fragile. It stopped working for a while, but now works again. I don't know why, but I don't have time to investigate, so I'll just mark it as ok. >--------------------------------------------------------------- 5d98b6828f65ce6eea45e93880928b7031955d38 testsuite/tests/simplCore/should_compile/all.T | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/simplCore/should_compile/all.T b/testsuite/tests/simplCore/should_compile/all.T index f7ff85b..3a8a6e1 100644 --- a/testsuite/tests/simplCore/should_compile/all.T +++ b/testsuite/tests/simplCore/should_compile/all.T @@ -107,7 +107,7 @@ test('T4918', ['$MAKE -s --no-print-directory T4918']) test('T4945', - expect_broken(4945), + normal, run_command, ['$MAKE -s --no-print-directory T4945']) From git at git.haskell.org Thu Jun 18 14:19:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 Jun 2015 14:19:31 +0000 (UTC) Subject: [commit: ghc] master: Parser: commas_tup_tail duplicate SrcSpan on "Missing" value (72b21c3) Message-ID: <20150618141931.541543A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/72b21c393831b49867a296f19a2d039e48bb8dcd/ghc >--------------------------------------------------------------- commit 72b21c393831b49867a296f19a2d039e48bb8dcd Author: Alan Zimmerman Date: Thu Jun 18 16:19:50 2015 +0200 Parser: commas_tup_tail duplicate SrcSpan on "Missing" value Summary: Parsing {-# LANGUAGE TupleSections #-} baz = (1, "hello", 6.5,,) 'a' (Just ()) Results in the following AST fragment (L tests/examples/Tuple.hs:3:7-25 (ExplicitTuple [ L tests/examples/Tuple.hs:3:8 (Present (L tests/examples/Tuple.hs:3:8 (HsOverLit (OverLit (HsIntegral [ '1' ] 1) PlaceHolder (HsLit (HsString [] {abstract:FastString})) PlaceHolder)))) , L tests/examples/Tuple.hs:3:11-17 (Present (L tests/examples/Tuple.hs:3:11-17 (HsLit (HsString [ '"' , 'h' , 'e' , 'l' , 'l' , 'o' , '"' ] {abstract:FastString})))) , L tests/examples/Tuple.hs:3:20-22 (Present (L tests/examples/Tuple.hs:3:20-22 (HsOverLit (OverLit (HsFractional (FL [ '6' , '.' , '5' ] (:% 13 2))) PlaceHolder (HsLit (HsString [] {abstract:FastString})) PlaceHolder)))) , L tests/examples/Tuple.hs:3:24 (Missing PlaceHolder) , L tests/examples/Tuple.hs:3:24 (Missing PlaceHolder) ] The final `Missing PlaceHolder` has a duplicated `SrcSpan` Test Plan: ./validate Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: thomie, bgamari, mpickering Differential Revision: https://phabricator.haskell.org/D995 GHC Trac Issues: #10537 >--------------------------------------------------------------- 72b21c393831b49867a296f19a2d039e48bb8dcd compiler/parser/Parser.y | 14 ++++---------- testsuite/tests/ghc-api/annotations/exampleTest.stdout | 3 +-- testsuite/tests/ghc-api/annotations/parseTree.stdout | 3 +-- 3 files changed, 6 insertions(+), 14 deletions(-) diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y index 682b342..5414735 100644 --- a/compiler/parser/Parser.y +++ b/compiler/parser/Parser.y @@ -2386,28 +2386,22 @@ tup_exprs :: { [LHsTupArg RdrName] } | commas tup_tail {% do { mapM_ (\ll -> addAnnotation ll AnnComma ll) (fst $1) ; return - (let tt = if null $2 - then [noLoc missingTupArg] - else $2 - in map (\l -> L l missingTupArg) (fst $1) ++ tt) } } + (map (\l -> L l missingTupArg) (fst $1) ++ $2) } } -- Always starts with commas; always follows an expr commas_tup_tail :: { (SrcSpan,[LHsTupArg RdrName]) } commas_tup_tail : commas tup_tail {% do { mapM_ (\ll -> addAnnotation ll AnnComma ll) (tail $ fst $1) ; return ( - let tt = if null $2 - then [L (last $ fst $1) missingTupArg] - else $2 - in (head $ fst $1 - ,(map (\l -> L l missingTupArg) (tail $ fst $1)) ++ tt)) } } + (head $ fst $1 + ,(map (\l -> L l missingTupArg) (tail $ fst $1)) ++ $2)) } } -- Always follows a comma tup_tail :: { [LHsTupArg RdrName] } : texp commas_tup_tail {% addAnnotation (gl $1) AnnComma (fst $2) >> return ((L (gl $1) (Present $1)) : snd $2) } | texp { [L (gl $1) (Present $1)] } - | {- empty -} { [] {- [noLoc missingTupArg] -} } + | {- empty -} { [noLoc missingTupArg] } ----------------------------------------------------------------------------- -- List expressions diff --git a/testsuite/tests/ghc-api/annotations/exampleTest.stdout b/testsuite/tests/ghc-api/annotations/exampleTest.stdout index cd6f9c0..210a4d8 100644 --- a/testsuite/tests/ghc-api/annotations/exampleTest.stdout +++ b/testsuite/tests/ghc-api/annotations/exampleTest.stdout @@ -1,10 +1,9 @@ ---Problems--------------------- [ -(AK AnnEofPos = [AnnotationTuple.hs:32:1]) ] ---Problems'-------------------- -[(AnnEofPos, AnnotationTuple.hs:32:1)] +[] -------------------------------- [ (AK AnnotationTuple.hs:1:1 AnnCloseC = [AnnotationTuple.hs:27:1]) diff --git a/testsuite/tests/ghc-api/annotations/parseTree.stdout b/testsuite/tests/ghc-api/annotations/parseTree.stdout index f7d1e5d..7d651aa 100644 --- a/testsuite/tests/ghc-api/annotations/parseTree.stdout +++ b/testsuite/tests/ghc-api/annotations/parseTree.stdout @@ -8,8 +8,7 @@ (AnnotationTuple.hs:16:20-22, [p], (6.5)), (AnnotationTuple.hs:16:24, [m], ()), (AnnotationTuple.hs:16:25, [m], ()), - (AnnotationTuple.hs:16:26, [m], ()), - (AnnotationTuple.hs:16:26, [m], ())] + (AnnotationTuple.hs:16:26, [m], ()), (, [m], ())] [ (AK AnnotationTuple.hs:1:1 AnnCloseC = [AnnotationTuple.hs:27:1]) From git at git.haskell.org Thu Jun 18 14:45:24 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 Jun 2015 14:45:24 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #10503 (ba7c8e5) Message-ID: <20150618144524.A38203A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ba7c8e5919411f84bdc84caa60317b0cb6c5cdc5/ghc >--------------------------------------------------------------- commit ba7c8e5919411f84bdc84caa60317b0cb6c5cdc5 Author: Simon Peyton Jones Date: Thu Jun 18 15:45:22 2015 +0100 Test Trac #10503 >--------------------------------------------------------------- ba7c8e5919411f84bdc84caa60317b0cb6c5cdc5 testsuite/tests/polykinds/T10503.hs | 9 +++++++++ testsuite/tests/polykinds/T10503.stderr | 16 ++++++++++++++++ testsuite/tests/polykinds/all.T | 1 + 3 files changed, 26 insertions(+) diff --git a/testsuite/tests/polykinds/T10503.hs b/testsuite/tests/polykinds/T10503.hs new file mode 100644 index 0000000..2cc1ee7 --- /dev/null +++ b/testsuite/tests/polykinds/T10503.hs @@ -0,0 +1,9 @@ +{-# LANGUAGE RankNTypes, PolyKinds, DataKinds, TypeFamilies #-} +module GHCBug where + +data Proxy p = Proxy + +data KProxy (a :: *) = KProxy + +h :: forall r . (Proxy ('KProxy :: KProxy k) ~ Proxy ('KProxy :: KProxy *) => r) -> r +h = undefined diff --git a/testsuite/tests/polykinds/T10503.stderr b/testsuite/tests/polykinds/T10503.stderr new file mode 100644 index 0000000..e2817fe --- /dev/null +++ b/testsuite/tests/polykinds/T10503.stderr @@ -0,0 +1,16 @@ + +T10503.hs:8:6: error: + Couldn't match kind ?k? with ?*? + ?k? is a rigid type variable bound by + the type signature for: + h :: ((Proxy 'KProxy ~ Proxy 'KProxy) => r) -> r + at T10503.hs:8:6 + Expected type: Proxy 'KProxy + Actual type: Proxy 'KProxy + In the ambiguity check for the type signature for ?h?: + h :: forall (k :: BOX) r. + ((Proxy 'KProxy ~ Proxy 'KProxy) => r) -> r + To defer the ambiguity check to use sites, enable AllowAmbiguousTypes + In the type signature for ?h?: + h :: forall r. + (Proxy (KProxy :: KProxy k) ~ Proxy (KProxy :: KProxy *) => r) -> r diff --git a/testsuite/tests/polykinds/all.T b/testsuite/tests/polykinds/all.T index 76af3ec..95f0d83 100644 --- a/testsuite/tests/polykinds/all.T +++ b/testsuite/tests/polykinds/all.T @@ -117,3 +117,4 @@ test('T7908', normal, compile, ['']) test('T10041', normal, compile, ['']) test('T10451', normal, compile_fail, ['']) test('T10516', normal, compile_fail, ['']) +test('T10503', normal, compile_fail, ['']) From git at git.haskell.org Thu Jun 18 14:46:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 Jun 2015 14:46:38 +0000 (UTC) Subject: [commit: ghc] wip/impredicativity: Work on constraint generation for impredicativity (0696ce2) Message-ID: <20150618144638.0FA793A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/impredicativity Link : http://ghc.haskell.org/trac/ghc/changeset/0696ce2400dbda332cea35ad7b535f1d9b9594b6/ghc >--------------------------------------------------------------- commit 0696ce2400dbda332cea35ad7b535f1d9b9594b6 Author: Alejandro Serrano Date: Thu Jun 18 15:33:58 2015 +0200 Work on constraint generation for impredicativity This is preliminary work, right now the compiler crashes because desugaring has not been yet implemented. Generation for patterns has not been updated either, it defaults to considering all variables monomorphic. >--------------------------------------------------------------- 0696ce2400dbda332cea35ad7b535f1d9b9594b6 compiler/typecheck/Inst.hs | 4 +- compiler/typecheck/TcArrows.hs | 14 +- compiler/typecheck/TcBinds.hs | 4 +- compiler/typecheck/TcEvidence.hs | 13 +- compiler/typecheck/TcExpr.hs | 264 +++++++++++++++++++++----------------- compiler/typecheck/TcExpr.hs-boot | 7 +- compiler/typecheck/TcForeign.hs | 2 +- compiler/typecheck/TcHsSyn.hs | 20 +++ compiler/typecheck/TcMatches.hs | 36 +++--- compiler/typecheck/TcRnDriver.hs | 2 +- compiler/typecheck/TcRules.hs | 2 +- compiler/typecheck/TcSplice.hs | 10 +- 12 files changed, 217 insertions(+), 161 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 0696ce2400dbda332cea35ad7b535f1d9b9594b6 From git at git.haskell.org Thu Jun 18 14:46:40 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 Jun 2015 14:46:40 +0000 (UTC) Subject: [commit: ghc] wip/impredicativity: Add reflexivity rule for InstanceOf (e33535a) Message-ID: <20150618144640.B45B13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/impredicativity Link : http://ghc.haskell.org/trac/ghc/changeset/e33535a3af2c5b146cd8837aa00dee37867994df/ghc >--------------------------------------------------------------- commit e33535a3af2c5b146cd8837aa00dee37867994df Author: Alejandro Serrano Date: Thu Jun 18 16:46:39 2015 +0200 Add reflexivity rule for InstanceOf >--------------------------------------------------------------- e33535a3af2c5b146cd8837aa00dee37867994df compiler/typecheck/TcCanonical.hs | 31 +++++++++++++++++++------------ 1 file changed, 19 insertions(+), 12 deletions(-) diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index d1c56cf..785d61b 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -1657,20 +1657,13 @@ canInstanceOf ev ; return (fmap mk_ct mb) } can_instance_of :: Ct -> TcS (StopOrContinue Ct) -can_instance_of ct@(CInstanceOfCan { cc_ev = ev, cc_lhs = lhs, cc_rhs = rhs }) +can_instance_of (CInstanceOfCan { cc_ev = ev, cc_lhs = lhs, cc_rhs = rhs }) + -- case InstanceOf sigma sigma, for the exact same sigma + | lhs `eqType` rhs + = can_instance_to_eq ev lhs rhs -- case InstanceOf sigma (T ...) --> sigma ~ T ... | Nothing <- getTyVar_maybe rhs, Nothing <- splitForAllTy_maybe rhs - = do { let eq = mkTcEqPredRole Nominal lhs rhs - ; case ev of - CtDerived {} -> canEqNC (ev { ctev_pred = eq }) NomEq lhs rhs - CtGiven {ctev_loc = loc } -> - do { emitNewDerivedEq loc eq - ; stopWith ev "Given instanceOf equality" } - CtWanted { ctev_evar = evar, ctev_loc = loc } -> - do { new_ev <- newWantedEvVarNC loc eq - ; setWantedEvBind evar (mkInstanceOfEq (ctEvCoercion new_ev)) - ; canEqNC new_ev NomEq lhs rhs } } - + = can_instance_to_eq ev lhs rhs -- case InstanceOf (T ...) (forall qvars. Q => ty) | Nothing <- getTyVar_maybe lhs, Nothing <- splitForAllTy_maybe lhs , Just _ <- splitForAllTy_maybe rhs @@ -1688,3 +1681,17 @@ can_instance_of ct@(CInstanceOfCan { cc_ev = ev, cc_lhs = lhs, cc_rhs = rhs }) ; emitWorkNC new_ev_qs ; canEqNC new_ev_ty NomEq lhs ty } _ -> stopWith ev "Given/Derived instanceOf instantiation" +can_instance_of _ = panic "can_instance_of in a non InstanceOf constraint" + +can_instance_to_eq :: CtEvidence -> TcType -> TcType -> TcS (StopOrContinue Ct) +can_instance_to_eq ev lhs rhs + = do { let eq = mkTcEqPredRole Nominal lhs rhs + ; case ev of + CtDerived {} -> canEqNC (ev { ctev_pred = eq }) NomEq lhs rhs + CtGiven {ctev_loc = loc } -> + do { emitNewDerivedEq loc eq + ; stopWith ev "Given instanceOf equality" } + CtWanted { ctev_evar = evar, ctev_loc = loc } -> + do { new_ev <- newWantedEvVarNC loc eq + ; setWantedEvBind evar (mkInstanceOfEq (ctEvCoercion new_ev)) + ; canEqNC new_ev NomEq lhs rhs } } From git at git.haskell.org Thu Jun 18 15:34:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 Jun 2015 15:34:48 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Care with impossible-cons in combineIdenticalAlts (558eb05) Message-ID: <20150618153448.76AD63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/558eb05053f2cec20acca1e0a244094c46048bdc/ghc >--------------------------------------------------------------- commit 558eb05053f2cec20acca1e0a244094c46048bdc Author: Simon Peyton Jones Date: Thu Jun 18 08:51:08 2015 +0100 Care with impossible-cons in combineIdenticalAlts This was a nasty, long-standing bug exposed in Trac #10538. Symptoms were that we had an empty case case (x :: Either a) of {} Core Lint correctly picked this bogus code up. Here is what happened * In SimplUtils.prepareAlts, we call filterAlts then combineIdenticalAlts * We had case x of { Left _ -> e1; Right _ -> e1 } * filterAlts did nothing, but correctly retuned imposs_deflt_cons saying that 'x' cannot be {Left, Right} in the DEFAULT branch, if any (there isn't one.) * combineIdentialAlts correctly combines the identical alts, to give case x of { DEFAULT -> e1 } * BUT combineIdenticalAlts did no adjust imposs_deft_cons * Result: when compiling e1 we did so in the belief that 'x' could not be {Left,Right}. Disaster. Easily fixed. (It is hard to trigger; I can't construct a simple test case.) (cherry picked from commit 023a0ba938b69bbb89cb2ce48a07459b07783391) >--------------------------------------------------------------- 558eb05053f2cec20acca1e0a244094c46048bdc compiler/simplCore/SimplUtils.hs | 59 +++++++++++++++++++++++++++++----------- 1 file changed, 43 insertions(+), 16 deletions(-) diff --git a/compiler/simplCore/SimplUtils.hs b/compiler/simplCore/SimplUtils.hs index 115d249..a768be4 100644 --- a/compiler/simplCore/SimplUtils.hs +++ b/compiler/simplCore/SimplUtils.hs @@ -62,6 +62,7 @@ import MonadUtils import Outputable import FastString import Pair +import ListSetOps ( minusList ) import Control.Monad ( when ) import Data.List ( partition ) @@ -1669,23 +1670,23 @@ prepareAlts scrut case_bndr' alts -- OutId, it has maximum information; this is important. -- Test simpl013 is an example = do { us <- getUniquesM - ; let (imposs_deflt_cons, refined_deflt, alts') + ; let (imposs_deflt_cons', refined_deflt, alts') = filterAlts us (varType case_bndr') imposs_cons alts - ; when refined_deflt $ tick (FillInCaseDefault case_bndr') - - ; alts'' <- combineIdenticalAlts case_bndr' alts' - ; return (imposs_deflt_cons, alts'') } + (combining_done, imposs_deflt_cons'', alts'') + = combineIdenticalAlts imposs_deflt_cons' alts' + ; when refined_deflt $ tick (FillInCaseDefault case_bndr') + ; when combining_done $ tick (AltMerge case_bndr') + ; return (imposs_deflt_cons'', alts'') } where imposs_cons = case scrut of Var v -> otherCons (idUnfolding v) _ -> [] -{- -Note [Combine identical alternatives] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ - If several alternatives are identical, merge them into - a single DEFAULT alternative. I've occasionally seen this - making a big difference: +{- Note [Combine identical alternatives] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +If several alternatives are identical, merge them into a single +DEFAULT alternative. I've occasionally seen this making a big +difference: case e of =====> case e of C _ -> f x D v -> ....v.... @@ -1723,23 +1724,49 @@ NB: it's important that all this is done in [InAlt], *before* we work on the alternatives themselves, because Simpify.simplAlt may zap the occurrence info on the binders in the alternatives, which in turn defeats combineIdenticalAlts (see Trac #7360). + +Note [Care with impossible-constructors when combining alternatives] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Suppose we have (Trac #10538) + data T = A | B | C + + ... case x::T of + DEFAULT -> e1 + A -> e2 + B -> e1 + +When calling combineIdentialAlts, we'll have computed that the "impossible +constructors" for the DEFAULT alt is {A,B}, since if x is A or B we'll +take the other alternatives. But suppose we combine B into the DEFAULT, +to get + ... case x::T of + DEFAULT -> e1 + A -> e2 +Then we must be careful to trim the impossible constructors to just {A}, +else we risk compiling 'e1' wrong! -} -combineIdenticalAlts :: OutId -> [InAlt] -> SimplM [InAlt] + +combineIdenticalAlts :: [AltCon] -> [InAlt] -> (Bool, [AltCon], [InAlt]) -- See Note [Combine identical alternatives] -combineIdenticalAlts case_bndr ((_con1,bndrs1,rhs1) : con_alts) +-- See Note [Care with impossible-constructors when combining alternatives] +-- True <=> we did some combining, result is a single DEFAULT alternative +combineIdenticalAlts imposs_cons ((_con1,bndrs1,rhs1) : con_alts) | all isDeadBinder bndrs1 -- Remember the default , not (null eliminated_alts) -- alternative comes first - = do { tick (AltMerge case_bndr) - ; return ((DEFAULT, [], mkTicks (concat tickss) rhs1) : filtered_alts) } + = (True, imposs_cons', deflt_alt : filtered_alts) where (eliminated_alts, filtered_alts) = partition identical_to_alt1 con_alts + deflt_alt = (DEFAULT, [], mkTicks (concat tickss) rhs1) + imposs_cons' = imposs_cons `minusList` map fstOf3 eliminated_alts + cheapEqTicked e1 e2 = cheapEqExpr' tickishFloatable e1 e2 identical_to_alt1 (_con,bndrs,rhs) = all isDeadBinder bndrs && rhs `cheapEqTicked` rhs1 tickss = map (stripTicksT tickishFloatable . thirdOf3) eliminated_alts -combineIdenticalAlts _ alts = return alts +combineIdenticalAlts imposs_cons alts + = (False, imposs_cons, alts) {- ************************************************************************ From git at git.haskell.org Thu Jun 18 15:34:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 Jun 2015 15:34:51 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Revert "Look inside synonyms for foralls when unifying" (8fb101e) Message-ID: <20150618153451.3D5543A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/8fb101e49b86c0f8bb8931620c9c3cd3e6c57228/ghc >--------------------------------------------------------------- commit 8fb101e49b86c0f8bb8931620c9c3cd3e6c57228 Author: Austin Seipp Date: Thu Jun 18 10:34:28 2015 -0500 Revert "Look inside synonyms for foralls when unifying" As discussed in #10194, this patch - while fixing a bug - also causes a minor regression when compiling certain in-the-wild programs, meaning some extant programs now failed with 7.10.2 RC1. Womp womp. This reverts commit 681d82c0d44f06f0b958b75778c30b0910df982b. >--------------------------------------------------------------- 8fb101e49b86c0f8bb8931620c9c3cd3e6c57228 compiler/typecheck/TcType.hs | 10 +++------- compiler/typecheck/TcUnify.hs | 5 +---- testsuite/tests/typecheck/should_fail/T10194.hs | 7 ------- testsuite/tests/typecheck/should_fail/T10194.stderr | 7 ------- testsuite/tests/typecheck/should_fail/all.T | 1 - 5 files changed, 4 insertions(+), 26 deletions(-) diff --git a/compiler/typecheck/TcType.hs b/compiler/typecheck/TcType.hs index 41db197..a5a5075 100644 --- a/compiler/typecheck/TcType.hs +++ b/compiler/typecheck/TcType.hs @@ -853,7 +853,7 @@ mkTcEqPredRole Nominal = mkTcEqPred mkTcEqPredRole Representational = mkTcReprEqPred mkTcEqPredRole Phantom = panic "mkTcEqPredRole Phantom" --- @isTauTy@ tests for nested for-alls. +-- @isTauTy@ tests for nested for-alls. It should not be called on a boxy type. isTauTy :: Type -> Bool isTauTy ty | Just ty' <- tcView ty = isTauTy ty' @@ -1228,7 +1228,7 @@ occurCheckExpand dflags tv ty -- True => fine fast_check (LitTy {}) = True fast_check (TyVarTy tv') = tv /= tv' - fast_check (TyConApp tc tys) = all fast_check tys && (isTauTyCon tc || impredicative) + fast_check (TyConApp _ tys) = all fast_check tys fast_check (FunTy arg res) = fast_check arg && fast_check res fast_check (AppTy fun arg) = fast_check fun && fast_check arg fast_check (ForAllTy tv' ty) = impredicative @@ -1262,11 +1262,7 @@ occurCheckExpand dflags tv ty -- it and try again. go ty@(TyConApp tc tys) = case do { tys <- mapM go tys; return (mkTyConApp tc tys) } of - OC_OK ty - | impredicative || isTauTyCon tc - -> return ty -- First try to eliminate the tyvar from the args - | otherwise - -> OC_Forall -- A type synonym with a forall on the RHS + OC_OK ty -> return ty -- First try to eliminate the tyvar from the args bad | Just ty' <- tcView ty -> go ty' | otherwise -> bad -- Failing that, try to expand a synonym diff --git a/compiler/typecheck/TcUnify.hs b/compiler/typecheck/TcUnify.hs index ef21d87..b4a6ada 100644 --- a/compiler/typecheck/TcUnify.hs +++ b/compiler/typecheck/TcUnify.hs @@ -1012,13 +1012,10 @@ checkTauTvUpdate dflags tv ty defer_me :: TcType -> Bool -- Checks for (a) occurrence of tv -- (b) type family applications - -- (c) foralls -- See Note [Conservative unification check] defer_me (LitTy {}) = False defer_me (TyVarTy tv') = tv == tv' - defer_me (TyConApp tc tys) = isTypeFamilyTyCon tc - || any defer_me tys - || not (impredicative || isTauTyCon tc) + defer_me (TyConApp tc tys) = isTypeFamilyTyCon tc || any defer_me tys defer_me (FunTy arg res) = defer_me arg || defer_me res defer_me (AppTy fun arg) = defer_me fun || defer_me arg defer_me (ForAllTy _ ty) = not impredicative || defer_me ty diff --git a/testsuite/tests/typecheck/should_fail/T10194.hs b/testsuite/tests/typecheck/should_fail/T10194.hs deleted file mode 100644 index 2174a59..0000000 --- a/testsuite/tests/typecheck/should_fail/T10194.hs +++ /dev/null @@ -1,7 +0,0 @@ -{-# LANGUAGE RankNTypes #-} -module T10194 where - -type X = forall a . a - -comp :: (X -> c) -> (a -> X) -> (a -> c) -comp = (.) diff --git a/testsuite/tests/typecheck/should_fail/T10194.stderr b/testsuite/tests/typecheck/should_fail/T10194.stderr deleted file mode 100644 index 53ee74b..0000000 --- a/testsuite/tests/typecheck/should_fail/T10194.stderr +++ /dev/null @@ -1,7 +0,0 @@ - -T10194.hs:7:8: - Cannot instantiate unification variable ?b0? - with a type involving foralls: X - Perhaps you want ImpredicativeTypes - In the expression: (.) - In an equation for ?comp?: comp = (.) diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index 31b6a5f..95911d1 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -354,7 +354,6 @@ test('T8044', normal, compile_fail, ['']) test('T4921', normal, compile_fail, ['']) test('T9605', normal, compile_fail, ['']) test('T9999', normal, compile_fail, ['']) -test('T10194', normal, compile_fail, ['']) test('T10285', extra_clean(['T10285a.hi', 'T10285a.o']), From git at git.haskell.org Thu Jun 18 22:26:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 18 Jun 2015 22:26:44 +0000 (UTC) Subject: [commit: ghc] master: Elaborate test for Trac #10403 (c45f8ce) Message-ID: <20150618222644.91DCE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c45f8ceb0de0f83d374909f4cb8dd411154e2bce/ghc >--------------------------------------------------------------- commit c45f8ceb0de0f83d374909f4cb8dd411154e2bce Author: Simon Peyton Jones Date: Thu Jun 18 23:26:48 2015 +0100 Elaborate test for Trac #10403 >--------------------------------------------------------------- c45f8ceb0de0f83d374909f4cb8dd411154e2bce .../tests/partial-sigs/should_compile/T10403.hs | 10 +++++--- .../partial-sigs/should_compile/T10403.stderr | 29 ++++++++++++++++++---- 2 files changed, 30 insertions(+), 9 deletions(-) diff --git a/testsuite/tests/partial-sigs/should_compile/T10403.hs b/testsuite/tests/partial-sigs/should_compile/T10403.hs index a33646d..6b77e5b 100644 --- a/testsuite/tests/partial-sigs/should_compile/T10403.hs +++ b/testsuite/tests/partial-sigs/should_compile/T10403.hs @@ -1,4 +1,5 @@ {-# LANGUAGE PartialTypeSignatures #-} +{-# OPTIONS_GHC -fdefer-type-errors #-} module T10403 where data I a = I a @@ -11,9 +12,10 @@ instance Functor (B t) where newtype H f = H (f ()) -app :: H (B t) -app = h (H . I) (B ()) - h :: _ => _ ---h :: Functor m => (a -> b) -> m a -> H m +-- h :: Functor m => (a -> b) -> m a -> H m h f b = (H . fmap (const ())) (fmap f b) + +h2 :: _ +-- h2 :: Functor m => (a -> b) -> m a -> H m +h2 f b = (H . fmap (const ())) (fmap f b) diff --git a/testsuite/tests/partial-sigs/should_compile/T10403.stderr b/testsuite/tests/partial-sigs/should_compile/T10403.stderr index 6b0660d..fb78b56 100644 --- a/testsuite/tests/partial-sigs/should_compile/T10403.stderr +++ b/testsuite/tests/partial-sigs/should_compile/T10403.stderr @@ -1,17 +1,36 @@ -T10403.hs:17:6: warning: +T10403.hs:15:6: warning: Found hole ?_? with inferred constraints: Functor f In the type signature for ?h?: _ => _ -T10403.hs:17:11: warning: +T10403.hs:15:11: warning: Found hole ?_? with type: (a -> b) -> f a -> H f Where: ?f? is a rigid type variable bound by the inferred type of h :: Functor f => (a -> b) -> f a -> H f - at T10403.hs:19:1 + at T10403.hs:17:1 ?b? is a rigid type variable bound by the inferred type of h :: Functor f => (a -> b) -> f a -> H f - at T10403.hs:19:1 + at T10403.hs:17:1 ?a? is a rigid type variable bound by the inferred type of h :: Functor f => (a -> b) -> f a -> H f - at T10403.hs:19:1 + at T10403.hs:17:1 In the type signature for ?h?: _ => _ + +T10403.hs:19:7: warning: + Found hole ?_? with type: (a -> b) -> f a -> H f + Where: ?f? is a rigid type variable bound by + the inferred type of h2 :: Functor f => (a -> b) -> f a -> H f + at T10403.hs:21:1 + ?b? is a rigid type variable bound by + the inferred type of h2 :: Functor f => (a -> b) -> f a -> H f + at T10403.hs:21:1 + ?a? is a rigid type variable bound by + the inferred type of h2 :: Functor f => (a -> b) -> f a -> H f + at T10403.hs:21:1 + In the type signature for ?h2?: _ + +T10403.hs:21:1: warning: + No instance for (Functor f) + When checking that ?h2? has the inferred type + h2 :: forall (f :: * -> *) b a. (a -> b) -> f a -> H f + Probable cause: the inferred type is ambiguous From git at git.haskell.org Fri Jun 19 11:49:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 19 Jun 2015 11:49:31 +0000 (UTC) Subject: [commit: ghc] wip/impredicativity: Implement desugaring of InstanceOf constraints (3ee32bf) Message-ID: <20150619114931.702673A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/impredicativity Link : http://ghc.haskell.org/trac/ghc/changeset/3ee32bfbe717e870dd10e4432d6762a433f8d021/ghc >--------------------------------------------------------------- commit 3ee32bfbe717e870dd10e4432d6762a433f8d021 Author: Alejandro Serrano Date: Fri Jun 19 12:53:41 2015 +0200 Implement desugaring of InstanceOf constraints Code does not yet work because of typing problems in the desugaring to Core. >--------------------------------------------------------------- 3ee32bfbe717e870dd10e4432d6762a433f8d021 compiler/deSugar/DsBinds.hs | 18 +++++++++++++++++ compiler/typecheck/TcCanonical.hs | 7 ++++--- compiler/typecheck/TcEvidence.hs | 41 +++++++++++++++++++-------------------- compiler/typecheck/TcExpr.hs | 4 ++-- compiler/typecheck/TcHsSyn.hs | 20 ++++++++++--------- 5 files changed, 55 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 3ee32bfbe717e870dd10e4432d6762a433f8d021 From git at git.haskell.org Fri Jun 19 11:49:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 19 Jun 2015 11:49:34 +0000 (UTC) Subject: [commit: ghc] wip/impredicativity: Switch the order of arguments in InstanceOf (30e9fa2) Message-ID: <20150619114934.2B3243A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/impredicativity Link : http://ghc.haskell.org/trac/ghc/changeset/30e9fa281cae44ae56a1cd19378e375282cd95a1/ghc >--------------------------------------------------------------- commit 30e9fa281cae44ae56a1cd19378e375282cd95a1 Author: Alejandro Serrano Date: Fri Jun 19 13:29:40 2015 +0200 Switch the order of arguments in InstanceOf In that way, we can make InstanceOf = (->) at zonking stage >--------------------------------------------------------------- 30e9fa281cae44ae56a1cd19378e375282cd95a1 compiler/deSugar/DsBinds.hs | 4 ++-- compiler/typecheck/TcCanonical.hs | 20 ++++++++++---------- compiler/typecheck/TcExpr.hs | 4 ++-- compiler/typecheck/TcHsSyn.hs | 14 ++++++++++++-- libraries/ghc-prim/GHC/Types.hs | 2 +- 5 files changed, 27 insertions(+), 17 deletions(-) diff --git a/compiler/deSugar/DsBinds.hs b/compiler/deSugar/DsBinds.hs index 528f641..4d7ab9d 100644 --- a/compiler/deSugar/DsBinds.hs +++ b/compiler/deSugar/DsBinds.hs @@ -1159,12 +1159,12 @@ dsEvInstanceOf _ (EvInstanceOfVar v) = return (Var v) dsEvInstanceOf ty (EvInstanceOfEq co) = do { bndr <- newSysLocalDs ty - ; expr <- dsTcCoercion (TcSymCo co) (mkCast (Var bndr)) + ; expr <- dsTcCoercion co (mkCast (Var bndr)) ; return (mkCoreLams [bndr] expr) } dsEvInstanceOf ty (EvInstanceOfInst qvars co qs) = do { bndr <- newSysLocalDs ty ; qs' <- mapM dsEvTerm qs ; let exprTy = foldl (\e t -> App e (Type t)) (Var bndr) qvars exprEv = foldl App exprTy qs' - ; expr <- dsTcCoercion (TcSymCo co) (mkCast exprEv) + ; expr <- dsTcCoercion co (mkCast exprEv) ; return (mkCoreLams [bndr] expr) } diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index 46ba17a..bb0b83d 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -1661,26 +1661,26 @@ can_instance_of (CInstanceOfCan { cc_ev = ev, cc_lhs = lhs, cc_rhs = rhs }) -- case InstanceOf sigma sigma, for the exact same sigma | lhs `eqType` rhs = can_instance_to_eq ev lhs rhs - -- case InstanceOf sigma (T ...) --> sigma ~ T ... - | Nothing <- getTyVar_maybe rhs, Nothing <- splitForAllTy_maybe rhs - = can_instance_to_eq ev lhs rhs - -- case InstanceOf (T ...) (forall qvars. Q => ty) + -- case InstanceOf (T ...) sigma --> T ... ~ sigma | Nothing <- getTyVar_maybe lhs, Nothing <- splitForAllTy_maybe lhs - , Just _ <- splitForAllTy_maybe rhs + = can_instance_to_eq ev lhs rhs + -- case InstanceOf (forall qvars. Q => ty) (T ...) + | Nothing <- getTyVar_maybe rhs, Nothing <- splitForAllTy_maybe rhs + , Just _ <- splitForAllTy_maybe lhs = case ev of CtWanted { ctev_evar = evar, ctev_loc = loc } -> - do { (qvars, q, ty) <- splitInst rhs + do { (qvars, q, ty) <- splitInst lhs -- generate new constraints ; new_ev_qs <- mapM (newWantedEvVarNC loc) q ; let eq = mkTcEqPredRole Nominal lhs ty ; new_ev_ty <- newWantedEvVarNC loc eq -- compute the evidence for the instantiation ; let qvars' = map TyVarTy qvars - ; setWantedEvBind evar (mkInstanceOfInst rhs qvars' (ctEvCoercion new_ev_ty) + ; setWantedEvBind evar (mkInstanceOfInst lhs qvars' (ctEvCoercion new_ev_ty) (map ctev_evar new_ev_qs)) -- emit new work ; emitWorkNC new_ev_qs - ; canEqNC new_ev_ty NomEq lhs ty } + ; canEqNC new_ev_ty NomEq rhs ty } _ -> stopWith ev "Given/Derived instanceOf instantiation" can_instance_of _ = panic "can_instance_of in a non InstanceOf constraint" @@ -1689,10 +1689,10 @@ can_instance_to_eq ev lhs rhs = do { let eq = mkTcEqPredRole Nominal lhs rhs ; case ev of CtDerived {} -> canEqNC (ev { ctev_pred = eq }) NomEq lhs rhs - CtGiven {ctev_loc = loc } -> + CtGiven { ctev_loc = loc } -> do { emitNewDerivedEq loc eq ; stopWith ev "Given instanceOf equality" } CtWanted { ctev_evar = evar, ctev_loc = loc } -> do { new_ev <- newWantedEvVarNC loc eq - ; setWantedEvBind evar (mkInstanceOfEq rhs (ctEvCoercion new_ev)) + ; setWantedEvBind evar (mkInstanceOfEq lhs (ctEvCoercion new_ev)) ; canEqNC new_ev NomEq lhs rhs } } diff --git a/compiler/typecheck/TcExpr.hs b/compiler/typecheck/TcExpr.hs index 4112d45..f819f22 100644 --- a/compiler/typecheck/TcExpr.hs +++ b/compiler/typecheck/TcExpr.hs @@ -959,7 +959,7 @@ tc_app fun args fun_ty res_ty post_proc -- Rather like tcWrapResult, but (perhaps for historical reasons) -- we do this before typechecking the arguments ; ev_res <- addErrCtxtM (funResCtxt True (unLoc fun) actual_res_ty res_ty) $ - emitWanted AppOrigin (mkInstanceOfPred res_ty actual_res_ty) + emitWanted AppOrigin (mkInstanceOfPred actual_res_ty res_ty) -- Typecheck the arguments ; args1 <- tcArgs fun args expected_arg_tys @@ -1142,7 +1142,7 @@ tc_check_id orig id_name res_ty -> do { co <- unifyType res_ty actual_ty ; return (mkHsWrap (mkWpCast co) (HsVar id)) } TcIdUnrestricted - -> do { ev <- emitWanted orig (mkInstanceOfPred res_ty actual_ty) + -> do { ev <- emitWanted orig (mkInstanceOfPred actual_ty res_ty) ; return (mkHsWrap (mkWpInstanceOf actual_ty ev) (HsVar id)) } } inst_data_con con diff --git a/compiler/typecheck/TcHsSyn.hs b/compiler/typecheck/TcHsSyn.hs index 63f51eb..caf1642 100644 --- a/compiler/typecheck/TcHsSyn.hs +++ b/compiler/typecheck/TcHsSyn.hs @@ -1442,8 +1442,18 @@ zonkTcTypeToType :: ZonkEnv -> TcType -> TcM Type zonkTcTypeToType env ty = go ty where - go (TyConApp tc tys) = do tys' <- mapM go tys - return (mkTyConApp tc tys') + go (TyConApp tc tys) + | tc `hasKey` instanceOfTyConKey + = do tys' <- mapM go tys + -- Zonc instantiations to functions + return $ case tys' of + [] -> (mkTyConApp funTyCon []) + [_] -> (mkTyConApp funTyCon tys') + [_,_] -> (mkTyConApp funTyCon tys') + _ -> pprPanic "zonkTcTypeToType/instanceOf" (ppr ty) + + | otherwise = do tys' <- mapM go tys + return (mkTyConApp tc tys') -- Establish Type invariants -- See Note [Zonking inside the knot] in TcHsType diff --git a/libraries/ghc-prim/GHC/Types.hs b/libraries/ghc-prim/GHC/Types.hs index 06ff898..b0c02d6 100644 --- a/libraries/ghc-prim/GHC/Types.hs +++ b/libraries/ghc-prim/GHC/Types.hs @@ -177,7 +177,7 @@ data Coercible a b = MkCoercible ((~#) a b) -- Also see Note [Kind-changing of (~) and Coercible] -- | A constraint inhabited only if type `a` is an instance of type `b`. -data InstanceOf a b = MkInstanceOf (b -> a) +data InstanceOf b a = MkInstanceOf (b -> a) -- | Alias for 'tagToEnum#'. Returns True if its parameter is 1# and False -- if it is 0#. From git at git.haskell.org Fri Jun 19 11:49:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 19 Jun 2015 11:49:36 +0000 (UTC) Subject: [commit: ghc] wip/impredicativity: Fix small glitch choosing wrong cast in Core (1960ad9) Message-ID: <20150619114936.EF2413A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/impredicativity Link : http://ghc.haskell.org/trac/ghc/changeset/1960ad944de43a639252e6407d83f3fa488cd3b6/ghc >--------------------------------------------------------------- commit 1960ad944de43a639252e6407d83f3fa488cd3b6 Author: Alejandro Serrano Date: Fri Jun 19 13:47:11 2015 +0200 Fix small glitch choosing wrong cast in Core Previously, mkCast was called, which expected a representational equality, which was not always the case. Change to simple Cast to fix it. >--------------------------------------------------------------- 1960ad944de43a639252e6407d83f3fa488cd3b6 compiler/deSugar/DsBinds.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/deSugar/DsBinds.hs b/compiler/deSugar/DsBinds.hs index 4d7ab9d..fa0404f 100644 --- a/compiler/deSugar/DsBinds.hs +++ b/compiler/deSugar/DsBinds.hs @@ -1159,12 +1159,12 @@ dsEvInstanceOf _ (EvInstanceOfVar v) = return (Var v) dsEvInstanceOf ty (EvInstanceOfEq co) = do { bndr <- newSysLocalDs ty - ; expr <- dsTcCoercion co (mkCast (Var bndr)) + ; expr <- dsTcCoercion co (Cast (Var bndr)) ; return (mkCoreLams [bndr] expr) } dsEvInstanceOf ty (EvInstanceOfInst qvars co qs) = do { bndr <- newSysLocalDs ty ; qs' <- mapM dsEvTerm qs ; let exprTy = foldl (\e t -> App e (Type t)) (Var bndr) qvars exprEv = foldl App exprTy qs' - ; expr <- dsTcCoercion co (mkCast exprEv) + ; expr <- dsTcCoercion co (Cast exprEv) ; return (mkCoreLams [bndr] expr) } From git at git.haskell.org Fri Jun 19 12:54:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 19 Jun 2015 12:54:03 +0000 (UTC) Subject: [commit: ghc] master: Spelling in comments (40698fe) Message-ID: <20150619125403.EC2B93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/40698fec2e63a651ebe6b5f67065f7a736d308a1/ghc >--------------------------------------------------------------- commit 40698fec2e63a651ebe6b5f67065f7a736d308a1 Author: Gabor Greif Date: Tue Jun 16 13:14:38 2015 +0200 Spelling in comments >--------------------------------------------------------------- 40698fec2e63a651ebe6b5f67065f7a736d308a1 compiler/iface/TcIface.hs | 2 +- compiler/types/FamInstEnv.hs | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/iface/TcIface.hs b/compiler/iface/TcIface.hs index 2553643..7d6d1a6 100644 --- a/compiler/iface/TcIface.hs +++ b/compiler/iface/TcIface.hs @@ -647,7 +647,7 @@ tcIfaceRule (IfaceRule {ifRuleName = name, ifActivation = act, ifRuleBndrs = bnd -- We could have stored the ru_rough field in the iface file -- but that would be redundant, I think. -- The only wrinkle is that we must not be deceived by - -- type syononyms at the top of a type arg. Since + -- type synonyms at the top of a type arg. Since -- we can't tell at this point, we are careful not -- to write them out in coreRuleToIfaceRule ifTopFreeName :: IfaceExpr -> Maybe Name diff --git a/compiler/types/FamInstEnv.hs b/compiler/types/FamInstEnv.hs index 9c53138..ee92996 100644 --- a/compiler/types/FamInstEnv.hs +++ b/compiler/types/FamInstEnv.hs @@ -951,7 +951,7 @@ normaliseType :: FamInstEnvs -- environment with family instances -- Normalise the input type, by eliminating *all* type-function redexes -- but *not* newtypes (which are visible to the programmer) -- Returns with Refl if nothing happens --- Try to not to disturb type syonyms if possible +-- Try to not to disturb type synonyms if possible normaliseType env role (TyConApp tc tys) = normaliseTcApp env role tc tys From git at git.haskell.org Fri Jun 19 17:29:20 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 19 Jun 2015 17:29:20 +0000 (UTC) Subject: [commit: ghc] master: testsuite: mark T4945 as expect_broken (e283cec) Message-ID: <20150619172920.16DE63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e283cecf6fd880aef3be2f3abe3936d0c06a250d/ghc >--------------------------------------------------------------- commit e283cecf6fd880aef3be2f3abe3936d0c06a250d Author: Austin Seipp Date: Fri Jun 19 12:28:14 2015 -0500 testsuite: mark T4945 as expect_broken This was working, and then it started failing again; it's a pretty fragile test anyway because it 'grep's the output of the compiler. In the mean time, make the CI system quiet down by marking it appropriately. Signed-off-by: Austin Seipp >--------------------------------------------------------------- e283cecf6fd880aef3be2f3abe3936d0c06a250d testsuite/tests/simplCore/should_compile/all.T | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/simplCore/should_compile/all.T b/testsuite/tests/simplCore/should_compile/all.T index 3a8a6e1..f7ff85b 100644 --- a/testsuite/tests/simplCore/should_compile/all.T +++ b/testsuite/tests/simplCore/should_compile/all.T @@ -107,7 +107,7 @@ test('T4918', ['$MAKE -s --no-print-directory T4918']) test('T4945', - normal, + expect_broken(4945), run_command, ['$MAKE -s --no-print-directory T4945']) From git at git.haskell.org Fri Jun 19 17:34:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 19 Jun 2015 17:34:31 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Parser: commas_tup_tail duplicate SrcSpan on "Missing" value (6520dbf) Message-ID: <20150619173431.300713A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/6520dbfb55fcede4947b0bbb9d736ce72a9acbfe/ghc >--------------------------------------------------------------- commit 6520dbfb55fcede4947b0bbb9d736ce72a9acbfe Author: Alan Zimmerman Date: Thu Jun 18 16:19:50 2015 +0200 Parser: commas_tup_tail duplicate SrcSpan on "Missing" value Summary: Parsing {-# LANGUAGE TupleSections #-} baz = (1, "hello", 6.5,,) 'a' (Just ()) Results in the following AST fragment (L tests/examples/Tuple.hs:3:7-25 (ExplicitTuple [ L tests/examples/Tuple.hs:3:8 (Present (L tests/examples/Tuple.hs:3:8 (HsOverLit (OverLit (HsIntegral [ '1' ] 1) PlaceHolder (HsLit (HsString [] {abstract:FastString})) PlaceHolder)))) , L tests/examples/Tuple.hs:3:11-17 (Present (L tests/examples/Tuple.hs:3:11-17 (HsLit (HsString [ '"' , 'h' , 'e' , 'l' , 'l' , 'o' , '"' ] {abstract:FastString})))) , L tests/examples/Tuple.hs:3:20-22 (Present (L tests/examples/Tuple.hs:3:20-22 (HsOverLit (OverLit (HsFractional (FL [ '6' , '.' , '5' ] (:% 13 2))) PlaceHolder (HsLit (HsString [] {abstract:FastString})) PlaceHolder)))) , L tests/examples/Tuple.hs:3:24 (Missing PlaceHolder) , L tests/examples/Tuple.hs:3:24 (Missing PlaceHolder) ] The final `Missing PlaceHolder` has a duplicated `SrcSpan` Test Plan: ./validate Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: thomie, bgamari, mpickering Differential Revision: https://phabricator.haskell.org/D995 GHC Trac Issues: #10537 (cherry picked from commit 72b21c393831b49867a296f19a2d039e48bb8dcd) >--------------------------------------------------------------- 6520dbfb55fcede4947b0bbb9d736ce72a9acbfe compiler/parser/Parser.y | 14 ++++---------- testsuite/tests/ghc-api/annotations/exampleTest.stdout | 3 +-- testsuite/tests/ghc-api/annotations/parseTree.stdout | 3 +-- 3 files changed, 6 insertions(+), 14 deletions(-) diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y index bc2bed8..7f3f26a 100644 --- a/compiler/parser/Parser.y +++ b/compiler/parser/Parser.y @@ -2268,28 +2268,22 @@ tup_exprs :: { [LHsTupArg RdrName] } | commas tup_tail {% do { mapM_ (\ll -> addAnnotation ll AnnComma ll) (fst $1) ; return - (let tt = if null $2 - then [noLoc missingTupArg] - else $2 - in map (\l -> L l missingTupArg) (fst $1) ++ tt) } } + (map (\l -> L l missingTupArg) (fst $1) ++ $2) } } -- Always starts with commas; always follows an expr commas_tup_tail :: { (SrcSpan,[LHsTupArg RdrName]) } commas_tup_tail : commas tup_tail {% do { mapM_ (\ll -> addAnnotation ll AnnComma ll) (tail $ fst $1) ; return ( - let tt = if null $2 - then [L (last $ fst $1) missingTupArg] - else $2 - in (head $ fst $1 - ,(map (\l -> L l missingTupArg) (tail $ fst $1)) ++ tt)) } } + (head $ fst $1 + ,(map (\l -> L l missingTupArg) (tail $ fst $1)) ++ $2)) } } -- Always follows a comma tup_tail :: { [LHsTupArg RdrName] } : texp commas_tup_tail {% addAnnotation (gl $1) AnnComma (fst $2) >> return ((L (gl $1) (Present $1)) : snd $2) } | texp { [L (gl $1) (Present $1)] } - | {- empty -} { [] {- [noLoc missingTupArg] -} } + | {- empty -} { [noLoc missingTupArg] } ----------------------------------------------------------------------------- -- List expressions diff --git a/testsuite/tests/ghc-api/annotations/exampleTest.stdout b/testsuite/tests/ghc-api/annotations/exampleTest.stdout index cd6f9c0..210a4d8 100644 --- a/testsuite/tests/ghc-api/annotations/exampleTest.stdout +++ b/testsuite/tests/ghc-api/annotations/exampleTest.stdout @@ -1,10 +1,9 @@ ---Problems--------------------- [ -(AK AnnEofPos = [AnnotationTuple.hs:32:1]) ] ---Problems'-------------------- -[(AnnEofPos, AnnotationTuple.hs:32:1)] +[] -------------------------------- [ (AK AnnotationTuple.hs:1:1 AnnCloseC = [AnnotationTuple.hs:27:1]) diff --git a/testsuite/tests/ghc-api/annotations/parseTree.stdout b/testsuite/tests/ghc-api/annotations/parseTree.stdout index f7d1e5d..7d651aa 100644 --- a/testsuite/tests/ghc-api/annotations/parseTree.stdout +++ b/testsuite/tests/ghc-api/annotations/parseTree.stdout @@ -8,8 +8,7 @@ (AnnotationTuple.hs:16:20-22, [p], (6.5)), (AnnotationTuple.hs:16:24, [m], ()), (AnnotationTuple.hs:16:25, [m], ()), - (AnnotationTuple.hs:16:26, [m], ()), - (AnnotationTuple.hs:16:26, [m], ())] + (AnnotationTuple.hs:16:26, [m], ()), (, [m], ())] [ (AK AnnotationTuple.hs:1:1 AnnCloseC = [AnnotationTuple.hs:27:1]) From git at git.haskell.org Fri Jun 19 21:41:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 19 Jun 2015 21:41:16 +0000 (UTC) Subject: [commit: ghc] master: docs: Unbreak the PS/PDF builds for the User's Guide (#10509) (440d1bc) Message-ID: <20150619214116.291F53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/440d1bc1f5fa4d31f1f7bc45f3f3485733509313/ghc >--------------------------------------------------------------- commit 440d1bc1f5fa4d31f1f7bc45f3f3485733509313 Author: Gabor Pali Date: Fri Jun 19 23:19:30 2015 +0200 docs: Unbreak the PS/PDF builds for the User's Guide (#10509) dblatex can only translate the Unicode glyphs introduced in #10509 for LaTeX if the `latex.unicode.use=1` flag is set, otherwise it will just fail. However, note that adding this flag is not going to fully solve the problem as those symbols are not known by LaTeX, so the corresponding character codes will be added instead to the resulting PS/PDF files. Hence it is considered an interim solution only, not a true fix, until a better one is found. >--------------------------------------------------------------- 440d1bc1f5fa4d31f1f7bc45f3f3485733509313 mk/config.mk.in | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/mk/config.mk.in b/mk/config.mk.in index d6831c9..cad5c71 100644 --- a/mk/config.mk.in +++ b/mk/config.mk.in @@ -731,7 +731,7 @@ BUILD_DOCBOOK_PS = @BUILD_DOCBOOK_PS@ BUILD_DOCBOOK_PDF = @BUILD_DOCBOOK_PDF@ DBLATEX = @DblatexCmd@ # filename.as.url=0 is needed with dblatex 0.3.4 (#7486) -DBLATEX_OPTS = -P 'filename.as.url=0' +DBLATEX_OPTS = -P 'filename.as.url=0' -P 'latex.unicode.use=1' XSLTPROC = @XsltprocCmd@ XMLLINT = @XmllintCmd@ HAVE_DOCBOOK_XSL = @HAVE_DOCBOOK_XSL@ From git at git.haskell.org Fri Jun 19 21:57:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 19 Jun 2015 21:57:32 +0000 (UTC) Subject: [commit: ghc] master: should_run/allocLimit4: disable ghci way (7d5a845) Message-ID: <20150619215732.E840C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7d5a845365761c125e637cfa0c341b661a57a879/ghc >--------------------------------------------------------------- commit 7d5a845365761c125e637cfa0c341b661a57a879 Author: Sergei Trofimovich Date: Fri Jun 19 22:54:15 2015 +0100 should_run/allocLimit4: disable ghci way Test sets allocation limit for a current main thread, ghci already loaded a bunch of stuff in it. Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- 7d5a845365761c125e637cfa0c341b661a57a879 testsuite/tests/concurrent/should_run/all.T | 4 +++- testsuite/tests/concurrent/should_run/allocLimit4.hs | 3 ++- 2 files changed, 5 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/concurrent/should_run/all.T b/testsuite/tests/concurrent/should_run/all.T index 2d3ac2e..3d059bd 100644 --- a/testsuite/tests/concurrent/should_run/all.T +++ b/testsuite/tests/concurrent/should_run/all.T @@ -99,7 +99,9 @@ test('allocLimit2', normal, compile_and_run, ['']) test('allocLimit3', [ when(opsys('mingw32'), only_ways(threaded_ways)), exit_code(1) ], compile_and_run, ['']) -test('allocLimit4', [ extra_run_opts('+RTS -xq300k -RTS') ], +test('allocLimit4', [ extra_run_opts('+RTS -xq300k -RTS'), + # ghci consumes part of set limit at startup + omit_ways(['ghci']) ], compile_and_run, ['']) # ----------------------------------------------------------------------------- diff --git a/testsuite/tests/concurrent/should_run/allocLimit4.hs b/testsuite/tests/concurrent/should_run/allocLimit4.hs index b589ffa..842ad1c 100644 --- a/testsuite/tests/concurrent/should_run/allocLimit4.hs +++ b/testsuite/tests/concurrent/should_run/allocLimit4.hs @@ -8,6 +8,7 @@ import Control.Monad -- check that +RTS -xq is doing the right thing: the test requires -- +RTS -xq300k +-- Test does not work in GHCi as it load A Lot Of Things at start main = do m <- newEmptyMVar @@ -19,7 +20,7 @@ main = do case e of Left AllocationLimitExceeded{} -> do c <- getAllocationCounter - when (c < 250*1024 || c > 350*1024) $ fail "wrong limit grace" + when (c < 250*1024 || c > 350*1024) $ fail $ "wrong limit grace: " ++ show c print (length [2..]) Right _ -> fail "didn't catch AllocationLimitExceeded" From git at git.haskell.org Sat Jun 20 08:55:30 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 20 Jun 2015 08:55:30 +0000 (UTC) Subject: [commit: ghc] master: Amend tcrun024, tcrun025 after Trac #7854 fix (e491803) Message-ID: <20150620085530.9025A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e4918034896948642718f15906f5b379b98f68cf/ghc >--------------------------------------------------------------- commit e4918034896948642718f15906f5b379b98f68cf Author: Sergei Trofimovich Date: Sat Jun 20 09:51:36 2015 +0100 Amend tcrun024, tcrun025 after Trac #7854 fix Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- e4918034896948642718f15906f5b379b98f68cf testsuite/tests/typecheck/should_run/TcRun025_B.hs | 2 +- testsuite/tests/typecheck/should_run/tcrun024.hs | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/typecheck/should_run/TcRun025_B.hs b/testsuite/tests/typecheck/should_run/TcRun025_B.hs index a6d752c..ae48117 100644 --- a/testsuite/tests/typecheck/should_run/TcRun025_B.hs +++ b/testsuite/tests/typecheck/should_run/TcRun025_B.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE ImplicitParams, TypeSynonymInstances, FlexibleInstances #-} +{-# LANGUAGE ImplicitParams, TypeSynonymInstances, FlexibleInstances, ConstrainedClassMethods #-} -- Similar to tc024, but cross module diff --git a/testsuite/tests/typecheck/should_run/tcrun024.hs b/testsuite/tests/typecheck/should_run/tcrun024.hs index 82c6f49..1edf5eb 100644 --- a/testsuite/tests/typecheck/should_run/tcrun024.hs +++ b/testsuite/tests/typecheck/should_run/tcrun024.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE ImplicitParams, TypeSynonymInstances, FlexibleInstances #-} +{-# LANGUAGE ImplicitParams, TypeSynonymInstances, FlexibleInstances, ConstrainedClassMethods #-} -- Class ops that bind no new type variables From git at git.haskell.org Sat Jun 20 09:07:10 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 20 Jun 2015 09:07:10 +0000 (UTC) Subject: [commit: ghc] master: Amend tcrun037 after Trac #7854 fix (7c2293a) Message-ID: <20150620090710.069E83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7c2293a07fb057e492278f46e8fde48b69d178a3/ghc >--------------------------------------------------------------- commit 7c2293a07fb057e492278f46e8fde48b69d178a3 Author: Sergei Trofimovich Date: Sat Jun 20 10:04:28 2015 +0100 Amend tcrun037 after Trac #7854 fix Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- 7c2293a07fb057e492278f46e8fde48b69d178a3 testsuite/tests/typecheck/should_run/tcrun037.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/typecheck/should_run/tcrun037.hs b/testsuite/tests/typecheck/should_run/tcrun037.hs index e79817d..ee1acba 100644 --- a/testsuite/tests/typecheck/should_run/tcrun037.hs +++ b/testsuite/tests/typecheck/should_run/tcrun037.hs @@ -1,4 +1,4 @@ - +{-# LANGUAGE ConstrainedClassMethods #-} module Main where From git at git.haskell.org Sat Jun 20 09:57:12 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 20 Jun 2015 09:57:12 +0000 (UTC) Subject: [commit: ghc] master: Fix a couple of tests for GHCi/-O* (Trac #10052) (2c6a041) Message-ID: <20150620095712.D23603A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2c6a0411dcd921ea6ec1cbe5eaf93d17adcf33a2/ghc >--------------------------------------------------------------- commit 2c6a0411dcd921ea6ec1cbe5eaf93d17adcf33a2 Author: Sergei Trofimovich Date: Sat Jun 20 10:24:40 2015 +0100 Fix a couple of tests for GHCi/-O* (Trac #10052) Tests use unboxed types (or optimizer gets to them), those can't be handled by ghci. Fixed by using -fobject-code. Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- 2c6a0411dcd921ea6ec1cbe5eaf93d17adcf33a2 testsuite/tests/codeGen/should_run/all.T | 3 ++- testsuite/tests/perf/should_run/all.T | 3 ++- testsuite/tests/programs/joao-circular/test.T | 1 + testsuite/tests/typecheck/should_run/all.T | 3 ++- 4 files changed, 7 insertions(+), 3 deletions(-) diff --git a/testsuite/tests/codeGen/should_run/all.T b/testsuite/tests/codeGen/should_run/all.T index 59e4dca..9125f0b 100644 --- a/testsuite/tests/codeGen/should_run/all.T +++ b/testsuite/tests/codeGen/should_run/all.T @@ -119,7 +119,8 @@ test('CgStaticPointers', , when(doing_ghci(), extra_hc_opts('-fobject-code')) ], compile_and_run, ['']) -test('StaticArraySize', normal, compile_and_run, ['-O2']) +test('StaticArraySize', [when(doing_ghci(), extra_hc_opts('-fobject-code'))], + compile_and_run, ['-O2']) test('StaticByteArraySize', normal, compile_and_run, ['-O2']) test('CopySmallArray', normal, compile_and_run, ['']) test('CopySmallArrayStressTest', reqlib('random'), compile_and_run, ['']) diff --git a/testsuite/tests/perf/should_run/all.T b/testsuite/tests/perf/should_run/all.T index 6302022..43b24f7 100644 --- a/testsuite/tests/perf/should_run/all.T +++ b/testsuite/tests/perf/should_run/all.T @@ -39,7 +39,8 @@ test('T4830', compile_and_run, ['-O2']) -test('T3245', normal, compile_and_run, ['-O']) +test('T3245', [when(doing_ghci(), extra_hc_opts('-fobject-code'))], + compile_and_run, ['-O']) # Test that bytestring reading/writing isn't over-allocating. We had # a bug in hGetBufNonBlocking in 6.13 that triggered this. diff --git a/testsuite/tests/programs/joao-circular/test.T b/testsuite/tests/programs/joao-circular/test.T index 3f229ab..3fbf054 100644 --- a/testsuite/tests/programs/joao-circular/test.T +++ b/testsuite/tests/programs/joao-circular/test.T @@ -1,5 +1,6 @@ test('joao-circular', [when(fast(), skip), + when(doing_ghci(), extra_hc_opts('-fobject-code')), extra_clean(['Data_Lazy.hi', 'Data_Lazy.o', 'Funcs_Lexer.hi', 'Funcs_Lexer.o', 'Funcs_Parser_Lazy.hi', 'Funcs_Parser_Lazy.o', diff --git a/testsuite/tests/typecheck/should_run/all.T b/testsuite/tests/typecheck/should_run/all.T index 9cf7a80..4195ca8 100755 --- a/testsuite/tests/typecheck/should_run/all.T +++ b/testsuite/tests/typecheck/should_run/all.T @@ -40,7 +40,8 @@ test('tcrun020', normal, compile_and_run, ['']) test('tcrun021', normal, compile_and_run, ['-package containers']) test('tcrun022', [omit_ways(['ghci']),only_compiler_types(['ghc'])], compile_and_run, ['-O']) -test('tcrun023', normal, compile_and_run, ['-O']) +test('tcrun023', [when(doing_ghci(), extra_hc_opts('-fobject-code'))], + compile_and_run, ['-O']) test('tcrun024', normal, compile_and_run, ['-O']) test('tcrun025', extra_clean(['TcRun025_B.hi', 'TcRun025_B.o']), multimod_compile_and_run, ['tcrun025','']) From git at git.haskell.org Sat Jun 20 11:25:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 20 Jun 2015 11:25:01 +0000 (UTC) Subject: [commit: ghc] master: Recognise 'hardhloat' as a valid vendor in a host tuple (5cc08eb) Message-ID: <20150620112501.0D73E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5cc08ebf2f346992a0abd4440252165c90b5ec05/ghc >--------------------------------------------------------------- commit 5cc08ebf2f346992a0abd4440252165c90b5ec05 Author: Sergei Trofimovich Date: Sat Jun 20 12:23:00 2015 +0100 Recognise 'hardhloat' as a valid vendor in a host tuple Observed on a tuple armv7a-hardfloat-linux-gnueabi: > Unknown vendor hardfloat Reported-by: Sergey Alirzaev Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- 5cc08ebf2f346992a0abd4440252165c90b5ec05 aclocal.m4 | 3 +++ 1 file changed, 3 insertions(+) diff --git a/aclocal.m4 b/aclocal.m4 index 590edb0..958622c 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -1966,6 +1966,9 @@ AC_DEFUN([GHC_CONVERT_VENDOR],[ softfloat) # like armv5tel-softfloat-linux-gnueabi $2="unknown" ;; + hardfloat) # like armv7a-hardfloat-linux-gnueabi + $2="unknown" + ;; *) #pass thru by default $2="$1" From git at git.haskell.org Sat Jun 20 11:49:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 20 Jun 2015 11:49:46 +0000 (UTC) Subject: [commit: ghc] master: Updated output for test ghci024 (f2ffdc6) Message-ID: <20150620114946.2C61D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f2ffdc6e023e3fb075842de382f3ed9aeb902647/ghc >--------------------------------------------------------------- commit f2ffdc6e023e3fb075842de382f3ed9aeb902647 Author: Sergei Trofimovich Date: Sat Jun 20 12:47:50 2015 +0100 Updated output for test ghci024 Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- f2ffdc6e023e3fb075842de382f3ed9aeb902647 testsuite/tests/ghci/scripts/ghci024.stdout | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/ghci/scripts/ghci024.stdout b/testsuite/tests/ghci/scripts/ghci024.stdout index f6b8cb3..1624322 100644 --- a/testsuite/tests/ghci/scripts/ghci024.stdout +++ b/testsuite/tests/ghci/scripts/ghci024.stdout @@ -9,6 +9,7 @@ other dynamic, non-language, flag settings: -fforce-recomp -fimplicit-import-qualified warning settings: + -fno-warn-tabs ~~~~~~~~~~ Testing :set -a options currently set: none. base language is: Haskell2010 @@ -26,8 +27,8 @@ with the following modifiers: ~~~~~~~~~~ Testing :show languages, with -XMagicHash base language is: Haskell2010 with the following modifiers: - -XMagicHash -XNoDatatypeContexts + -XMagicHash -XNondecreasingIndentation ~~~~~~~~~~ Testing :show packages active package flags: none From git at git.haskell.org Sat Jun 20 21:58:58 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 20 Jun 2015 21:58:58 +0000 (UTC) Subject: [commit: ghc] master: Make GHC install libraries to e.g. xhtml-3000.2.1-0ACfOp3hebWD9jGWE4v4Gh. (85d5397) Message-ID: <20150620215858.D85993A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/85d539754ac07286ef5fed714ad42451bd5a1d28/ghc >--------------------------------------------------------------- commit 85d539754ac07286ef5fed714ad42451bd5a1d28 Author: Edward Z. Yang Date: Thu May 28 17:11:12 2015 -0700 Make GHC install libraries to e.g. xhtml-3000.2.1-0ACfOp3hebWD9jGWE4v4Gh. Summary: Previously, we'd install them to something like xhtml_0ACfOp3hebWD9jGWE4v4G which was fairly ugly; this commit changes the default install path to contain the full package name and version, as well as the package key. Needs a Cabal submodule update for the commit for install paths support "Add libname install-dirs variable, use it by default. Fixes #2437". It also contains some miscellaneous fixes for Cabal HEAD. Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: austin Subscribers: bgamari, thomie Trac Issues: #10479 Differential Revision: https://phabricator.haskell.org/D922 >--------------------------------------------------------------- 85d539754ac07286ef5fed714ad42451bd5a1d28 ghc.mk | 2 +- libraries/Cabal | 2 +- libraries/ghc-prim/ghc-prim.cabal | 3 +++ rules/distdir-way-opts.mk | 4 ++-- utils/ghc-cabal/Main.hs | 10 +++++++++- utils/ghc-pkg/Main.hs | 2 +- 6 files changed, 17 insertions(+), 6 deletions(-) diff --git a/ghc.mk b/ghc.mk index 93da0cb..bee6abf 100644 --- a/ghc.mk +++ b/ghc.mk @@ -908,7 +908,7 @@ install_packages: rts/dist/package.conf.install $(call INSTALL_DIR,"$(DESTDIR)$(topdir)/rts") $(call installLibsTo, $(RTS_INSTALL_LIBS), "$(DESTDIR)$(topdir)/rts") $(foreach p, $(INSTALL_DYNLIBS), \ - $(call installLibsTo, $(wildcard $p/dist-install/build/*.so $p/dist-install/build/*.dll $p/dist-install/build/*.dylib), "$(DESTDIR)$(topdir)/$($p_dist-install_PACKAGE_KEY)")) + $(call installLibsTo, $(wildcard $p/dist-install/build/*.so $p/dist-install/build/*.dll $p/dist-install/build/*.dylib), "$(DESTDIR)$(topdir)/$($p_dist-install_LIB_NAME)")) $(foreach p, $(INSTALL_PACKAGES), \ $(call make-command, \ "$(ghc-cabal_INPLACE)" copy \ diff --git a/libraries/Cabal b/libraries/Cabal index bda1ce6..9e9e437 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit bda1ce6b757cdaca93f2eba4e1906a4658719537 +Subproject commit 9e9e4370bbca6af032794225fe5638124acf2d85 diff --git a/libraries/ghc-prim/ghc-prim.cabal b/libraries/ghc-prim/ghc-prim.cabal index b9e74d1..58b6ee0 100644 --- a/libraries/ghc-prim/ghc-prim.cabal +++ b/libraries/ghc-prim/ghc-prim.cabal @@ -21,6 +21,9 @@ flag include-ghc-prim Description: Include GHC.Prim in exposed-modules default: False +custom-setup + setup-depends: base >= 4 && < 5, Cabal >= 1.23 + Library default-language: Haskell2010 other-extensions: diff --git a/rules/distdir-way-opts.mk b/rules/distdir-way-opts.mk index 99f7ce9..8073093 100644 --- a/rules/distdir-way-opts.mk +++ b/rules/distdir-way-opts.mk @@ -186,11 +186,11 @@ ifneq "$4" "0" ifeq "$$(TargetElf)" "YES" $1_$2_$3_GHC_LD_OPTS += \ -fno-use-rpaths \ - $$(foreach d,$$($1_$2_TRANSITIVE_DEP_KEYS),-optl-Wl$$(comma)-rpath -optl-Wl$$(comma)'$$$$ORIGIN/../$$d') -optl-Wl,-zorigin + $$(foreach d,$$($1_$2_TRANSITIVE_DEP_LIB_NAMES),-optl-Wl$$(comma)-rpath -optl-Wl$$(comma)'$$$$ORIGIN/../$$d') -optl-Wl,-zorigin else ifeq "$$(TargetOS_CPP)" "darwin" $1_$2_$3_GHC_LD_OPTS += \ -fno-use-rpaths \ - $$(foreach d,$$($1_$2_TRANSITIVE_DEP_KEYS),-optl-Wl$$(comma)-rpath -optl-Wl$$(comma)'@loader_path/../$$d') + $$(foreach d,$$($1_$2_TRANSITIVE_DEP_LIB_NAMES),-optl-Wl$$(comma)-rpath -optl-Wl$$(comma)'@loader_path/../$$d') endif endif endif diff --git a/utils/ghc-cabal/Main.hs b/utils/ghc-cabal/Main.hs index 4ae85ec..3c049fe 100644 --- a/utils/ghc-cabal/Main.hs +++ b/utils/ghc-cabal/Main.hs @@ -118,6 +118,7 @@ doCheck directory [] -> return () errs -> mapM_ print errs >> exitWith (ExitFailure 1) where isFailure (PackageDistSuspicious {}) = False + isFailure (PackageDistSuspiciousWarn {}) = False isFailure _ = True runHsColour :: FilePath -> FilePath -> [String] -> IO () @@ -256,7 +257,7 @@ updateInstallDirTemplates relocatableBuild myPrefix myLibdir myDocdir idts if relocatableBuild then "$topdir" else myLibdir, - libsubdir = toPathTemplate "$pkgkey", + libsubdir = toPathTemplate "$libname", docdir = toPathTemplate $ if relocatableBuild then "$topdir/../doc/html/libraries/$pkgid" @@ -414,6 +415,12 @@ generate directory distdir dll0Modules config_args | packageKeySupported comp = map (display . Installed.packageKey) dep_pkgs | otherwise = transitiveDeps + transitiveDepLibNames + | packageKeySupported comp + = map (\p -> packageKeyLibraryName + (Installed.sourcePackageId p) + (Installed.packageKey p)) dep_pkgs + | otherwise = transitiveDeps transitiveDepNames = map (display . packageName) transitive_dep_ids libraryDirs = forDeps Installed.libraryDirs @@ -444,6 +451,7 @@ generate directory distdir dll0Modules config_args variablePrefix ++ "_DEP_NAMES = " ++ unwords depNames, variablePrefix ++ "_TRANSITIVE_DEPS = " ++ unwords transitiveDeps, variablePrefix ++ "_TRANSITIVE_DEP_KEYS = " ++ unwords transitiveDepKeys, + variablePrefix ++ "_TRANSITIVE_DEP_LIB_NAMES = " ++ unwords transitiveDepLibNames, variablePrefix ++ "_TRANSITIVE_DEP_NAMES = " ++ unwords transitiveDepNames, variablePrefix ++ "_INCLUDE_DIRS = " ++ unwords (includeDirs bi), variablePrefix ++ "_INCLUDES = " ++ unwords (includes bi), diff --git a/utils/ghc-pkg/Main.hs b/utils/ghc-pkg/Main.hs index f3017a2..a83720b 100644 --- a/utils/ghc-pkg/Main.hs +++ b/utils/ghc-pkg/Main.hs @@ -19,7 +19,7 @@ import Distribution.ModuleName (ModuleName) import Distribution.InstalledPackageInfo as Cabal import Distribution.Compat.ReadP hiding (get) import Distribution.ParseUtils -import Distribution.Package hiding (depends, installedPackageId) +import Distribution.Package hiding (installedPackageId) import Distribution.Text import Distribution.Version import Distribution.Simple.Utils (fromUTF8, toUTF8) From git at git.haskell.org Sat Jun 20 22:13:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 20 Jun 2015 22:13:35 +0000 (UTC) Subject: [commit: ghc] master: Filter orphan rules based on imports, fixes #10294 and #10420. (0cb1f5c) Message-ID: <20150620221335.314CC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0cb1f5cf26fae946ca745abc5e302e62a8f66feb/ghc >--------------------------------------------------------------- commit 0cb1f5cf26fae946ca745abc5e302e62a8f66feb Author: Edward Z. Yang Date: Wed Jun 3 14:33:05 2015 -0700 Filter orphan rules based on imports, fixes #10294 and #10420. Summary: If we have an orphan rule in our database, don't apply it unless the defining module is transitively imported by the module we are processing. We do this by defining a new RuleEnv data type which includes both the RuleBase as well as the set of visible orphan modules, and threading this through the relevant environments (CoreReader, RuleCheckEnv and ScEnv). This is analogous to the instances fix we applied in #2182 4c834fdddf4d44d12039da4d6a2c63a660975b95, but done for RULES. An important knock-on effect is that we can remove some buggy code in LoadInterface which tried to avoid loading interfaces that were loaded by plugins (which sometimes caused instances and rules to NEVER become visible). One note about tests: I renamed the old plugins07 test to T10420 and replaced plugins07 with a test to ensure that a plugin import did not cause new rules to be loaded in. Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: simonpj, austin, goldfire Subscribers: bgamari, thomie Differential Revision: https://phabricator.haskell.org/D950 GHC Trac Issues: #10420 >--------------------------------------------------------------- 0cb1f5cf26fae946ca745abc5e302e62a8f66feb compiler/coreSyn/CoreFVs.hs | 2 +- compiler/coreSyn/CoreLint.hs | 1 + compiler/coreSyn/CoreSyn.hs | 116 ++++++++++++++++++++- compiler/deSugar/Desugar.hs | 3 +- compiler/deSugar/DsBinds.hs | 3 +- compiler/iface/LoadIface.hs | 27 +---- compiler/iface/MkIface.hs | 24 ++--- compiler/iface/TcIface.hs | 5 +- compiler/simplCore/CoreMonad.hs | 9 +- compiler/simplCore/SimplCore.hs | 23 ++-- compiler/simplCore/SimplMonad.hs | 8 +- compiler/specialise/Rules.hs | 38 +++++-- compiler/specialise/SpecConstr.hs | 14 ++- compiler/specialise/Specialise.hs | 24 +++-- compiler/types/InstEnv.hs | 78 +------------- testsuite/.gitignore | 4 + testsuite/tests/plugins/Makefile | 19 +++- testsuite/tests/plugins/T10294.hs | 7 ++ testsuite/tests/plugins/T10294.stderr | 1 + testsuite/tests/plugins/T10294a.hs | 7 ++ .../tests/plugins/{plugins07.hs => T10420.hs} | 2 +- .../plugins/{plugins07.stdout => T10420.stdout} | 0 .../tests/plugins/{Plugins07a.hs => T10420a.hs} | 2 +- testsuite/tests/plugins/all.T | 21 +++- .../p => plugins/annotation-plugin}/LICENSE | 0 .../Makefile | 0 .../tests/plugins/annotation-plugin/SayAnnNames.hs | 34 ++++++ .../cabal05 => plugins/annotation-plugin}/Setup.hs | 0 .../annotation-plugin/annotation-plugin.cabal | 11 ++ testsuite/tests/plugins/plugins07.hs | 4 - testsuite/tests/plugins/plugins07.stdout | 2 +- .../tests/simplCore/should_compile/T8848.stderr | 10 +- 32 files changed, 321 insertions(+), 178 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 0cb1f5cf26fae946ca745abc5e302e62a8f66feb From git at git.haskell.org Sat Jun 20 22:58:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 20 Jun 2015 22:58:51 +0000 (UTC) Subject: [commit: ghc] master: Fix all.T for T8131/T8131b. (29bc13a) Message-ID: <20150620225851.0F6073A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/29bc13aa72fd113349f15cc2d47257a4979c25f2/ghc >--------------------------------------------------------------- commit 29bc13aa72fd113349f15cc2d47257a4979c25f2 Author: Edward Z. Yang Date: Sat Jun 20 15:58:46 2015 -0700 Fix all.T for T8131/T8131b. Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- 29bc13aa72fd113349f15cc2d47257a4979c25f2 testsuite/tests/llvm/should_compile/all.T | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/llvm/should_compile/all.T b/testsuite/tests/llvm/should_compile/all.T index 0082635..443e76f 100644 --- a/testsuite/tests/llvm/should_compile/all.T +++ b/testsuite/tests/llvm/should_compile/all.T @@ -12,4 +12,5 @@ test('T5681', normal, compile, ['']) test('T6158', [reqlib('vector'), reqlib('primitive')], compile, ['-package vector -package primitive']) test('T7571', cmm_src, compile, ['']) test('T7575', unless(wordsize(32), skip), compile, ['']) -test('T8131b', [cmm_src], compile, ['']) +test('T8131', cmm_src, compile, ['']) +test('T8131b', normal, compile, ['']) From git at git.haskell.org Sat Jun 20 23:11:56 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 20 Jun 2015 23:11:56 +0000 (UTC) Subject: [commit: ghc] master: Remove duplicate test. (15ef5fc) Message-ID: <20150620231156.27F0F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/15ef5fcb63cb8e3a7137490af04b84103e3a1e0d/ghc >--------------------------------------------------------------- commit 15ef5fcb63cb8e3a7137490af04b84103e3a1e0d Author: Edward Z. Yang Date: Sat Jun 20 16:12:20 2015 -0700 Remove duplicate test. Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- 15ef5fcb63cb8e3a7137490af04b84103e3a1e0d testsuite/tests/llvm/should_compile/T8131.cmm | 7 ------- testsuite/tests/llvm/should_compile/all.T | 1 - 2 files changed, 8 deletions(-) diff --git a/testsuite/tests/llvm/should_compile/T8131.cmm b/testsuite/tests/llvm/should_compile/T8131.cmm deleted file mode 100644 index 153fb02..0000000 --- a/testsuite/tests/llvm/should_compile/T8131.cmm +++ /dev/null @@ -1,7 +0,0 @@ -#include "Cmm.h" - -testMemcpy (W_ dst, W_ src, W_ l, W_ sz) -{ - prim %memcpy(dst, src, l, sz); - return (); -} diff --git a/testsuite/tests/llvm/should_compile/all.T b/testsuite/tests/llvm/should_compile/all.T index 443e76f..9da136d 100644 --- a/testsuite/tests/llvm/should_compile/all.T +++ b/testsuite/tests/llvm/should_compile/all.T @@ -12,5 +12,4 @@ test('T5681', normal, compile, ['']) test('T6158', [reqlib('vector'), reqlib('primitive')], compile, ['-package vector -package primitive']) test('T7571', cmm_src, compile, ['']) test('T7575', unless(wordsize(32), skip), compile, ['']) -test('T8131', cmm_src, compile, ['']) test('T8131b', normal, compile, ['']) From git at git.haskell.org Sat Jun 20 23:35:50 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 20 Jun 2015 23:35:50 +0000 (UTC) Subject: [commit: ghc] master: Build system: unset HADDOCK when haddock is not found (13ba87f) Message-ID: <20150620233550.92DE13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/13ba87f8a28154e33b5b6d6b8302e18f7c56760b/ghc >--------------------------------------------------------------- commit 13ba87f8a28154e33b5b6d6b8302e18f7c56760b Author: Thomas Miedema Date: Thu Jun 18 19:40:40 2015 +0200 Build system: unset HADDOCK when haddock is not found This prevents the following test errors on Windows: perf/haddock haddock.Cabal [[Errno 2] No such file or directory: ... perf/haddock haddock.base [[Errno 2] No such file or directory: ... perf/haddock haddock.compiler [[Errno 2] No such file or directory: ... The tests will now be reported as having missing libraries. >--------------------------------------------------------------- 13ba87f8a28154e33b5b6d6b8302e18f7c56760b testsuite/mk/boilerplate.mk | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/testsuite/mk/boilerplate.mk b/testsuite/mk/boilerplate.mk index d5b7fb5..b5039d5 100644 --- a/testsuite/mk/boilerplate.mk +++ b/testsuite/mk/boilerplate.mk @@ -143,8 +143,8 @@ endif $(eval $(call canonicaliseExecutable,HADDOCK)) ifeq "$(shell test -x '$(HADDOCK)' && echo exists)" "" -# haddock is optional. -HADDOCK := +# haddock is optional. Use 'override' to override canonicalise's override... +override HADDOCK := endif $(eval $(call canonicaliseExecutable,HSC2HS)) From git at git.haskell.org Sun Jun 21 19:27:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 21 Jun 2015 19:27:33 +0000 (UTC) Subject: [commit: ghc] master: Change `Typeable` instance for type-lis to use the Known* classes. (4854fce) Message-ID: <20150621192733.483D53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4854fcea4f73897bbdcdfede382c826da7b64b97/ghc >--------------------------------------------------------------- commit 4854fcea4f73897bbdcdfede382c826da7b64b97 Author: Iavor S. Diatchki Date: Sun Jun 21 12:24:42 2015 -0700 Change `Typeable` instance for type-lis to use the Known* classes. This should fix T10348 >--------------------------------------------------------------- 4854fcea4f73897bbdcdfede382c826da7b64b97 compiler/deSugar/DsBinds.hs | 25 ++++++++++++++-------- compiler/prelude/PrelNames.hs | 24 +++++++++++++-------- compiler/typecheck/TcEvidence.hs | 6 +++--- compiler/typecheck/TcHsSyn.hs | 2 +- compiler/typecheck/TcInteract.hs | 18 +++++++++++----- compiler/typecheck/TcSMonad.hs | 6 +++++- libraries/base/Data/Typeable/Internal.hs | 11 +++++++++- testsuite/tests/typecheck/should_compile/T10348.hs | 11 ++++++++-- 8 files changed, 72 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 4854fcea4f73897bbdcdfede382c826da7b64b97 From git at git.haskell.org Sun Jun 21 19:52:35 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 21 Jun 2015 19:52:35 +0000 (UTC) Subject: [commit: ghc] master: Add parsePattern parser entry point (38f3745) Message-ID: <20150621195235.C440F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/38f374571290b8115ef5b82587ac2ec6c18e91f1/ghc >--------------------------------------------------------------- commit 38f374571290b8115ef5b82587ac2ec6c18e91f1 Author: Alan Zimmerman Date: Sun Jun 21 21:52:58 2015 +0200 Add parsePattern parser entry point Reviewers: austin, thomie, alanz Reviewed By: thomie, alanz Subscribers: thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1005 GHC Trac Issues: #10556 >--------------------------------------------------------------- 38f374571290b8115ef5b82587ac2ec6c18e91f1 compiler/parser/Parser.y | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y index 5414735..d5d8c6c 100644 --- a/compiler/parser/Parser.y +++ b/compiler/parser/Parser.y @@ -31,7 +31,8 @@ -- parseState = mkPState flags buffer location -- @ module Parser (parseModule, parseImport, parseStatement, - parseDeclaration, parseExpression, parseTypeSignature, + parseDeclaration, parseExpression, parsePattern, + parseTypeSignature, parseFullStmt, parseStmt, parseIdentifier, parseType, parseHeader) where @@ -561,6 +562,7 @@ TH_QQUASIQUOTE { L _ (ITqQuasiQuote _) } %name parseStatement stmt %name parseDeclaration topdecl %name parseExpression exp +%name parsePattern pat %name parseTypeSignature sigdecl %name parseFullStmt stmt %name parseStmt maybe_stmt From git at git.haskell.org Mon Jun 22 09:34:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 22 Jun 2015 09:34:15 +0000 (UTC) Subject: [commit: ghc] master: Documentation: add section on .haskeline file (#2531) (b5a2e87) Message-ID: <20150622093415.F1B9F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b5a2e8763fcf0e2b4c57e12f2b2e5817e5ce9df0/ghc >--------------------------------------------------------------- commit b5a2e8763fcf0e2b4c57e12f2b2e5817e5ce9df0 Author: Thomas Miedema Date: Sun Jun 21 20:56:56 2015 +0200 Documentation: add section on .haskeline file (#2531) >--------------------------------------------------------------- b5a2e8763fcf0e2b4c57e12f2b2e5817e5ce9df0 docs/users_guide/ghci.xml | 21 ++++++++++++++++++++- 1 file changed, 20 insertions(+), 1 deletion(-) diff --git a/docs/users_guide/ghci.xml b/docs/users_guide/ghci.xml index 627aa79..d3b65ef 100644 --- a/docs/users_guide/ghci.xml +++ b/docs/users_guide/ghci.xml @@ -3380,7 +3380,11 @@ Then the interactive options are modified as follows: - The <filename>.ghci</filename> file + The <filename>.ghci</filename> and <filename>.haskeline</filename> files + + + The <filename>.ghci</filename> files + .ghcifile startupfiles, GHCi @@ -3536,6 +3540,21 @@ Then the interactive options are modified as follows: + + + + The <filename>.haskeline</filename> file + + .haskelinefile + + startupfiles, GHCi + + + GHCi uses Haskeline + under the hood. You can configure it to, among other things, prune + duplicates from ghci history. See: + Haskeline user preferences. + From git at git.haskell.org Mon Jun 22 12:45:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 22 Jun 2015 12:45:48 +0000 (UTC) Subject: [commit: ghc] wip/impredicativity: Refactor constraint gen. for App and SectionL (4c719be) Message-ID: <20150622124548.BB95B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/impredicativity Link : http://ghc.haskell.org/trac/ghc/changeset/4c719bebaae9552a102406d29df875528181fab1/ghc >--------------------------------------------------------------- commit 4c719bebaae9552a102406d29df875528181fab1 Author: Alejandro Serrano Date: Mon Jun 22 14:44:59 2015 +0200 Refactor constraint gen. for App and SectionL Now both cases use common code, so propagation works regardless of whether you write (op x y) or ((x `op) y). The code for SectionR is now broken. >--------------------------------------------------------------- 4c719bebaae9552a102406d29df875528181fab1 compiler/typecheck/TcExpr.hs | 190 ++++++++++++++++++++++++++++--------------- 1 file changed, 124 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 4c719bebaae9552a102406d29df875528181fab1 From git at git.haskell.org Mon Jun 22 13:07:13 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 22 Jun 2015 13:07:13 +0000 (UTC) Subject: [commit: ghc] wip/impredicativity: Fix constraint generation for SectionR (0cb0c47) Message-ID: <20150622130713.C22413A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/impredicativity Link : http://ghc.haskell.org/trac/ghc/changeset/0cb0c47f524c3d76c52ecc023ac3b03404283305/ghc >--------------------------------------------------------------- commit 0cb0c47f524c3d76c52ecc023ac3b03404283305 Author: Alejandro Serrano Date: Mon Jun 22 15:06:57 2015 +0200 Fix constraint generation for SectionR >--------------------------------------------------------------- 0cb0c47f524c3d76c52ecc023ac3b03404283305 compiler/typecheck/TcExpr.hs | 37 +++++++++++++++++++------------------ 1 file changed, 19 insertions(+), 18 deletions(-) diff --git a/compiler/typecheck/TcExpr.hs b/compiler/typecheck/TcExpr.hs index 6b3cae4..c4e81a6 100644 --- a/compiler/typecheck/TcExpr.hs +++ b/compiler/typecheck/TcExpr.hs @@ -323,17 +323,16 @@ tcExpr app@(OpApp _ _ _ _) res_ty = tcApp app res_ty -- \ x -> op x expr tcExpr (SectionR op arg2) res_ty - = do { -- res_ty = arg1_ty -> op_res_ty - (co_fn, [arg1_ty], op_res_ty) <- unifyOpFunTysWrap op 1 res_ty - -- op_ty - arg1_ty -> new var -> op_res_ty - ; op_arg_ty <- tc_app_inst 1 op_res_ty - ; let op_ty = mkFunTy arg1_ty op_arg_ty - ; op' <- tcCheckFun op op_ty - ; (co_fn, [arg1_ty, arg2_ty], op_res_ty) <- unifyOpFunTysWrap op 2 op_ty - ; co_res <- unifyType (mkFunTy arg1_ty op_res_ty) res_ty + = do { -- res_ty = arg1_ty -> rest_ty + (co_fun, [arg1_ty], rest_ty) <- + matchExpectedFunTys (mk_app_msg op) 1 res_ty + ; arg2_ty <- newFlexiTyVarTy openTypeKind + -- op_ty = arg1_ty -> arg2_ty -> rest_ty + ; let op_ty = mkFunTys [arg1_ty,arg2_ty] rest_ty + -- typecheck op and arg2 + ; op' <- tcCheckFun op op_ty ; arg2' <- tcArg op (arg2, arg2_ty, 2) - ; return $ mkHsWrapCo co_res $ - SectionR (mkLHsWrapCo co_fn op') arg2' } + ; return $ SectionR (mkLHsWrapCo co_fun op') arg2' } tcExpr app@(SectionL _ _) res_ty = tcApp app res_ty @@ -939,7 +938,7 @@ tcAppWorker _ (L loc (SectionL arg1 op)) args res_ty tcAppWorker _ (L loc (SectionR op arg2)) (arg1:args) res_ty = do { result <- tcAppWorker' op (arg1:arg2:args) res_ty ; return $ stepTcAppResult result $ \op' (arg1':arg2':args') co' -> - NormalTcAppResult (L loc (SectionR arg2' op')) (arg1':args') co' } + NormalTcAppResult (L loc (SectionR op' arg2')) (arg1':args') co' } tcAppWorker special fun@(L loc (HsVar fun_name)) args res_ty | fun_name `hasKey` tagToEnumKey @@ -1000,13 +999,15 @@ tc_app fun args fun_ty res_ty special -- Extract its argument types ; (co_fun, expected_arg_tys, actual_res_ty) <- case special of - TcAppNormal -> matchExpectedFunTys (mk_app_msg fun) (length args) fun_ty - TcAppSectionL -> -- We need return type to be of form a -> b - do { (co_fun_l, expected_l, actual_res_l) <- - matchExpectedFunTys (mk_app_msg fun) (length args + 1) fun_ty - ; return ( co_fun_l - , init expected_l - , mkFunTy (last expected_l) actual_res_l) } + TcAppNormal + -> matchExpectedFunTys (mk_app_msg fun) (length args) fun_ty + TcAppSectionL + -> -- We need return type to be of form a -> b + do { (co_fun_l, expected_l, actual_res_l) <- + matchExpectedFunTys (mk_app_msg fun) (length args + 1) fun_ty + ; return ( co_fun_l + , init expected_l + , mkFunTy (last expected_l) actual_res_l) } ; traceTc "tc_app/2" (vcat [ppr expected_arg_tys, ppr actual_res_ty]) From git at git.haskell.org Mon Jun 22 13:44:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 22 Jun 2015 13:44:45 +0000 (UTC) Subject: [commit: ghc] master: Check KnownSymbol => Typeable deduction (e60dbf3) Message-ID: <20150622134445.345D73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e60dbf30adfcc0ba90ed9271239c0c8a7bc14f06/ghc >--------------------------------------------------------------- commit e60dbf30adfcc0ba90ed9271239c0c8a7bc14f06 Author: Gabor Greif Date: Mon Jun 22 15:40:01 2015 +0200 Check KnownSymbol => Typeable deduction verifying fix for #10348 >--------------------------------------------------------------- e60dbf30adfcc0ba90ed9271239c0c8a7bc14f06 testsuite/tests/typecheck/should_compile/T10348.hs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/typecheck/should_compile/T10348.hs b/testsuite/tests/typecheck/should_compile/T10348.hs index 7380d81..dadb8aa 100644 --- a/testsuite/tests/typecheck/should_compile/T10348.hs +++ b/testsuite/tests/typecheck/should_compile/T10348.hs @@ -1,9 +1,10 @@ -{-# LANGUAGE AutoDeriveTypeable, GADTs, DataKinds, KindSignatures, StandaloneDeriving #-} +{-# LANGUAGE AutoDeriveTypeable, GADTs, DataKinds, KindSignatures, StandaloneDeriving, TypeOperators #-} module T10348 where import GHC.TypeLits import Data.Typeable +import Data.Proxy data Foo (n :: Nat) where Hey :: KnownNat n => Foo n @@ -27,4 +28,5 @@ f1 = typeRep g2 :: KnownSymbol a => Proxy a -> TypeRep g2 = typeRep - +pEqT :: (KnownSymbol a, KnownSymbol b) => Proxy a -> Proxy b -> Maybe (a :~: b) +pEqT Proxy Proxy = eqT From git at git.haskell.org Mon Jun 22 17:32:05 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 22 Jun 2015 17:32:05 +0000 (UTC) Subject: [commit: ghc] master: Fix #10551 by using LIB_NAMES. (6c5a66a) Message-ID: <20150622173205.DAD4E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6c5a66a225fcd65eb3abe32cc2128b0b90440451/ghc >--------------------------------------------------------------- commit 6c5a66a225fcd65eb3abe32cc2128b0b90440451 Author: Edward Z. Yang Date: Sat Jun 20 16:15:41 2015 -0700 Fix #10551 by using LIB_NAMES. Summary: (NB: this code is dead at the moment since Windows is not built dynamically.) Signed-off-by: Edward Z. Yang Test Plan: none Reviewers: austin Subscribers: thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1001 GHC Trac Issues: #10551 >--------------------------------------------------------------- 6c5a66a225fcd65eb3abe32cc2128b0b90440451 rules/build-prog.mk | 2 +- utils/ghc-cabal/Main.hs | 5 ----- 2 files changed, 1 insertion(+), 6 deletions(-) diff --git a/rules/build-prog.mk b/rules/build-prog.mk index f2f6ad2..eca3358 100644 --- a/rules/build-prog.mk +++ b/rules/build-prog.mk @@ -241,7 +241,7 @@ $1/$2/build/tmp/$$($1_$2_PROG)-wrapper.c: driver/utils/dynwrapper.c | $$$$(dir $ echo '#include ' >> $$@ echo '#include "Rts.h"' >> $$@ echo 'LPTSTR path_dirs[] = {' >> $$@ - $$(foreach p,$$($1_$2_TRANSITIVE_DEP_KEYS),$$(call make-command,echo ' TEXT("/../lib/$$p")$$(comma)' >> $$@)) + $$(foreach p,$$($1_$2_TRANSITIVE_DEP_LIB_NAMES),$$(call make-command,echo ' TEXT("/../lib/$$p")$$(comma)' >> $$@)) echo ' TEXT("/../lib/"),' >> $$@ echo ' NULL};' >> $$@ echo 'LPTSTR progDll = TEXT("../lib/$$($1_$2_PROG).dll");' >> $$@ diff --git a/utils/ghc-cabal/Main.hs b/utils/ghc-cabal/Main.hs index 6302349..77caf58 100644 --- a/utils/ghc-cabal/Main.hs +++ b/utils/ghc-cabal/Main.hs @@ -411,10 +411,6 @@ generate directory distdir dll0Modules config_args transitive_dep_ids = map Installed.sourcePackageId dep_pkgs transitiveDeps = map display transitive_dep_ids - transitiveDepKeys - | packageKeySupported comp - = map (display . Installed.packageKey) dep_pkgs - | otherwise = transitiveDeps transitiveDepLibNames | packageKeySupported comp = map (\p -> packageKeyLibraryName @@ -451,7 +447,6 @@ generate directory distdir dll0Modules config_args variablePrefix ++ "_DEP_IPIDS = " ++ unwords dep_ipids, variablePrefix ++ "_DEP_NAMES = " ++ unwords depNames, variablePrefix ++ "_TRANSITIVE_DEPS = " ++ unwords transitiveDeps, - variablePrefix ++ "_TRANSITIVE_DEP_KEYS = " ++ unwords transitiveDepKeys, variablePrefix ++ "_TRANSITIVE_DEP_LIB_NAMES = " ++ unwords transitiveDepLibNames, variablePrefix ++ "_TRANSITIVE_DEP_NAMES = " ++ unwords transitiveDepNames, variablePrefix ++ "_INCLUDE_DIRS = " ++ unwords (includeDirs bi), From git at git.haskell.org Mon Jun 22 17:32:08 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 22 Jun 2015 17:32:08 +0000 (UTC) Subject: [commit: ghc] master: Rename $1_$2_$3_LIB_NAME to LIB_FILE. (01f7e44) Message-ID: <20150622173208.9B1AE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/01f7e440ce221c01ba082003c372b5420e42797b/ghc >--------------------------------------------------------------- commit 01f7e440ce221c01ba082003c372b5420e42797b Author: Edward Z. Yang Date: Sat Jun 20 16:23:58 2015 -0700 Rename $1_$2_$3_LIB_NAME to LIB_FILE. Summary: When we introduced user-friendly library names (e.g. unix-2.7.1.0-G4Yo1pNtYrk8nCq1cx8P9d instead of unix_G4Yo1pNtYrk8nCq1cx8P9d) we added a new variable to be written out by ghc-cabal, $1_$2_LIB_NAME. What I didn't realize at the time was that this conflicts with an existing variable in the build system, $1_$2_$3_LIB_NAME, which (confusingly) refers to something like 'libHSunix-2.7.1.0-G4Yo1pNtYrk8nCq1cx8P9d.so'. This is pretty confusing (despite never conflicting), so I renamed this variable to LIB_FILE for enhanced greppability. Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: austin Subscribers: thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1002 >--------------------------------------------------------------- 01f7e440ce221c01ba082003c372b5420e42797b ghc.mk | 2 +- rts/ghc.mk | 4 ++-- rules/build-package-way.mk | 4 ++-- 3 files changed, 5 insertions(+), 5 deletions(-) diff --git a/ghc.mk b/ghc.mk index bee6abf..1b50472 100644 --- a/ghc.mk +++ b/ghc.mk @@ -229,7 +229,7 @@ endif ifeq "$(GhcDebugged)" "YES" WINDOWS_DYN_PROG_RTS := $(WINDOWS_DYN_PROG_RTS)_debug endif -WINDOWS_DYN_PROG_RTS := $(WINDOWS_DYN_PROG_RTS)_dyn_LIB_NAME +WINDOWS_DYN_PROG_RTS := $(WINDOWS_DYN_PROG_RTS)_dyn_LIB_FILE # ----------------------------------------------------------------------------- # Compilation Flags diff --git a/rts/ghc.mk b/rts/ghc.mk index 787f67a..7fa36b6 100644 --- a/rts/ghc.mk +++ b/rts/ghc.mk @@ -153,8 +153,8 @@ $(call distdir-way-opts,rts,dist,$1) $(call c-suffix-rules,rts,dist,$1,YES) $(call cmm-suffix-rules,rts,dist,$1) -rts_$1_LIB_NAME = libHSrts$$($1_libsuf) -rts_$1_LIB = rts/dist/build/$$(rts_$1_LIB_NAME) +rts_$1_LIB_FILE = libHSrts$$($1_libsuf) +rts_$1_LIB = rts/dist/build/$$(rts_$1_LIB_FILE) rts_$1_C_OBJS = $$(patsubst rts/%.c,rts/dist/build/%.$$($1_osuf),$$(rts_C_SRCS)) $$(patsubst %.c,%.$$($1_osuf),$$(rts_$1_EXTRA_C_SRCS)) rts_$1_S_OBJS = $$(patsubst rts/%.S,rts/dist/build/%.$$($1_osuf),$$(rts_S_SRCS)) diff --git a/rules/build-package-way.mk b/rules/build-package-way.mk index 27da099..cb8440d 100644 --- a/rules/build-package-way.mk +++ b/rules/build-package-way.mk @@ -23,8 +23,8 @@ $(call hs-objs,$1,$2,$3) # The .a/.so library file, indexed by two different sets of vars: # the first is indexed by the dir, distdir and way # the second is indexed by the package id, distdir and way -$1_$2_$3_LIB_NAME = libHS$$($1_$2_LIB_NAME)$$($3_libsuf) -$1_$2_$3_LIB = $1/$2/build/$$($1_$2_$3_LIB_NAME) +$1_$2_$3_LIB_FILE = libHS$$($1_$2_LIB_NAME)$$($3_libsuf) +$1_$2_$3_LIB = $1/$2/build/$$($1_$2_$3_LIB_FILE) $$($1_$2_PACKAGE_KEY)_$2_$3_LIB = $$($1_$2_$3_LIB) ifeq "$$(HostOS_CPP)" "mingw32" From git at git.haskell.org Mon Jun 22 17:32:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 22 Jun 2015 17:32:11 +0000 (UTC) Subject: [commit: ghc] master: Use -package-id to specify libraries on command line. (f70fb68) Message-ID: <20150622173211.4F18F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f70fb6892f5fd32e6161e951aa3e804148afd2fe/ghc >--------------------------------------------------------------- commit f70fb6892f5fd32e6161e951aa3e804148afd2fe Author: Edward Z. Yang Date: Sat Jun 20 15:35:28 2015 -0700 Use -package-id to specify libraries on command line. Summary: There's not really any good reason to use -package-key over -package-id, so use the latter as standard practice. Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: austin Subscribers: thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1000 >--------------------------------------------------------------- f70fb6892f5fd32e6161e951aa3e804148afd2fe rules/distdir-way-opts.mk | 7 +++---- utils/ghc-cabal/Main.hs | 17 +++++++++-------- 2 files changed, 12 insertions(+), 12 deletions(-) diff --git a/rules/distdir-way-opts.mk b/rules/distdir-way-opts.mk index 8073093..7a4115c 100644 --- a/rules/distdir-way-opts.mk +++ b/rules/distdir-way-opts.mk @@ -87,13 +87,12 @@ $4_USE_PACKAGE_KEY=NO endif endif -ifeq "$($4_USE_PACKAGE_KEY)" "NO" $1_$2_$4_DEP_OPTS = \ - $$(foreach pkg,$$($1_$2_DEPS),-package $$(pkg)) + $$(foreach pkg,$$($1_$2_DEP_IPIDS),-package-id $$(pkg)) + +ifeq "$($4_USE_PACKAGE_KEY)" "NO" $4_THIS_PACKAGE_KEY = -package-name else -$1_$2_$4_DEP_OPTS = \ - $$(foreach pkg,$$($1_$2_DEP_KEYS),-package-key $$(pkg)) $4_THIS_PACKAGE_KEY = -this-package-key endif diff --git a/utils/ghc-cabal/Main.hs b/utils/ghc-cabal/Main.hs index 3c049fe..6302349 100644 --- a/utils/ghc-cabal/Main.hs +++ b/utils/ghc-cabal/Main.hs @@ -396,17 +396,17 @@ generate directory distdir dll0Modules config_args dep_ids = map snd (externalPackageDeps lbi) deps = map display dep_ids + dep_direct = map (fromMaybe (error "ghc-cabal: dep_keys failed") + . PackageIndex.lookupInstalledPackageId + (installedPkgs lbi) + . fst) + . externalPackageDeps + $ lbi dep_keys | packageKeySupported comp - = map (display - . Installed.packageKey - . fromMaybe (error "ghc-cabal: dep_keys failed") - . PackageIndex.lookupInstalledPackageId - (installedPkgs lbi) - . fst) - . externalPackageDeps - $ lbi + = map (display . Installed.packageKey) dep_direct | otherwise = deps + dep_ipids = map (display . Installed.installedPackageId) dep_direct depNames = map (display . packageName) dep_ids transitive_dep_ids = map Installed.sourcePackageId dep_pkgs @@ -448,6 +448,7 @@ generate directory distdir dll0Modules config_args variablePrefix ++ "_HS_SRC_DIRS = " ++ unwords (hsSourceDirs bi), variablePrefix ++ "_DEPS = " ++ unwords deps, variablePrefix ++ "_DEP_KEYS = " ++ unwords dep_keys, + variablePrefix ++ "_DEP_IPIDS = " ++ unwords dep_ipids, variablePrefix ++ "_DEP_NAMES = " ++ unwords depNames, variablePrefix ++ "_TRANSITIVE_DEPS = " ++ unwords transitiveDeps, variablePrefix ++ "_TRANSITIVE_DEP_KEYS = " ++ unwords transitiveDepKeys, From git at git.haskell.org Tue Jun 23 09:16:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Jun 2015 09:16:16 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: Comments (4bdec1b) Message-ID: <20150623091616.D6FAB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/4bdec1b1576508fa522f461c564f815d205d4857/ghc >--------------------------------------------------------------- commit 4bdec1b1576508fa522f461c564f815d205d4857 Author: Simon Peyton Jones Date: Mon Jun 22 15:58:05 2015 +0100 Comments >--------------------------------------------------------------- 4bdec1b1576508fa522f461c564f815d205d4857 compiler/deSugar/Check.hs | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs index c20375d..72e5bf3 100644 --- a/compiler/deSugar/Check.hs +++ b/compiler/deSugar/Check.hs @@ -215,7 +215,12 @@ translatePat usupply pat = case pat of g = GBindAbs pats $ PmExprOther $ HsApp (noLoc to_list) xe -- [...] <- toList x in [xp,g] - ConPatOut { pat_con = L _ (PatSynCon _) } -> -- CHECKME: Is there a way to unfold this into a normal pattern? + ConPatOut { pat_con = L _ (PatSynCon _) } -> + -- Pattern synonyms have a "matcher" (see Note [Pattern synonym representation] in PatSyn.hs + -- We should be able to transform (P x y) + -- to v (Just (x, y) <- matchP v (\x y -> Just (x,y)) Nothing + -- That is, a combination of a variable pattern and a guard + -- But there are complications with GADTs etc, and this isn't done yet [mkPmVar usupply (hsPatType pat)] ConPatOut { pat_con = L _ (RealDataCon con), pat_args = ps } -> From git at git.haskell.org Tue Jun 23 09:16:19 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Jun 2015 09:16:19 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: Edits by George and Simon (2de6e5a) Message-ID: <20150623091619.8D0E93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/2de6e5af0dd7b3228fb47597d5d893f939f0df90/ghc >--------------------------------------------------------------- commit 2de6e5af0dd7b3228fb47597d5d893f939f0df90 Author: Simon Peyton Jones Date: Tue Jun 23 10:16:43 2015 +0100 Edits by George and Simon >--------------------------------------------------------------- 2de6e5af0dd7b3228fb47597d5d893f939f0df90 compiler/deSugar/Check.hs | 98 +++++++++++++++++++++++++++++++++-------------- 1 file changed, 69 insertions(+), 29 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 2de6e5af0dd7b3228fb47597d5d893f939f0df90 From git at git.haskell.org Tue Jun 23 11:31:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Jun 2015 11:31:36 +0000 (UTC) Subject: [commit: ghc] wip/impredicativity: Fix problems with ($) and InstanceOf constraints (10161e6) Message-ID: <20150623113136.5090A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/impredicativity Link : http://ghc.haskell.org/trac/ghc/changeset/10161e65d6aa92ade7d479e77787188e04c4f214/ghc >--------------------------------------------------------------- commit 10161e65d6aa92ade7d479e77787188e04c4f214 Author: Alejandro Serrano Date: Tue Jun 23 10:28:44 2015 +0200 Fix problems with ($) and InstanceOf constraints - Ensure that the correct constraints are generated when ($) is applied to several known arguments - Fix a problem in the second rule for canonicalization of InstanceOf where the incorrect eq was generated - Add a fallback case for irreducible InstanceOf constraints to make them go to the inert set (previously an error was raised). >--------------------------------------------------------------- 10161e65d6aa92ade7d479e77787188e04c4f214 compiler/typecheck/TcCanonical.hs | 12 +++-- compiler/typecheck/TcExpr.hs | 104 ++++++++++++++++++++++---------------- 2 files changed, 68 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 10161e65d6aa92ade7d479e77787188e04c4f214 From git at git.haskell.org Tue Jun 23 11:31:39 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Jun 2015 11:31:39 +0000 (UTC) Subject: [commit: ghc] wip/impredicativity: Track monomorphism of variables in environment and implement approximation. (88275a7) Message-ID: <20150623113139.0B1553A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/impredicativity Link : http://ghc.haskell.org/trac/ghc/changeset/88275a7b29d9deb113e06c7ec9f9a198949504d1/ghc >--------------------------------------------------------------- commit 88275a7b29d9deb113e06c7ec9f9a198949504d1 Author: Alejandro Serrano Date: Tue Jun 23 13:28:46 2015 +0200 Track monomorphism of variables in environment and implement approximation. - The code in TcPat has been changed to tag (term) varibles introduced in the environment with an expected type of a (type) variable. This is later used in TcExpr to decide whether to emit an equality or instantiation constraint when that (term) variable is found. - Implement approximation of InstanceOf constraints by a System FC-type with the least amount of polymorphism. >--------------------------------------------------------------- 88275a7b29d9deb113e06c7ec9f9a198949504d1 compiler/typecheck/TcBinds.hs | 2 +- compiler/typecheck/TcCanonical.hs | 2 +- compiler/typecheck/TcPat.hs | 13 +++++++++--- compiler/typecheck/TcSimplify.hs | 43 +++++++++++++++++++++++++++++++-------- 4 files changed, 46 insertions(+), 14 deletions(-) diff --git a/compiler/typecheck/TcBinds.hs b/compiler/typecheck/TcBinds.hs index c00bd8f..a818919 100644 --- a/compiler/typecheck/TcBinds.hs +++ b/compiler/typecheck/TcBinds.hs @@ -387,7 +387,7 @@ tc_group top_lvl sig_fn prag_fn (Recursive, binds) thing_inside go :: [SCC (LHsBind Name)] -> TcM (LHsBinds TcId, thing) go (scc:sccs) = do { (binds1, ids1) <- tc_scc scc - ; let uids1 = map (\x -> (x, TcIdUnrestricted)) ids1 + ; let uids1 = map (\x -> (x, TcIdMonomorphic)) ids1 ; (binds2, thing) <- tcExtendLetEnv top_lvl uids1 $ go sccs ; return (binds1 `unionBags` binds2, thing) } diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index 0756e6f..5c7363c 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -1671,7 +1671,7 @@ can_instance_of (CInstanceOfCan { cc_ev = ev, cc_lhs = lhs, cc_rhs = rhs }) do { (qvars, q, ty) <- splitInst lhs -- generate new constraints ; new_ev_qs <- mapM (newWantedEvVarNC loc) q - ; let eq = mkTcEqPredRole Nominal ty rhs + ; let eq = mkTcEqPred ty rhs ; new_ev_ty <- newWantedEvVarNC loc eq -- compute the evidence for the instantiation ; let qvars' = map TyVarTy qvars diff --git a/compiler/typecheck/TcPat.hs b/compiler/typecheck/TcPat.hs index 1540a92..88e6f65 100644 --- a/compiler/typecheck/TcPat.hs +++ b/compiler/typecheck/TcPat.hs @@ -483,7 +483,7 @@ tc_pat :: PatEnv tc_pat penv (VarPat name) pat_ty thing_inside = do { (co, id) <- tcPatBndr penv name pat_ty - ; res <- tcExtendIdEnv1 name id TcIdUnrestricted thing_inside + ; res <- tcExtendIdEnv1 name id (chooseInstFlavor pat_ty) thing_inside ; return (mkHsWrapPatCo co (VarPat id) pat_ty, res) } tc_pat penv (ParPat pat) pat_ty thing_inside @@ -520,7 +520,7 @@ tc_pat _ (WildPat _) pat_ty thing_inside tc_pat penv (AsPat (L nm_loc name) pat) pat_ty thing_inside = do { (co, bndr_id) <- setSrcSpan nm_loc (tcPatBndr penv name pat_ty) - ; (pat', res) <- tcExtendIdEnv1 name bndr_id TcIdUnrestricted $ + ; (pat', res) <- tcExtendIdEnv1 name bndr_id (chooseInstFlavor pat_ty) $ tc_lpat pat (idType bndr_id) penv thing_inside -- NB: if we do inference on: -- \ (y@(x::forall a. a->a)) = e @@ -657,7 +657,7 @@ tc_pat penv (NPlusKPat (L nm_loc name) (L loc lit) ge minus) pat_ty thing_inside ; icls <- tcLookupClass integralClassName ; instStupidTheta orig [mkClassPred icls [pat_ty']] - ; res <- tcExtendIdEnv1 name bndr_id TcIdUnrestricted thing_inside + ; res <- tcExtendIdEnv1 name bndr_id (chooseInstFlavor pat_ty) thing_inside ; return (mkHsWrapPatCo co pat' pat_ty, res) } tc_pat _ _other_pat _ _ = panic "tc_pat" -- ConPatOut, SigPatOut @@ -672,6 +672,13 @@ unifyPatType actual_ty expected_ty = do { coi <- unifyType actual_ty expected_ty ; return (mkTcSymCo coi) } +chooseInstFlavor :: TcSigmaType -> TcIdFlavor +chooseInstFlavor ty + -- if type is a variable, we need to add a monomorphic + -- flag for the environment + | Just _ <- tcGetTyVar_maybe ty = TcIdMonomorphic + | otherwise = TcIdUnrestricted + {- Note [Hopping the LIE in lazy patterns] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs index 5b35437..cef26dc 100644 --- a/compiler/typecheck/TcSimplify.hs +++ b/compiler/typecheck/TcSimplify.hs @@ -444,8 +444,9 @@ simplifyInfer rhs_tclvl apply_mr name_taus wanteds -- NB: must include derived errors in this test, -- hence "incl_derivs" - else do { let quant_cand = approximateWC wanted_transformed - meta_tvs = filter isMetaTyVar (varSetElems (tyVarsOfCts quant_cand)) + else do { quant_cand <- runTcSWithEvBinds null_ev_binds_var $ approximateWC wanted_transformed + ; traceTc "simplifyInfer/quant_cand = " (ppr quant_cand) + ; let meta_tvs = filter isMetaTyVar (varSetElems (tyVarsOfCts quant_cand)) ; gbl_tvs <- tcGetGlobalTyVars -- Miminise quant_cand. We are not interested in any evidence -- produced, because we are going to simplify wanted_transformed @@ -1294,10 +1295,13 @@ defaultTyVar the_tv | otherwise = return the_tv -- The common case -approximateWC :: WantedConstraints -> Cts +approximateWC :: WantedConstraints -> TcS Cts +approximateWC = fmap andManyCts . mapM instantiateWC . bagToList . approximateWC_ + +approximateWC_ :: WantedConstraints -> Cts -- Postcondition: Wanted or Derived Cts -- See Note [ApproximateWC] -approximateWC wc +approximateWC_ wc = float_wc emptyVarSet wc where float_wc :: TcTyVarSet -> WantedConstraints -> Cts @@ -1327,6 +1331,20 @@ approximateWC wc do_bag :: (a -> Bag c) -> Bag a -> Bag c do_bag f = foldrBag (unionBags.f) emptyBag +instantiateWC :: Ct -> TcS Cts +instantiateWC ct + | isWantedCt ct, InstanceOfPred lhs rhs <- classifyPredType (ctPred ct) + = do { let loc = ctLoc ct + ; (_qvars, q, ty) <- splitInst lhs + ; new_ev_qs <- mapM (newWantedEvVarNC loc) q + ; let eq = mkTcEqPred ty rhs + ; new_ev_ty <- newWantedEvVarNC loc eq + ; return $ consCts + (mkNonCanonical new_ev_ty) + (listToBag (map mkNonCanonical new_ev_qs)) } + | otherwise = return (singleCt ct) + + {- Note [ApproximateWC] ~~~~~~~~~~~~~~~~~~~~ @@ -1660,7 +1678,7 @@ applyDefaultingRules wanteds = do { info@(default_tys, _) <- getDefaultInfo ; wanteds <- TcS.zonkWC wanteds - ; let groups = findDefaultableGroups info wanteds + ; groups <- findDefaultableGroups info wanteds ; traceTcS "applyDefaultingRules {" $ vcat [ text "wanteds =" <+> ppr wanteds @@ -1673,12 +1691,20 @@ applyDefaultingRules wanteds ; return (or something_happeneds) } -findDefaultableGroups +findDefaultableGroups :: ([Type], (Bool,Bool)) + -> WantedConstraints + -> TcS [(TyVar, [Ct])] +findDefaultableGroups info wanteds + = do { simples <- approximateWC wanteds + ; return (findDefaultableGroups_ info simples) } + +findDefaultableGroups_ :: ( [Type] , (Bool,Bool) ) -- (Overloaded strings, extended default rules) - -> WantedConstraints -- Unsolved (wanted or derived) + -- -> WantedConstraints -- Unsolved (wanted or derived) + -> Cts -> [(TyVar, [Ct])] -findDefaultableGroups (default_tys, (ovl_strings, extended_defaults)) wanteds +findDefaultableGroups_ (default_tys, (ovl_strings, extended_defaults)) {-wanteds-} simples | null default_tys = [] | otherwise @@ -1687,7 +1713,6 @@ findDefaultableGroups (default_tys, (ovl_strings, extended_defaults)) wanteds , defaultable_tyvar tv , defaultable_classes (map sndOf3 group) ] where - simples = approximateWC wanteds (unaries, non_unaries) = partitionWith find_unary (bagToList simples) unary_groups = equivClasses cmp_tv unaries From git at git.haskell.org Tue Jun 23 12:14:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Jun 2015 12:14:11 +0000 (UTC) Subject: [commit: ghc] master: Further elaborate Trac #10403 test (55843f1) Message-ID: <20150623121411.6687F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/55843f1c43ec3721a924cbbe5d422798819030c1/ghc >--------------------------------------------------------------- commit 55843f1c43ec3721a924cbbe5d422798819030c1 Author: Simon Peyton Jones Date: Tue Jun 23 13:14:26 2015 +0100 Further elaborate Trac #10403 test Adding app1, app2, as requested in the ticket >--------------------------------------------------------------- 55843f1c43ec3721a924cbbe5d422798819030c1 testsuite/tests/partial-sigs/should_compile/T10403.hs | 10 ++++++++-- testsuite/tests/partial-sigs/should_compile/T10403.stderr | 14 +++++++------- 2 files changed, 15 insertions(+), 9 deletions(-) diff --git a/testsuite/tests/partial-sigs/should_compile/T10403.hs b/testsuite/tests/partial-sigs/should_compile/T10403.hs index 6b77e5b..97cda7a 100644 --- a/testsuite/tests/partial-sigs/should_compile/T10403.hs +++ b/testsuite/tests/partial-sigs/should_compile/T10403.hs @@ -12,10 +12,16 @@ instance Functor (B t) where newtype H f = H (f ()) -h :: _ => _ +h1 :: _ => _ -- h :: Functor m => (a -> b) -> m a -> H m -h f b = (H . fmap (const ())) (fmap f b) +h1 f b = (H . fmap (const ())) (fmap f b) h2 :: _ -- h2 :: Functor m => (a -> b) -> m a -> H m h2 f b = (H . fmap (const ())) (fmap f b) + +app1 :: H (B t) +app1 = h1 (H . I) (B ()) + +app2 :: H (B t) +app2 = h2 (H . I) (B ()) diff --git a/testsuite/tests/partial-sigs/should_compile/T10403.stderr b/testsuite/tests/partial-sigs/should_compile/T10403.stderr index fb78b56..9aec3e2 100644 --- a/testsuite/tests/partial-sigs/should_compile/T10403.stderr +++ b/testsuite/tests/partial-sigs/should_compile/T10403.stderr @@ -1,20 +1,20 @@ -T10403.hs:15:6: warning: +T10403.hs:15:7: warning: Found hole ?_? with inferred constraints: Functor f - In the type signature for ?h?: _ => _ + In the type signature for ?h1?: _ => _ -T10403.hs:15:11: warning: +T10403.hs:15:12: warning: Found hole ?_? with type: (a -> b) -> f a -> H f Where: ?f? is a rigid type variable bound by - the inferred type of h :: Functor f => (a -> b) -> f a -> H f + the inferred type of h1 :: Functor f => (a -> b) -> f a -> H f at T10403.hs:17:1 ?b? is a rigid type variable bound by - the inferred type of h :: Functor f => (a -> b) -> f a -> H f + the inferred type of h1 :: Functor f => (a -> b) -> f a -> H f at T10403.hs:17:1 ?a? is a rigid type variable bound by - the inferred type of h :: Functor f => (a -> b) -> f a -> H f + the inferred type of h1 :: Functor f => (a -> b) -> f a -> H f at T10403.hs:17:1 - In the type signature for ?h?: _ => _ + In the type signature for ?h1?: _ => _ T10403.hs:19:7: warning: Found hole ?_? with type: (a -> b) -> f a -> H f From git at git.haskell.org Tue Jun 23 12:39:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Jun 2015 12:39:43 +0000 (UTC) Subject: [commit: ghc] master: powerpc: add basic support for PLT relocations (#10402) (c084796) Message-ID: <20150623123943.9E5843A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c0847967caf51ea4ca88d0ffc25fe1bd99dcabed/ghc >--------------------------------------------------------------- commit c0847967caf51ea4ca88d0ffc25fe1bd99dcabed Author: Sergei Trofimovich Date: Tue Jun 23 07:39:34 2015 -0500 powerpc: add basic support for PLT relocations (#10402) Commit a93ab43ab5f40cadbedea2f6342b93c245e91434 enabled support for proper PIC relocations from assembler. Commit adds support for relocations of type: R_PPC_REL16_HI R_PPC_REL16_HA R_PPC_REL16_LO R_PPC_PLTREL24 They are used only when GHC is built in DYNAMIC_GHC_PROGRAMS = NO mode. Verified by running the following test: // cat a.c #include void ffi_a_hello (int i) { fprintf (stderr, "WEEEEEEEE: i=%d\n", i); } -- cat A.hs {-# LANGUAGE ForeignFunctionInterface #-} module A where import Foreign.C foreign import ccall "ffi_a_hello" a :: CInt -> IO () # ghc -fPIC -c a.c -fforce-recomp # ghc -fPIC -c A.hs -fforce-recomp # ghc --interactive ./a.o A ... *A> a 42 WEEEEEEEE: i=42 See gory details in Trac #10402. Signed-off-by: Colin Watson Signed-off-by: Sergei Trofimovich Reviewed By: bgamari, austin Differential Revision: https://phabricator.haskell.org/D996 GHC Trac Issues: #10402 >--------------------------------------------------------------- c0847967caf51ea4ca88d0ffc25fe1bd99dcabed rts/Linker.c | 15 +++++++++++++++ 1 file changed, 15 insertions(+) diff --git a/rts/Linker.c b/rts/Linker.c index f3b170b..2437e83 100644 --- a/rts/Linker.c +++ b/rts/Linker.c @@ -5952,6 +5952,9 @@ do_Elf_Rela_relocations ( ObjectCode* oc, char* ehdrC, *(Elf32_Word *) P = value - P; break; + case R_PPC_PLTREL24: + value -= 0x8000; /* See Note [.LCTOC1 in PPC PIC code] */ + /* fallthrough */ case R_PPC_REL24: delta = value - P; @@ -5972,6 +5975,18 @@ do_Elf_Rela_relocations ( ObjectCode* oc, char* ehdrC, *(Elf_Word *) P = (*(Elf_Word *) P & 0xfc000003) | (delta & 0x3fffffc); break; + + case R_PPC_REL16_LO: + *(Elf32_Half*) P = value - P; + break; + + case R_PPC_REL16_HI: + *(Elf32_Half*) P = (value - P) >> 16; + break; + + case R_PPC_REL16_HA: + *(Elf32_Half*) P = (value + 0x8000 - P) >> 16; + break; # endif #if x86_64_HOST_ARCH From git at git.haskell.org Tue Jun 23 12:42:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Jun 2015 12:42:33 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Add parsePattern parser entry point (dd928e1) Message-ID: <20150623124233.512CD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/dd928e1c3d3f3139856256dac05c1c3a56c087bc/ghc >--------------------------------------------------------------- commit dd928e1c3d3f3139856256dac05c1c3a56c087bc Author: Alan Zimmerman Date: Sun Jun 21 21:52:58 2015 +0200 Add parsePattern parser entry point Reviewers: austin, thomie, alanz Reviewed By: thomie, alanz Subscribers: thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1005 GHC Trac Issues: #10556 (cherry picked from commit 38f374571290b8115ef5b82587ac2ec6c18e91f1) >--------------------------------------------------------------- dd928e1c3d3f3139856256dac05c1c3a56c087bc compiler/parser/Parser.y | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y index 7f3f26a..9006206 100644 --- a/compiler/parser/Parser.y +++ b/compiler/parser/Parser.y @@ -31,7 +31,8 @@ -- parseState = mkPState flags buffer location in -- @ module Parser (parseModule, parseImport, parseStatement, - parseDeclaration, parseExpression, parseTypeSignature, + parseDeclaration, parseExpression, parsePattern, + parseTypeSignature, parseFullStmt, parseStmt, parseIdentifier, parseType, parseHeader) where @@ -434,6 +435,7 @@ TH_QQUASIQUOTE { L _ (ITqQuasiQuote _) } %name parseStatement stmt %name parseDeclaration topdecl %name parseExpression exp +%name parsePattern pat %name parseTypeSignature sigdecl %name parseFullStmt stmt %name parseStmt maybe_stmt From git at git.haskell.org Tue Jun 23 12:42:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Jun 2015 12:42:36 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: powerpc: add basic support for PLT relocations (#10402) (18e0e95) Message-ID: <20150623124236.131E63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/18e0e95fc492a85fac275f600bfd4934c5de45b5/ghc >--------------------------------------------------------------- commit 18e0e95fc492a85fac275f600bfd4934c5de45b5 Author: Sergei Trofimovich Date: Tue Jun 23 07:39:34 2015 -0500 powerpc: add basic support for PLT relocations (#10402) Commit a93ab43ab5f40cadbedea2f6342b93c245e91434 enabled support for proper PIC relocations from assembler. Commit adds support for relocations of type: R_PPC_REL16_HI R_PPC_REL16_HA R_PPC_REL16_LO R_PPC_PLTREL24 They are used only when GHC is built in DYNAMIC_GHC_PROGRAMS = NO mode. Verified by running the following test: // cat a.c #include void ffi_a_hello (int i) { fprintf (stderr, "WEEEEEEEE: i=%d\n", i); } -- cat A.hs {-# LANGUAGE ForeignFunctionInterface #-} module A where import Foreign.C foreign import ccall "ffi_a_hello" a :: CInt -> IO () # ghc -fPIC -c a.c -fforce-recomp # ghc -fPIC -c A.hs -fforce-recomp # ghc --interactive ./a.o A ... *A> a 42 WEEEEEEEE: i=42 See gory details in Trac #10402. Signed-off-by: Colin Watson Signed-off-by: Sergei Trofimovich Reviewed By: bgamari, austin Differential Revision: https://phabricator.haskell.org/D996 GHC Trac Issues: #10402 (cherry picked from commit c0847967caf51ea4ca88d0ffc25fe1bd99dcabed) >--------------------------------------------------------------- 18e0e95fc492a85fac275f600bfd4934c5de45b5 rts/Linker.c | 15 +++++++++++++++ 1 file changed, 15 insertions(+) diff --git a/rts/Linker.c b/rts/Linker.c index 5b30b84..13e222b 100644 --- a/rts/Linker.c +++ b/rts/Linker.c @@ -5956,6 +5956,9 @@ do_Elf_Rela_relocations ( ObjectCode* oc, char* ehdrC, *(Elf32_Word *) P = value - P; break; + case R_PPC_PLTREL24: + value -= 0x8000; /* See Note [.LCTOC1 in PPC PIC code] */ + /* fallthrough */ case R_PPC_REL24: delta = value - P; @@ -5976,6 +5979,18 @@ do_Elf_Rela_relocations ( ObjectCode* oc, char* ehdrC, *(Elf_Word *) P = (*(Elf_Word *) P & 0xfc000003) | (delta & 0x3fffffc); break; + + case R_PPC_REL16_LO: + *(Elf32_Half*) P = value - P; + break; + + case R_PPC_REL16_HI: + *(Elf32_Half*) P = (value - P) >> 16; + break; + + case R_PPC_REL16_HA: + *(Elf32_Half*) P = (value + 0x8000 - P) >> 16; + break; # endif #if x86_64_HOST_ARCH From git at git.haskell.org Tue Jun 23 14:13:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Jun 2015 14:13:32 +0000 (UTC) Subject: [commit: ghc] wip/impredicativity: Fix missing conversion to repr. equality in InstanceOf (ad32e64) Message-ID: <20150623141332.470133A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/impredicativity Link : http://ghc.haskell.org/trac/ghc/changeset/ad32e64bae3ab10d509ed44f7a6f747d28d55413/ghc >--------------------------------------------------------------- commit ad32e64bae3ab10d509ed44f7a6f747d28d55413 Author: Alejandro Serrano Date: Tue Jun 23 16:14:01 2015 +0200 Fix missing conversion to repr. equality in InstanceOf >--------------------------------------------------------------- ad32e64bae3ab10d509ed44f7a6f747d28d55413 compiler/deSugar/DsBinds.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/deSugar/DsBinds.hs b/compiler/deSugar/DsBinds.hs index fa0404f..95656ad 100644 --- a/compiler/deSugar/DsBinds.hs +++ b/compiler/deSugar/DsBinds.hs @@ -1159,12 +1159,12 @@ dsEvInstanceOf _ (EvInstanceOfVar v) = return (Var v) dsEvInstanceOf ty (EvInstanceOfEq co) = do { bndr <- newSysLocalDs ty - ; expr <- dsTcCoercion co (Cast (Var bndr)) + ; expr <- dsTcCoercion co (\c -> Cast (Var bndr) (mkSubCo c)) ; return (mkCoreLams [bndr] expr) } dsEvInstanceOf ty (EvInstanceOfInst qvars co qs) = do { bndr <- newSysLocalDs ty ; qs' <- mapM dsEvTerm qs ; let exprTy = foldl (\e t -> App e (Type t)) (Var bndr) qvars exprEv = foldl App exprTy qs' - ; expr <- dsTcCoercion co (Cast exprEv) + ; expr <- dsTcCoercion co (\c -> Cast exprEv (mkSubCo c)) ; return (mkCoreLams [bndr] expr) } From git at git.haskell.org Tue Jun 23 14:26:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Jun 2015 14:26:26 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: Only one strictness constraint per value vector abstraction (ac699de) Message-ID: <20150623142626.8D5843A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/ac699de5f8e9ac93e07bffeedbb7b60d7e7a5053/ghc >--------------------------------------------------------------- commit ac699de5f8e9ac93e07bffeedbb7b60d7e7a5053 Author: George Karachalias Date: Tue Jun 23 11:46:08 2015 +0200 Only one strictness constraint per value vector abstraction >--------------------------------------------------------------- ac699de5f8e9ac93e07bffeedbb7b60d7e7a5053 compiler/deSugar/Check.hs | 21 ++++++++++----------- 1 file changed, 10 insertions(+), 11 deletions(-) diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs index 7f5854e..4a6b9ee 100644 --- a/compiler/deSugar/Check.hs +++ b/compiler/deSugar/Check.hs @@ -60,7 +60,7 @@ import Control.Monad.Trans.Class (lift) import qualified Data.Map as Map import Data.Map (Map) import Data.List (foldl') - +import Data.Maybe (isNothing, fromJust) import Control.Arrow (first, second) {- @@ -86,7 +86,7 @@ type PmM a = DsM a data PmConstraint = TmConstraint Id PmExpr -- Term equalities: x ~ e | TyConstraint [EvVar] -- Type equalities - | BtConstraint [Id] -- Strictness constraints: x ~ _|_ + | BtConstraint Id -- Strictness constraints: x ~ _|_ data Abstraction = P | V -- Used to parameterise PmPat @@ -488,7 +488,7 @@ divergent usupply (ConAbs c1 args1 : ps) (Cons (ConAbs c2 args2) vsa) -- DConVar [NEEDS WORK] divergent usupply (ConAbs con args : ps) (Cons (VarAbs x) vsa) - = Union (Cons (VarAbs x) (Constraint [BtConstraint [x]] vsa)) + = Union (Cons (VarAbs x) (Constraint [BtConstraint x] vsa)) (divergent usupply2 (ConAbs con args : ps) (con_abs `consValSetAbs` (all_cs `addConstraints` vsa))) where (usupply1, usupply2) = splitUniqSupply usupply @@ -638,13 +638,13 @@ valSetAbsToList Singleton = [([],[])] valSetAbsToList (Constraint cs vsa) = [(vs, cs ++ cs') | (vs, cs') <- valSetAbsToList vsa] valSetAbsToList (Cons va vsa) = [(va:vs, cs) | (vs, cs) <- valSetAbsToList vsa] -splitConstraints :: [PmConstraint] -> ([EvVar], [(Id, PmExpr)], [Id]) -- Type constraints, term constraints, forced variables -splitConstraints [] = ([],[],[]) +splitConstraints :: [PmConstraint] -> ([EvVar], [(Id, PmExpr)], Maybe Id) -- Type constraints, term constraints, forced variables +splitConstraints [] = ([],[],Nothing) splitConstraints (c : rest) = case c of TyConstraint cs -> (cs ++ ty_cs, tm_cs, bot_cs) TmConstraint x e -> (ty_cs, (x,e):tm_cs, bot_cs) - BtConstraint cs -> (ty_cs, tm_cs, cs ++ bot_cs) + BtConstraint cs -> ASSERT (isNothing bot_cs) (ty_cs, tm_cs, Just cs) -- NB: Only one x ~ _|_ where (ty_cs, tm_cs, bot_cs) = splitConstraints rest @@ -667,10 +667,10 @@ satisfiable constraints = do Left failure -> return $ failure >> return False -- inconsistent term constraints/overloaded syntax Right (residual, (expr_eqs, mapping)) -> let finals = forcedVars mapping -- lazily - answer = null bot_cs || -- just term eqs ==> OK (success) + answer = isNothing bot_cs || -- just term eqs ==> OK (success) notNull residual || -- something we cannot reason about -- gives inaccessible while it shouldn't notNull expr_eqs || -- something we cannot reason about - all (`Map.notMember` finals) bot_cs + fromJust bot_cs `Map.notMember` finals in return $ Just answer False -> return (Just False) -- inconsistent type constraints @@ -1242,9 +1242,8 @@ pprUncovered vsa = vcat (map pprOne vsa) instance Outputable PmConstraint where ppr (TmConstraint x expr) = ppr x <+> equals <+> ppr expr - ppr (TyConstraint theta) = pprSet $ map idType theta - ppr (BtConstraint bots) = let ppr_bot x = ppr x <+> ptext (sLit "~") <+> ptext (sLit "_|_") - in braces (pprWithCommas ppr_bot bots) + ppr (TyConstraint theta) = empty -- pprSet $ map idType theta + ppr (BtConstraint x) = braces (ppr x <+> ptext (sLit "~") <+> ptext (sLit "_|_")) instance Outputable (PmPat abs) where ppr (GBindAbs pats expr) = ppr pats <+> ptext (sLit "<-") <+> ppr expr From git at git.haskell.org Tue Jun 23 14:26:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Jun 2015 14:26:29 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: Added some fields in constructor abstraction (ConAbs) (0a8925f) Message-ID: <20150623142629.5A7613A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/0a8925f2eaebc6a21548b97ca2fc3978ba79916c/ghc >--------------------------------------------------------------- commit 0a8925f2eaebc6a21548b97ca2fc3978ba79916c Author: George Karachalias Date: Tue Jun 23 14:36:44 2015 +0200 Added some fields in constructor abstraction (ConAbs) * Plus: Tiny work on incremental term equality solving >--------------------------------------------------------------- 0a8925f2eaebc6a21548b97ca2fc3978ba79916c compiler/deSugar/Check.hs | 180 +++++++++++++++++++++++++++++++--------------- 1 file changed, 122 insertions(+), 58 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 0a8925f2eaebc6a21548b97ca2fc3978ba79916c From git at git.haskell.org Tue Jun 23 14:26:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Jun 2015 14:26:32 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: mkPmConPat (c682778) Message-ID: <20150623142632.1B7D33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/c6827780679057b9831e7a73698a0c11dbf287d6/ghc >--------------------------------------------------------------- commit c6827780679057b9831e7a73698a0c11dbf287d6 Author: George Karachalias Date: Tue Jun 23 15:26:24 2015 +0200 mkPmConPat >--------------------------------------------------------------- c6827780679057b9831e7a73698a0c11dbf287d6 compiler/deSugar/Check.hs | 77 ++++++++++++++++++++++++++--------------------- 1 file changed, 42 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 c6827780679057b9831e7a73698a0c11dbf287d6 From git at git.haskell.org Tue Jun 23 14:26:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Jun 2015 14:26:34 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: Short-circuit for covered/divergent + Faster check for diversion (24e2076) Message-ID: <20150623142634.EB8993A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/24e207673fb5393a7f9a9579f1441009fbca270a/ghc >--------------------------------------------------------------- commit 24e207673fb5393a7f9a9579f1441009fbca270a Author: George Karachalias Date: Tue Jun 23 16:10:50 2015 +0200 Short-circuit for covered/divergent + Faster check for diversion >--------------------------------------------------------------- 24e207673fb5393a7f9a9579f1441009fbca270a compiler/deSugar/Check.hs | 59 +++++++++++++++++++++++++---------------------- 1 file changed, 32 insertions(+), 27 deletions(-) diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs index 98cb8d2..6342ab2 100644 --- a/compiler/deSugar/Check.hs +++ b/compiler/deSugar/Check.hs @@ -699,19 +699,31 @@ satisfiable constraints = do True -> case tmOracle tm_cs of Left failure -> return $ failure >> return False -- inconsistent term constraints/overloaded syntax Right (residual, (expr_eqs, mapping)) -> - let finals = forcedVars mapping -- lazily - answer = isNothing bot_cs || -- just term eqs ==> OK (success) + let answer = isNothing bot_cs || -- just term eqs ==> OK (success) notNull residual || -- something we cannot reason about -- gives inaccessible while it shouldn't notNull expr_eqs || -- something we cannot reason about - fromJust bot_cs `Map.notMember` finals + isForced (fromJust bot_cs) mapping in return $ Just answer False -> return (Just False) -- inconsistent type constraints +-- | For coverage & laziness anySatValSetAbs :: ValSetAbs -> PmM (Maybe Bool) -anySatValSetAbs vsa = do - mb_vsa <- pruneValSetAbs vsa - return $ liftM isNotEmptyValSetAbs mb_vsa - +anySatValSetAbs = anySatValSetAbs' [] + where + anySatValSetAbs' :: [PmConstraint] -> ValSetAbs -> PmM (Maybe Bool) + anySatValSetAbs' _cs Empty = return (Just False) + anySatValSetAbs' cs (Union vsa1 vsa2) = orM (anySatValSetAbs' cs vsa1) (anySatValSetAbs' cs vsa2) + anySatValSetAbs' cs Singleton = satisfiable cs + anySatValSetAbs' cs (Constraint cs' vsa) = anySatValSetAbs' (cs' ++ cs) vsa -- in front for faster concatenation + anySatValSetAbs' cs (Cons va vsa) = anySatValSetAbs' cs vsa + + orM m1 m2 = m1 >>= \x -> + case x of + Nothing -> return Nothing + Just True -> return (Just True) + Just False -> m2 + +-- | For exhaustiveness check pruneValSetAbs :: ValSetAbs -> PmM (Maybe ValSetAbs) pruneValSetAbs = pruneValSetAbs' [] where @@ -974,15 +986,8 @@ isFalsePmExpr :: PmExpr -> Bool isFalsePmExpr (PmExprCon c []) = c == falseDataCon isFalsePmExpr _other_expr = False --- ConAbs { cabs_con :: DataCon --- -- , cabs_arg_tys :: [Type] -- The univeral arg types, 1-1 with the universal --- -- -- tyvars of the constructor/pattern synonym --- -- -- Use (conLikeResTy pat_con pat_arg_tys) to get --- -- -- the type of the pattern --- --- -- , cabs_tvs :: [TyVar] -- Existentially bound type variables (tyvars only) --- -- , cabs_dicts :: [EvVar] -- Ditto *coercion variables* and *dictionaries* --- , cabs_args :: [PmPat abs] } :: PmPat abs +isTrivialTrueLHsExpr :: LHsExpr Id -> Bool +isTrivialTrueLHsExpr lexpr = isJust (isTrueLHsExpr lexpr) -- ---------------------------------------------------------------------------- -- | Substitution for PmExpr @@ -1212,12 +1217,11 @@ getValuePmExpr env (PmExprCon c es) = PmExprCon c (map (getValuePmExpr env) es) getValuePmExpr env (PmExprEq e1 e2) = PmExprEq (getValuePmExpr env e1) (getValuePmExpr env e2) getValuePmExpr _ other_expr = other_expr -forcedVars :: PmVarEnv -> PmVarEnv -forcedVars env = Map.filter isForced $ Map.map (getValuePmExpr env) env --terminal elements point to themselves - where - isForced :: PmExpr -> Bool - isForced (PmExprVar _) = False - isForced _other_pmexpr = True +isForced :: Id -> PmVarEnv -> Bool +isForced x env = case getValuePmExpr env (PmExprVar x) of + PmExprVar _ -> False + _other_expr -> True + -- ---------------------------------------------------------------------------- -- NOTE [Representation of substitution] @@ -1278,24 +1282,25 @@ forcedVars env = Map.filter isForced $ Map.map (getValuePmExpr env) env --termin %************************************************************************ -} --- | The env is always a FINAL MAP. NO REDIRECTION --- Assume in input, preserve in output +emptyPmVarEnv :: PmVarEnv +emptyPmVarEnv = Map.empty + solveVarEqI :: VarEq -> PmVarEnv -> Maybe PmVarEnv solveVarEqI (x,y) env = case (Map.lookup x env, Map.lookup y env) of (Nothing, Nothing) -> Just $ Map.insert x (PmExprVar y) env (Just ex, Nothing) -> Just $ Map.insert y ex env (Nothing, Just ey) -> Just $ Map.insert x ey env - (Just ex, Just ey) -> undefined {- Probably no extension, we need to check if ex and ey are unifiable -} + (Just ex, Just ey) -> solveComplexEqI (ex,ey) env solveSimpleEqI :: SimpleEq -> PmVarEnv -> Maybe PmVarEnv solveSimpleEqI (x, e) env = case Map.lookup x env of Nothing -> Just $ Map.insert x e env - Just ex -> undefined {- Just like final case of solveVarEq with e and ex this time -} + Just ex -> solveComplexEqI (e,ex) env solveComplexEqI :: ComplexEq -> PmVarEnv -> Maybe PmVarEnv -solveComplexEqI (e1,e2) env = undefined {- Just like the above final cases -} +solveComplexEqI (e1,e2) env = undefined {- Actual Work -} {- %************************************************************************ From git at git.haskell.org Tue Jun 23 15:09:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Jun 2015 15:09:47 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: [ONGOING WORK] mkOneConFull (18ddf70) Message-ID: <20150623150947.7339E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/18ddf700ef16072440bb19f89c4c7e64a2194e0e/ghc >--------------------------------------------------------------- commit 18ddf700ef16072440bb19f89c4c7e64a2194e0e Author: George Karachalias Date: Tue Jun 23 17:09:50 2015 +0200 [ONGOING WORK] mkOneConFull >--------------------------------------------------------------- 18ddf700ef16072440bb19f89c4c7e64a2194e0e compiler/deSugar/Check.hs | 60 +++++++++++++++++++++++++++++++++++++++++++++ compiler/deSugar/DsGRHSs.hs | 2 +- 2 files changed, 61 insertions(+), 1 deletion(-) diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs index 6342ab2..c307e88 100644 --- a/compiler/deSugar/Check.hs +++ b/compiler/deSugar/Check.hs @@ -62,6 +62,7 @@ import Data.Map (Map) import Data.List (foldl') import Data.Maybe (isNothing, fromJust) import Control.Arrow (first, second) +import DsGRHSs (isTrueLHsExpr) {- This module checks pattern matches for: @@ -533,6 +534,65 @@ divergent _usupply [] (Cons _ _) = panic "divergent: length mismat -- ---------------------------------------------------------------------------- -- | Basic utilities +-- **************************************************************************** +-- **************************************************************************** + +-- drop \tau_x ~ \tau +mkOneConFull :: Id {- x -} -> UniqSupply -> DataCon {- K_i -} -> (ValAbs, [PmConstraint]) +mkOneConFull x usupply con = ... + +(listToBag theta_cs `unionBags` arg_cs `unionBags` res_eq) -- the constraints + + where + res_ty = idType x -- Get the result type from the variable we want to be unified with + -- Otherwise pass explicitly cabs@(Ki ps) so the res_ty will be: + -- res_ty == TyConApp (dataConTyCon (cabs_con cabs)) (cabs_arg_tys cabs) + + -- ConAbs { cabs_con :: DataCon + -- , cabs_arg_tys :: [Type] + -- , cabs_tvs :: [TyVar] + -- , cabs_dicts :: [EvVar] + -- , cabs_args :: [PmPat abs] } + + -- ==> univ_tys = cabs_arg_tys + -- ==> ex_tys = cabs_tvs + -- ==> eq_speq ++ thetas = cabs_dicts + -- ==> arg_tys = ??? + -- ==> dc_res_ty = NO NEED TO HAVE IT. WE CAN CONSTRUCT IT BY APPLYING {T} to {univ_tys} + + (univ_tvs, ex_tvs, eq_spec, thetas, arg_tys, dc_res_ty) = dataConFullSig con + data_tc = dataConTyCon con -- The representation TyCon + + mb_tc_args = case splitTyConApp_maybe res_ty of + Nothing -> Nothing + Just (res_tc, res_tc_tys) + | Just (fam_tc, fam_args, _) <- tyConFamInstSig_maybe data_tc + , let fam_tc_tvs = tyConTyVars fam_tc + -> ASSERT( res_tc == fam_tc ) + case tcMatchTys (mkVarSet fam_tc_tvs) fam_args res_tc_tys of + Just fam_subst -> Just (map (substTyVar fam_subst) fam_tc_tvs) + Nothing -> Nothing + | otherwise + -> ASSERT( res_tc == data_tc ) Just res_tc_tys + + -- ************************************************************************ + (subst, res_eq) = case mb_tc_args of + Nothing -> -- The context type doesn't have a type constructor at the head. + -- so generate an equality. But this doesn't really work if there + -- are kind variables involved + let {- FIXME -} (subst, _) = genInstSkolTyVars loc univ_tvs + {- FIXME -} res_eq = newEqPmM {- USUPPLY -} (substTy subst dc_res_ty) res_ty + in (if any isKindVar univ_tvs + then trace "checkTyPmPat: Danger! Kind variables" () + else ()) `seq` (subst, unitBag res_eq) + Just tys -> (zipTopTvSubst univ_tvs tys, emptyBag) + + {- FIXME -} (subst, _) = genInstSkolTyVarsX loc subst ex_tvs + {- FIXME -} arg_cs = checkTyPmPats args (substTys subst arg_tys) -- Make it pure first to make this work + theta_cs = substTheta subst (eqSpecPreds eq_spec ++ thetas) +-- **************************************************************************** +-- **************************************************************************** + mkOneConFull :: Id -> UniqSupply -> DataCon -> (ValAbs, [PmConstraint]) mkOneConFull x usupply con = (con_abs, all_cs) where diff --git a/compiler/deSugar/DsGRHSs.hs b/compiler/deSugar/DsGRHSs.hs index 1346f8a..9368b32 100644 --- a/compiler/deSugar/DsGRHSs.hs +++ b/compiler/deSugar/DsGRHSs.hs @@ -8,7 +8,7 @@ Matching guarded right-hand-sides (GRHSs) {-# LANGUAGE CPP #-} -module DsGRHSs ( dsGuarded, dsGRHSs, dsGRHS ) where +module DsGRHSs ( dsGuarded, dsGRHSs, dsGRHS, isTrueLHsExpr ) where #include "HsVersions.h" From git at git.haskell.org Tue Jun 23 16:44:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Jun 2015 16:44:09 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: More shared edites (c30b969) Message-ID: <20150623164409.07A0F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/c30b9692c19a5d3cd1d30a3ecbbe54e946f4abdc/ghc >--------------------------------------------------------------- commit c30b9692c19a5d3cd1d30a3ecbbe54e946f4abdc Author: Simon Peyton Jones Date: Tue Jun 23 17:44:35 2015 +0100 More shared edites >--------------------------------------------------------------- c30b9692c19a5d3cd1d30a3ecbbe54e946f4abdc compiler/deSugar/Check.hs | 112 ++++++++++++++++++++++++++++++---------------- 1 file changed, 74 insertions(+), 38 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c30b9692c19a5d3cd1d30a3ecbbe54e946f4abdc From git at git.haskell.org Tue Jun 23 17:59:06 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Jun 2015 17:59:06 +0000 (UTC) Subject: [commit: ghc] master: Make $1 in $1_$2_$3_FOO actually be directory. (73a6265) Message-ID: <20150623175906.4EAEF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/73a6265e040fdbb2c9e75337663aa6879e20e233/ghc >--------------------------------------------------------------- commit 73a6265e040fdbb2c9e75337663aa6879e20e233 Author: Edward Z. Yang Date: Sat Jun 20 16:32:56 2015 -0700 Make $1 in $1_$2_$3_FOO actually be directory. Summary: Previously, we used $1_$2_PACKAGE_KEY to parametrize $1. But the documentation says that $1 should be the directory... and we're now putting the libraries in $1_$2_LIB_NAME. So use /that/. This is just alpha-renaming, so as long as we're consistent, there's no material difference.) I also fixed a bug of a package ID calculation which I missed first time around, which was tickled by this change. BTW, this means DEP_KEYS and TRANSITIVE_DEP_KEYS are unused, so remove them from ghc-cabal. Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: austin Subscribers: thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1010 >--------------------------------------------------------------- 73a6265e040fdbb2c9e75337663aa6879e20e233 rules/build-package-way.mk | 8 ++++---- rules/build-package.mk | 2 +- rules/build-prog.mk | 2 +- utils/ghc-cabal/Main.hs | 10 ++++++---- 4 files changed, 12 insertions(+), 10 deletions(-) diff --git a/rules/build-package-way.mk b/rules/build-package-way.mk index cb8440d..c179159 100644 --- a/rules/build-package-way.mk +++ b/rules/build-package-way.mk @@ -25,7 +25,7 @@ $(call hs-objs,$1,$2,$3) # the second is indexed by the package id, distdir and way $1_$2_$3_LIB_FILE = libHS$$($1_$2_LIB_NAME)$$($3_libsuf) $1_$2_$3_LIB = $1/$2/build/$$($1_$2_$3_LIB_FILE) -$$($1_$2_PACKAGE_KEY)_$2_$3_LIB = $$($1_$2_$3_LIB) +$$($1_$2_LIB_NAME)_$2_$3_LIB = $$($1_$2_$3_LIB) ifeq "$$(HostOS_CPP)" "mingw32" ifneq "$$($1_$2_dll0_HS_OBJS)" "" @@ -42,7 +42,7 @@ endif # Really we should use a consistent scheme for distdirs, but in the # meantime we work around it by defining ghc-_dist-install_way_LIB: ifeq "$$($1_PACKAGE) $2" "ghc stage2" -$$($1_$2_PACKAGE_KEY)_dist-install_$3_LIB = $$($1_$2_$3_LIB) +$$($1_$2_LIB_NAME)_dist-install_$3_LIB = $$($1_$2_$3_LIB) endif # All the .a/.so library file dependencies for this library. @@ -50,8 +50,8 @@ endif # The $(subst stage2,dist-install,..) is needed due to Note # [inconsistent distdirs]. # -# NB: Use DEP_KEYS, since DEPS only contains package IDs -$1_$2_$3_DEPS_LIBS=$$(foreach dep,$$($1_$2_DEP_KEYS),$$($$(dep)_$(subst stage2,dist-install,$2)_$3_LIB)) +# NB: Use DEP_LIB_NAMES for the /directory/ parameter. +$1_$2_$3_DEPS_LIBS=$$(foreach dep,$$($1_$2_DEP_LIB_NAMES),$$($$(dep)_$(subst stage2,dist-install,$2)_$3_LIB)) $1_$2_$3_NON_HS_OBJS = $$($1_$2_$3_CMM_OBJS) $$($1_$2_$3_C_OBJS) $$($1_$2_$3_S_OBJS) $$($1_$2_EXTRA_OBJS) $1_$2_$3_ALL_OBJS = $$($1_$2_$3_HS_OBJS) $$($1_$2_$3_NON_HS_OBJS) diff --git a/rules/build-package.mk b/rules/build-package.mk index 34997cc..f05f230 100644 --- a/rules/build-package.mk +++ b/rules/build-package.mk @@ -133,7 +133,7 @@ $$(foreach way,$$($1_$2_WAYS),$$(eval \ # If dyn libs are not being built then $$($1_$2_dyn_LIB) will just # expand to the empty string, and be ignored. $1_$2_PROGRAM_DEP_LIB = $$($1_$2_v_LIB) $$($1_$2_dyn_LIB) -$$($1_PACKAGE)-$$($1_$2_VERSION)_$2_PROGRAM_DEP_LIB = $$($1_$2_PROGRAM_DEP_LIB) +$$($1_$2_LIB_NAME)_$2_PROGRAM_DEP_LIB = $$($1_$2_PROGRAM_DEP_LIB) # C and S files are possibly built the "dyn" way. ifeq "$$(BuildSharedLibs)" "YES" diff --git a/rules/build-prog.mk b/rules/build-prog.mk index eca3358..1029fdd 100644 --- a/rules/build-prog.mk +++ b/rules/build-prog.mk @@ -189,7 +189,7 @@ ifneq "$$(BINDIST)" "YES" # The quadrupled $'s here are because the __LIB variables aren't # necessarily set when this part of the makefile is read $1/$2/build/tmp/$$($1_$2_PROG) $1/$2/build/tmp/$$($1_$2_PROG).dll : \ - $$(foreach dep,$$($1_$2_DEPS),\ + $$(foreach dep,$$($1_$2_DEP_LIB_NAMES),\ $$(if $$(filter ghc%,$$(dep)),\ $(if $(filter 0,$3),$$(compiler_stage1_PROGRAM_DEP_LIB),\ $(if $(filter 1,$3),$$(compiler_stage2_PROGRAM_DEP_LIB),\ diff --git a/utils/ghc-cabal/Main.hs b/utils/ghc-cabal/Main.hs index 77caf58..ed57fb8 100644 --- a/utils/ghc-cabal/Main.hs +++ b/utils/ghc-cabal/Main.hs @@ -402,11 +402,13 @@ generate directory distdir dll0Modules config_args . fst) . externalPackageDeps $ lbi - dep_keys + dep_ipids = map (display . Installed.installedPackageId) dep_direct + depLibNames | packageKeySupported comp - = map (display . Installed.packageKey) dep_direct + = map (\p -> packageKeyLibraryName + (Installed.sourcePackageId p) + (Installed.packageKey p)) dep_direct | otherwise = deps - dep_ipids = map (display . Installed.installedPackageId) dep_direct depNames = map (display . packageName) dep_ids transitive_dep_ids = map Installed.sourcePackageId dep_pkgs @@ -443,9 +445,9 @@ generate directory distdir dll0Modules config_args variablePrefix ++ "_SYNOPSIS =" ++ synopsis pd, variablePrefix ++ "_HS_SRC_DIRS = " ++ unwords (hsSourceDirs bi), variablePrefix ++ "_DEPS = " ++ unwords deps, - variablePrefix ++ "_DEP_KEYS = " ++ unwords dep_keys, variablePrefix ++ "_DEP_IPIDS = " ++ unwords dep_ipids, variablePrefix ++ "_DEP_NAMES = " ++ unwords depNames, + variablePrefix ++ "_DEP_LIB_NAMES = " ++ unwords depLibNames, variablePrefix ++ "_TRANSITIVE_DEPS = " ++ unwords transitiveDeps, variablePrefix ++ "_TRANSITIVE_DEP_LIB_NAMES = " ++ unwords transitiveDepLibNames, variablePrefix ++ "_TRANSITIVE_DEP_NAMES = " ++ unwords transitiveDepNames, From git at git.haskell.org Tue Jun 23 22:10:24 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Jun 2015 22:10:24 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: `translatePat' made monadic (ac5f0ab) Message-ID: <20150623221024.1299D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/ac5f0ab6bcb35d6cc46b8f09032e1e5e4c219305/ghc >--------------------------------------------------------------- commit ac5f0ab6bcb35d6cc46b8f09032e1e5e4c219305 Author: George Karachalias Date: Tue Jun 23 19:59:59 2015 +0200 `translatePat' made monadic >--------------------------------------------------------------- ac5f0ab6bcb35d6cc46b8f09032e1e5e4c219305 compiler/deSugar/Check.hs | 356 +++++++++++++++++++++++----------------------- 1 file changed, 180 insertions(+), 176 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ac5f0ab6bcb35d6cc46b8f09032e1e5e4c219305 From git at git.haskell.org Tue Jun 23 22:10:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Jun 2015 22:10:26 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: Changed translation of CoPats (data families) (58de1bf) Message-ID: <20150623221026.AE9093A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/58de1bf0393d5070834a336ff49ac08d75e4ff3d/ghc >--------------------------------------------------------------- commit 58de1bf0393d5070834a336ff49ac08d75e4ff3d Author: George Karachalias Date: Tue Jun 23 20:34:27 2015 +0200 Changed translation of CoPats (data families) >--------------------------------------------------------------- 58de1bf0393d5070834a336ff49ac08d75e4ff3d 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 2af3083..5779bb5 100644 --- a/compiler/deSugar/Check.hs +++ b/compiler/deSugar/Check.hs @@ -254,7 +254,7 @@ mkPmConPat con arg_tys ex_tvs dicts args translatePat :: Pat Id -> UniqSM PatVec translatePat pat = case pat of - WildPat ty -> getUniqueSupplyM >>= \us -> return [mkPmVar us ty] + WildPat ty -> (:[]) <$> mkPmVarSM ty VarPat id -> return [VarAbs id] ParPat p -> translatePat (unLoc p) LazyPat p -> translatePat (unLoc p) -- COMEHERE: We ignore laziness for now @@ -267,8 +267,13 @@ translatePat pat = case pat of g = GBindAbs ps (PmExprVar (unLoc lid)) return [idp, g] - SigPatOut p ty -> translatePat (unLoc p) -- TODO: Use the signature? - CoPat wrapper p ty -> translatePat p -- TODO: Check if we need the coercion + SigPatOut p ty -> translatePat (unLoc p) -- TODO: Use the signature? + + CoPat wrapper p ty -> do + ps <- translatePat p + (xp,xe) <- mkPmId2FormsSM ty {- IS THIS TYPE CORRECT OR IS IT THE OPPOSITE?? -} + let g = GBindAbs ps $ PmExprOther $ HsWrap wrapper (unLoc xe) + return [xp,g] -- (n + k) ===> x (True <- x >= k) (n <- x-k) NPlusKPat n k ge minus -> do From git at git.haskell.org Tue Jun 23 22:10:29 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Jun 2015 22:10:29 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: Prune Uncovered only at the end (00164a5) Message-ID: <20150623221029.66B8F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/00164a566143591bb04be2724585187730fd9a9c/ghc >--------------------------------------------------------------- commit 00164a566143591bb04be2724585187730fd9a9c Author: George Karachalias Date: Tue Jun 23 21:07:08 2015 +0200 Prune Uncovered only at the end >--------------------------------------------------------------- 00164a566143591bb04be2724585187730fd9a9c compiler/deSugar/Check.hs | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs index 5779bb5..7b9437b 100644 --- a/compiler/deSugar/Check.hs +++ b/compiler/deSugar/Check.hs @@ -186,7 +186,11 @@ check tys eq_info return $ mb_res >>= \(rs, is, us) -> return (rs, is, valSetAbsToList us) check' :: [EquationInfo] -> ValSetAbs -> DsM (Maybe ([EquationInfo], [EquationInfo], ValSetAbs)) -check' [] missing = return $ Just ([], [], missing) +check' [] missing = do + missing' <- pruneValSetAbs missing + return $ case missing' of + Nothing -> Nothing + Just u -> Just ([], [], u) check' (eq:eqs) missing = do -- Translate and process current clause usupply <- getUniqueSupplyM @@ -390,8 +394,7 @@ patVectProc vec vsa = do usD <- getUniqueSupplyM mb_c <- anySatValSetAbs (covered usC vec vsa) mb_d <- anySatValSetAbs (divergent usD vec vsa) - mb_u <- pruneValSetAbs (uncovered usU vec vsa) - return $ liftM3 (,,) mb_c mb_d mb_u + return $ liftM3 (,,) mb_c mb_d (Just $ uncovered usU vec vsa) -- ---------------------------------------------------------------------------- -- | Main function 1 (covered) From git at git.haskell.org Tue Jun 23 22:10:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Jun 2015 22:10:32 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: Improved mkOneConFull (22c1ca0) Message-ID: <20150623221032.204413A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/22c1ca09bc3dc267e081589eabe915dbf95914fc/ghc >--------------------------------------------------------------- commit 22c1ca09bc3dc267e081589eabe915dbf95914fc Author: George Karachalias Date: Wed Jun 24 00:10:35 2015 +0200 Improved mkOneConFull >--------------------------------------------------------------- 22c1ca09bc3dc267e081589eabe915dbf95914fc compiler/deSugar/Check.hs | 117 ++++++++++++++++++------------------------ compiler/typecheck/TcMType.hs | 37 +++++++++++++ 2 files changed, 88 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 22c1ca09bc3dc267e081589eabe915dbf95914fc From git at git.haskell.org Tue Jun 23 22:50:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 23 Jun 2015 22:50:57 +0000 (UTC) Subject: [commit: ghc] master: Build system: delete unused variables in config.mk.in (95d5031) Message-ID: <20150623225057.8C7B93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/95d503103a08418506298c936b76de4ae8651538/ghc >--------------------------------------------------------------- commit 95d503103a08418506298c936b76de4ae8651538 Author: Thomas Miedema Date: Tue Jun 23 17:08:48 2015 +0200 Build system: delete unused variables in config.mk.in GhcStage1DefaultNewCodegen, GhcStage2DefaultNewCodegen, GhcStage3DefaultNewCodegen and GhcCompilerWays are not used anywhere. >--------------------------------------------------------------- 95d503103a08418506298c936b76de4ae8651538 mk/config.mk.in | 14 -------------- 1 file changed, 14 deletions(-) diff --git a/mk/config.mk.in b/mk/config.mk.in index cad5c71..ab177af 100644 --- a/mk/config.mk.in +++ b/mk/config.mk.in @@ -48,10 +48,6 @@ NO_INCLUDE_PKGDATA = NO # The compiler used to build GHC is $(GHC). To change the actual compiler # used, re-configure with --with-ghc=. -# Extra ways in which to build the compiler (for example, you might want to -# build a profiled compiler so you can see where it spends its time) -GhcCompilerWays= - # Extra option flags to pass to the compiler that compiles the compiler # (Ones that are essential are wired into compiler/Makefile) # Typical options to use here: @@ -72,16 +68,6 @@ GhcStage1HcOpts= GhcStage2HcOpts=-O2 GhcStage3HcOpts=-O2 -# These options modify whether or not a built compiler for a bootstrap -# stage defaults to using the new code generation path. The new -# code generation path is a bit slower, so for development just -# GhcStage2DefaultNewCodegen=YES, but it's also a good idea to try -# building all libraries and the stage2 compiler with the -# new code generator, which involves GhcStage1DefaultNewCodegen=YES. -GhcStage1DefaultNewCodegen=NO -GhcStage2DefaultNewCodegen=NO -GhcStage3DefaultNewCodegen=NO - GhcDebugged=NO GhcDynamic=NO From git at git.haskell.org Wed Jun 24 07:32:52 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 24 Jun 2015 07:32:52 +0000 (UTC) Subject: [commit: ghc] wip/impredicativity: Fix problems with the let/app invariant and InstanceOf constraints. (9a816cd) Message-ID: <20150624073252.45D433A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/impredicativity Link : http://ghc.haskell.org/trac/ghc/changeset/9a816cd31115c99419fb4f5019073277cf129c01/ghc >--------------------------------------------------------------- commit 9a816cd31115c99419fb4f5019073277cf129c01 Author: Alejandro Serrano Date: Wed Jun 24 09:32:49 2015 +0200 Fix problems with the let/app invariant and InstanceOf constraints. >--------------------------------------------------------------- 9a816cd31115c99419fb4f5019073277cf129c01 compiler/deSugar/DsBinds.hs | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/compiler/deSugar/DsBinds.hs b/compiler/deSugar/DsBinds.hs index 95656ad..578f77c 100644 --- a/compiler/deSugar/DsBinds.hs +++ b/compiler/deSugar/DsBinds.hs @@ -801,7 +801,7 @@ dsHsWrapper (WpCast co) e = ASSERT(tcCoercionRole co == Representational) dsHsWrapper (WpEvLam ev) e = return $ Lam ev e dsHsWrapper (WpTyLam tv) e = return $ Lam tv e dsHsWrapper (WpEvApp tm) e = liftM (App e) (dsEvTerm tm) -dsHsWrapper (WpEvRevApp tm) e = liftM (flip App e) (dsEvTerm tm) +dsHsWrapper (WpEvRevApp tm) e = liftM (flip mkCoreApp e) (dsEvTerm tm) -------------------------------------- dsTcEvBinds_s :: [TcEvBinds] -> DsM [CoreBind] @@ -1159,12 +1159,12 @@ dsEvInstanceOf _ (EvInstanceOfVar v) = return (Var v) dsEvInstanceOf ty (EvInstanceOfEq co) = do { bndr <- newSysLocalDs ty - ; expr <- dsTcCoercion co (\c -> Cast (Var bndr) (mkSubCo c)) + ; expr <- dsTcCoercion co (\c -> mkCast (Var bndr) (mkSubCo c)) ; return (mkCoreLams [bndr] expr) } dsEvInstanceOf ty (EvInstanceOfInst qvars co qs) = do { bndr <- newSysLocalDs ty ; qs' <- mapM dsEvTerm qs - ; let exprTy = foldl (\e t -> App e (Type t)) (Var bndr) qvars - exprEv = foldl App exprTy qs' - ; expr <- dsTcCoercion co (\c -> Cast exprEv (mkSubCo c)) + ; let exprTy = mkCoreApps (Var bndr) (map Type qvars) + exprEv = mkCoreApps exprTy qs' + ; expr <- dsTcCoercion co (\c -> mkCast exprEv (mkSubCo c)) ; return (mkCoreLams [bndr] expr) } From git at git.haskell.org Wed Jun 24 09:54:06 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 24 Jun 2015 09:54:06 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: more (75a4537) Message-ID: <20150624095406.80B673A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/75a45374d2cd1c8b7b967b5544298b0e3199d2db/ghc >--------------------------------------------------------------- commit 75a45374d2cd1c8b7b967b5544298b0e3199d2db Author: Simon Peyton Jones Date: Wed Jun 24 10:54:31 2015 +0100 more >--------------------------------------------------------------- 75a45374d2cd1c8b7b967b5544298b0e3199d2db compiler/deSugar/Check.hs | 92 +++++++++++++++++++++++++++++++++++------------ 1 file changed, 70 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 75a45374d2cd1c8b7b967b5544298b0e3199d2db From git at git.haskell.org Wed Jun 24 11:38:07 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 24 Jun 2015 11:38:07 +0000 (UTC) Subject: [commit: ghc] wip/impredicativity: Add printing of error messages involving InstanceOf constraints (3dc731c) Message-ID: <20150624113807.E905B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/impredicativity Link : http://ghc.haskell.org/trac/ghc/changeset/3dc731c6c34156994e1d2cbfff791ec6052cfd94/ghc >--------------------------------------------------------------- commit 3dc731c6c34156994e1d2cbfff791ec6052cfd94 Author: Alejandro Serrano Date: Wed Jun 24 13:38:32 2015 +0200 Add printing of error messages involving InstanceOf constraints >--------------------------------------------------------------- 3dc731c6c34156994e1d2cbfff791ec6052cfd94 compiler/typecheck/TcErrors.hs | 19 +++++++++++++++++-- compiler/typecheck/TcSimplify.hs | 1 + 2 files changed, 18 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcErrors.hs b/compiler/typecheck/TcErrors.hs index 36b7947..655bc60 100644 --- a/compiler/typecheck/TcErrors.hs +++ b/compiler/typecheck/TcErrors.hs @@ -348,13 +348,14 @@ reportWanteds ctxt (WC { wc_simple = simples, wc_insol = insols, wc_impl = impli , ("Implicit params", is_ip, False, mkGroupReporter mkIPErr) , ("Irreds", is_irred, False, mkGroupReporter mkIrredErr) - , ("Dicts", is_dict, False, mkGroupReporter mkDictErr) ] + , ("Dicts", is_dict, False, mkGroupReporter mkDictErr) + , ("Instantiation", is_instanceof, False, mkGroupReporter mkInstanceOfErr) ] (&&&) :: (Ct->PredTree->Bool) -> (Ct->PredTree->Bool) -> (Ct->PredTree->Bool) (&&&) p1 p2 ct pred = p1 ct pred && p2 ct pred is_skol_eq, is_hole, is_dict, - is_equality, is_ip, is_irred :: Ct -> PredTree -> Bool + is_equality, is_ip, is_irred, is_instanceof :: Ct -> PredTree -> Bool utterly_wrong _ (EqPred NomEq ty1 ty2) = isRigid ty1 && isRigid ty2 utterly_wrong _ _ = False @@ -378,6 +379,9 @@ reportWanteds ctxt (WC { wc_simple = simples, wc_insol = insols, wc_impl = impli is_irred _ (IrredPred {}) = True is_irred _ _ = False + is_instanceof _ (InstanceOfPred {}) = True + is_instanceof _ _ = False + -- isRigidEqPred :: PredTree -> Bool -- isRigidEqPred (EqPred NomEq ty1 ty2) = isRigid ty1 && isRigid ty2 @@ -1725,3 +1729,14 @@ solverDepthErrorTcS loc ty , text "(any upper bound you could choose might fail unpredictably with" , text " minor updates to GHC, so disabling the check is recommended if" , text " you're sure that type checking should terminate)" ] + +{- +************************************************************************ +* * + Instantiation errors +* * +************************************************************************ +-} + +mkInstanceOfErr :: ReportErrCtxt -> [Ct] -> TcM ErrMsg +mkInstanceOfErr = mkIrredErr -- temporal way to show diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs index cef26dc..94b5e2f 100644 --- a/compiler/typecheck/TcSimplify.hs +++ b/compiler/typecheck/TcSimplify.hs @@ -1696,6 +1696,7 @@ findDefaultableGroups :: ([Type], (Bool,Bool)) -> TcS [(TyVar, [Ct])] findDefaultableGroups info wanteds = do { simples <- approximateWC wanteds + ; traceTcS "findDefaultableGroups" (ppr simples) ; return (findDefaultableGroups_ info simples) } findDefaultableGroups_ From git at git.haskell.org Wed Jun 24 14:11:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 24 Jun 2015 14:11:09 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: tiny (d26c493) Message-ID: <20150624141109.BE3B23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/d26c49350efaf8e9a38fa2bfa09ae6924d5fe055/ghc >--------------------------------------------------------------- commit d26c49350efaf8e9a38fa2bfa09ae6924d5fe055 Author: George Karachalias Date: Wed Jun 24 12:54:53 2015 +0200 tiny >--------------------------------------------------------------- d26c49350efaf8e9a38fa2bfa09ae6924d5fe055 compiler/basicTypes/UniqSupply.hs | 4 ++++ compiler/deSugar/Check.hs | 20 +++++++++----------- 2 files changed, 13 insertions(+), 11 deletions(-) diff --git a/compiler/basicTypes/UniqSupply.hs b/compiler/basicTypes/UniqSupply.hs index 3d0573d..62700a6 100644 --- a/compiler/basicTypes/UniqSupply.hs +++ b/compiler/basicTypes/UniqSupply.hs @@ -18,6 +18,7 @@ module UniqSupply ( -- * Unique supply monad and its abstraction UniqSM, MonadUnique(..), + liftUs, -- ** Operations on the monad initUs, initUs_, @@ -180,6 +181,9 @@ instance MonadUnique UniqSM where getUniqueM = getUniqueUs getUniquesM = getUniquesUs +liftUs :: MonadUnique m => UniqSM a -> m a +liftUs m = getUniqueSupplyM >>= return . flip initUs_ m + getUniqueUs :: UniqSM Unique getUniqueUs = USM (\us -> case takeUniqFromSupply us of (u,us') -> (# u, us' #)) diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs index 499aba8..c7a0632 100644 --- a/compiler/deSugar/Check.hs +++ b/compiler/deSugar/Check.hs @@ -201,8 +201,6 @@ check tys eq_info mb_res <- check' eq_info (initial_uncovered usupply tys) return $ mb_res >>= \(rs, is, us) -> return (rs, is, valSetAbsToList us) -liftUs :: UniqSM a -> DsM a - check' :: [EquationInfo] -> ValSetAbs -> DsM (Maybe ([EquationInfo], [EquationInfo], ValSetAbs)) check' [] missing = do missing' <- pruneValSetAbs missing @@ -211,8 +209,8 @@ check' [] missing = do Just u -> Just ([], [], u) check' (eq:eqs) missing = do -- Translate and process current clause - translated <- liftUs translateEqnInfo eq - pm_result <- patVectProc translated missing + translated <- liftUs (translateEqnInfo eq) + pm_result <- patVectProc translated missing -- Recursively reason about the rest of the match case pm_result of @@ -373,7 +371,7 @@ translatePatVec pats = mapM translatePat pats -- Temporary function (drops the guard (MR at the moment)) translateEqnInfo :: EquationInfo -> UniqSM PatVec translateEqnInfo (EqnInfo { eqn_pats = ps }) - = translatePatVec ps + = concat <$> translatePatVec ps -- ----------------------------------------------------------------------- translateConPatVec :: DataCon -> HsConPatDetails Id -> UniqSM PatVec @@ -438,10 +436,10 @@ covered :: UniqSupply -> PatVec -> ValSetAbs -> ValSetAbs -- Constraint cs vsa -> mkConstraint cs (traverse f us vsa) -- Cons va vsa -> traverseCons f us pv va vsa -traverse2 f us (p gs : pv) va vsa = .... - -traverse2 f us (x : pv) va vsa = .... -traverse2 f us (p gd : pv) va vsa = .... +-- traverse2 f us (p gs : pv) va vsa = .... +-- +-- traverse2 f us (x : pv) va vsa = .... +-- traverse2 f us (p gd : pv) va vsa = .... -- -- @@ -847,7 +845,7 @@ satisfiable constraints = do -- False => Set is definitely empty -- Fact: anySatValSetAbs s = pruneValSetAbs /= Empty -- (but we implement it directly for efficiency) -anySatValSetAbs :: ValSetAbs -> PmM Bool +anySatValSetAbs :: ValSetAbs -> PmM (Maybe Bool) -- TO BOOL anySatValSetAbs = anySatValSetAbs' [] where anySatValSetAbs' :: [PmConstraint] -> ValSetAbs -> PmM (Maybe Bool) @@ -865,7 +863,7 @@ anySatValSetAbs = anySatValSetAbs' [] -- | For exhaustiveness check -- Prune the set by removing unsatisfiable paths -pruneValSetAbs :: ValSetAbs -> PmM ValSetAbs +pruneValSetAbs :: ValSetAbs -> PmM (Maybe ValSetAbs) -- TO BOOL pruneValSetAbs = pruneValSetAbs' [] where pruneValSetAbs' :: [PmConstraint] -> ValSetAbs -> PmM (Maybe ValSetAbs) From git at git.haskell.org Wed Jun 24 14:11:12 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 24 Jun 2015 14:11:12 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: Replaced `pureGenInstSkolTyVarsX' with (the proper) `cloneTyVarBndrs' (e646f44) Message-ID: <20150624141112.7F4803A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/e646f44261501a29a71d0295a71e0bf6f9533763/ghc >--------------------------------------------------------------- commit e646f44261501a29a71d0295a71e0bf6f9533763 Author: George Karachalias Date: Wed Jun 24 15:12:12 2015 +0200 Replaced `pureGenInstSkolTyVarsX' with (the proper) `cloneTyVarBndrs' >--------------------------------------------------------------- e646f44261501a29a71d0295a71e0bf6f9533763 compiler/deSugar/Check.hs | 4 ++-- compiler/typecheck/TcMType.hs | 36 ------------------------------------ compiler/types/Type.hs | 11 ++++++++++- 3 files changed, 12 insertions(+), 39 deletions(-) diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs index c7a0632..eca9977 100644 --- a/compiler/deSugar/Check.hs +++ b/compiler/deSugar/Check.hs @@ -36,7 +36,7 @@ import TcType ( mkTcEqPred, toTcType, toTcTypeBag ) import VarSet import Bag import ErrUtils -import TcMType (pureGenInstSkolTyVarsX, genInstSkolTyVarsX) +import TcMType (genInstSkolTyVarsX) import IOEnv (tryM, failM) import Data.Maybe (isJust) @@ -631,7 +631,7 @@ mkOneConFull x usupply con = (con_abs, constraints) subst1 = zipTopTvSubst univ_tvs tc_args -- IS THE SECOND PART OF THE TUPLE THE SET OF FRESHENED EXISTENTIALS? MUST BE - (subst, ex_tvs') = pureGenInstSkolTyVarsX usupply1 noSrcSpan subst1 ex_tvs + (subst, ex_tvs') = cloneTyVarBndrs subst1 ex_tvs usupply1 arguments = mkConVars usupply2 (substTys subst arg_tys) -- Constructor arguments (value abstractions) theta_cs = substTheta subst (eqSpecPreds eq_spec ++ thetas) -- All the constraints bound by the constructor diff --git a/compiler/typecheck/TcMType.hs b/compiler/typecheck/TcMType.hs index aaa17ea..6276b92 100644 --- a/compiler/typecheck/TcMType.hs +++ b/compiler/typecheck/TcMType.hs @@ -30,11 +30,6 @@ module TcMType ( -- Creating fresh type variables for pm checking genInstSkolTyVarsX, - -- Pure versions - pureGenInstSkolTyVarsX, - pureInstSkolTyVarsX, - pureInstSkolTyVarX, - -------------------------------- -- Creating new evidence variables newEvVar, newEvVars, newEq, newDict, @@ -1017,34 +1012,3 @@ genInstSkolTyVarsX :: SrcSpan -> TvSubst -> [TyVar] -> TcRnIf gbl lcl (TvSubst, -- see Note [Kind substitution when instantiating] -- Get the location from the monad; this is a complete freshening operation genInstSkolTyVarsX loc subst tvs = instSkolTyVarsX (mkTcSkolTyVar loc False) subst tvs - --- PURE VERSIONS -pureGenInstSkolTyVarsX :: UniqSupply -> SrcSpan -> TvSubst -> [TyVar] -> (TvSubst, [TcTyVar]) -pureGenInstSkolTyVarsX usupply loc subst tvs - = pureInstSkolTyVarsX usupply (mkTcSkolTyVar loc False) subst tvs - -pureInstSkolTyVarsX :: UniqSupply - -> (Unique -> Name -> Kind -> TyVar) - -> TvSubst - -> [TyVar] - -> (TvSubst, [TyVar]) -pureInstSkolTyVarsX us mk_tv subst - = mapAccumLU (pureInstSkolTyVarX mk_tv) (us,subst) - where - mapAccumLU :: (UniqSupply -> acc -> x -> (acc, y)) - -> (UniqSupply, acc) -> [x] -> (acc, [y]) - mapAccumLU f (u,s) [] = (s,[]) - mapAccumLU f (u,s) (x:xs) = let (us1, us2) = splitUniqSupply u - (s' , y ) = f us1 s x - (s'', ys) = mapAccumLU f (us2,s') xs - in (s'', y:ys) - -pureInstSkolTyVarX :: (Unique -> Name -> Kind -> TyVar) - -> UniqSupply -> TvSubst -> TyVar -> (TvSubst, TyVar) -pureInstSkolTyVarX mk_tv usupply subst tyvar - = (extendTvSubst subst tyvar (mkTyVarTy new_tv), new_tv) - where - new_tv = mk_tv (uniqFromSupply usupply) old_name kind - old_name = tyVarName tyvar - kind = substTy subst (tyVarKind tyvar) - diff --git a/compiler/types/Type.hs b/compiler/types/Type.hs index edc3067..ab4d2dc 100644 --- a/compiler/types/Type.hs +++ b/compiler/types/Type.hs @@ -122,7 +122,7 @@ module Type ( -- ** Performing substitution on types and kinds substTy, substTys, substTyWith, substTysWith, substTheta, substTyVar, substTyVars, substTyVarBndr, - cloneTyVarBndr, deShadowTy, lookupTyVar, + cloneTyVarBndr, cloneTyVarBndrs, deShadowTy, lookupTyVar, substKiWith, substKisWith, -- * Pretty-printing @@ -168,6 +168,7 @@ import CoAxiom -- others import Unique ( Unique, hasKey ) +import UniqSupply ( UniqSupply, takeUniqFromSupply ) import BasicTypes ( Arity, RepArity ) import Util import ListSetOps ( getNth ) @@ -1642,6 +1643,14 @@ cloneTyVarBndr (TvSubst in_scope tv_env) tv uniq tv' = setVarUnique tv uniq -- Simply set the unique; the kind -- has no type variables to worry about +cloneTyVarBndrs :: TvSubst -> [TyVar] -> UniqSupply -> (TvSubst, [TyVar]) +cloneTyVarBndrs subst [] _usupply = (subst, []) +cloneTyVarBndrs subst (t:ts) usupply = (subst'', tv:tvs) + where + (uniq, usupply') = takeUniqFromSupply usupply + (subst' , tv ) = cloneTyVarBndr subst t uniq + (subst'', tvs) = cloneTyVarBndrs subst' ts usupply' + {- ---------------------------------------------------- -- Kind Stuff From git at git.haskell.org Wed Jun 24 14:11:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 24 Jun 2015 14:11:15 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: Do not issue a special warning for #322, just be conservative (aad0a6f) Message-ID: <20150624141115.3B9FA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/aad0a6f6e2f490b3a5f7ea4aae853d9e42592591/ghc >--------------------------------------------------------------- commit aad0a6f6e2f490b3a5f7ea4aae853d9e42592591 Author: George Karachalias Date: Wed Jun 24 16:11:29 2015 +0200 Do not issue a special warning for #322, just be conservative >--------------------------------------------------------------- aad0a6f6e2f490b3a5f7ea4aae853d9e42592591 compiler/deSugar/Check.hs | 125 +++++++++++++++++++++------------------------- compiler/deSugar/Match.hs | 22 +++----- 2 files changed, 65 insertions(+), 82 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc aad0a6f6e2f490b3a5f7ea4aae853d9e42592591 From git at git.haskell.org Wed Jun 24 15:55:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 24 Jun 2015 15:55:51 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: Some sanity checks (f779623) Message-ID: <20150624155551.E452C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/f779623bb0f79aeb4524b5ae7ca6053aac27dfc1/ghc >--------------------------------------------------------------- commit f779623bb0f79aeb4524b5ae7ca6053aac27dfc1 Author: George Karachalias Date: Wed Jun 24 17:08:52 2015 +0200 Some sanity checks >--------------------------------------------------------------- f779623bb0f79aeb4524b5ae7ca6053aac27dfc1 compiler/deSugar/Check.hs | 37 +++++++++++++++++++++++++++++++++++++ 1 file changed, 37 insertions(+) diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs index 70a043c..620cf23 100644 --- a/compiler/deSugar/Check.hs +++ b/compiler/deSugar/Check.hs @@ -1517,3 +1517,40 @@ To check this match, we should perform arbitrary computations at compile time returning a @Nothing at . -} + +{- +%************************************************************************ +%* * +\subsection{Sanity Checks} +%* * +%************************************************************************ +-} + +type PmArity = Int + +patVecArity :: PatVec -> PmArity +patVecArity = sum . map patternArity + +patternArity :: Pattern -> PmArity +patternArity (GBindAbs {}) = 0 +patternArity (ConAbs {}) = 1 +patternArity (VarAbs {}) = 1 + +-- Should get a default value because an empty set has any arity +-- (We have no value vector abstractions to see) +vsaArity :: PmArity -> ValSetAbs -> PmArity +vsaArity arity Empty = arity +vsaArity _arity vsa = ASSERT (allTheSame arities) (head arities) + where arities = vsaArities vsa + +vsaArities :: ValSetAbs -> [PmArity] -- Arity for every path. INVARIANT: All the same +vsaArities Empty = [] +vsaArities (Union vsa1 vsa2) = vsaArities vsa1 ++ vsaArities vsa2 +vsaArities Singleton = [0] +vsaArities (Constraint _ vsa) = vsaArities vsa +vsaArities (Cons _ vsa) = [1 + arity | arity <- vsaArities vsa] + +allTheSame :: Eq a => [a] -> Bool +allTheSame [] = True +allTheSame (x:xs) = all (==x) xs + From git at git.haskell.org Wed Jun 24 15:55:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 24 Jun 2015 15:55:54 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: Extract the type from a PmPat (pmPatType) + enabled tyOracle (056a846) Message-ID: <20150624155554.9FF343A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/056a846b6011ada2ecc207b4eb11e0d25c206f65/ghc >--------------------------------------------------------------- commit 056a846b6011ada2ecc207b4eb11e0d25c206f65 Author: George Karachalias Date: Wed Jun 24 17:56:05 2015 +0200 Extract the type from a PmPat (pmPatType) + enabled tyOracle >--------------------------------------------------------------- 056a846b6011ada2ecc207b4eb11e0d25c206f65 compiler/deSugar/Check.hs | 28 +++++++++++++++++++--------- 1 file changed, 19 insertions(+), 9 deletions(-) diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs index 620cf23..7c62156 100644 --- a/compiler/deSugar/Check.hs +++ b/compiler/deSugar/Check.hs @@ -39,6 +39,7 @@ import ErrUtils import TcMType (genInstSkolTyVarsX) import IOEnv (tryM, failM) +import Data.List (find) import Data.Maybe (isJust) import Control.Monad ( when, forM, zipWithM, liftM, liftM2, liftM3 ) @@ -47,7 +48,6 @@ import Var (EvVar) import Type import TcRnTypes ( pprInTcRnIf ) -- Shouldn't be here -import TysPrim ( anyTy ) -- Shouldn't be here import UniqSupply -- ( UniqSupply -- , splitUniqSupply -- :: UniqSupply -> (UniqSupply, UniqSupply) -- , listSplitUniqSupply -- :: UniqSupply -> [UniqSupply] @@ -453,12 +453,12 @@ covered usupply vec (Constraint cs vsa) = cs `mkConstraint` covered usupply vec vsa -- CGuard -covered usupply (GBindAbs p e : ps) vsa +covered usupply (pat@(GBindAbs p e) : ps) vsa | vsa' <- tailValSetAbs $ covered usupply2 (p++ps) (VarAbs y `mkCons` vsa) = cs `mkConstraint` vsa' where (usupply1, usupply2) = splitUniqSupply usupply - y = mkPmId usupply1 anyTy -- CHECKME: Which type to use? + y = mkPmId usupply1 (pmPatType pat) cs = [TmConstraint y e] -- CVar @@ -502,11 +502,11 @@ uncovered usupply vec (Union vsa1 vsa2) = uncovered usupply1 vec vsa1 `mkUnion` uncovered usupply vec (Constraint cs vsa) = cs `mkConstraint` uncovered usupply vec vsa -- UGuard -uncovered usupply (GBindAbs p e : ps) vsa +uncovered usupply (pat@(GBindAbs p e) : ps) vsa = cs `mkConstraint` (tailValSetAbs $ uncovered usupply2 (p++ps) (VarAbs y `mkCons` vsa)) where (usupply1, usupply2) = splitUniqSupply usupply - y = mkPmId usupply1 anyTy -- CHECKME: Which type to use? + y = mkPmId usupply1 (pmPatType pat) cs = [TmConstraint y e] -- UVar @@ -556,12 +556,12 @@ divergent usupply vec (Union vsa1 vsa2) = divergent usupply1 vec vsa1 `mkUnion` divergent usupply vec (Constraint cs vsa) = cs `mkConstraint` divergent usupply vec vsa -- DGuard -divergent usupply (GBindAbs p e : ps) vsa +divergent usupply (pat@(GBindAbs p e) : ps) vsa | vsa' <- tailValSetAbs $ divergent usupply2 (p++ps) (VarAbs y `mkCons` vsa) = cs `mkConstraint` vsa' where (usupply1, usupply2) = splitUniqSupply usupply - y = mkPmId usupply1 anyTy -- CHECKME: Which type to use? + y = mkPmId usupply1 (pmPatType pat) cs = [TmConstraint y e] -- DVar @@ -590,6 +590,16 @@ divergent _usupply [] (Cons _ _) = panic "divergent: length mismat -- ---------------------------------------------------------------------------- -- | Basic utilities +-- | Get the type out of a PmPat. For guard patterns (ps <- e) we use the type +-- of the first (or the single -WHEREVER IT IS- valid to use?) pattern +pmPatType :: PmPat abs -> Type +pmPatType (GBindAbs { gabs_pats = pats }) + = ASSERT (patVecArity pats == 1) (pmPatType p) + where Just p = find ((==1) . patternArity) pats +pmPatType (ConAbs { cabs_con = con, cabs_arg_tys = tys }) + = mkTyConApp (dataConTyCon con) tys +pmPatType (VarAbs { vabs_id = x }) = idType x + mkOneConFull :: Id -> UniqSupply -> DataCon -> (ValAbs, [PmConstraint]) -- * x :: T tys, where T is an algebraic data type -- NB: in the case of a data familiy, T is the *representation* TyCon @@ -818,8 +828,8 @@ splitConstraints (c : rest) satisfiable :: [PmConstraint] -> PmM Bool satisfiable constraints = do let (ty_cs, tm_cs, bot_cs) = splitConstraints constraints - -- sat <- tyOracle (listToBag ty_cs) - sat <- return True -- Leave it like this until you fix type constraint generation + sat <- tyOracle (listToBag ty_cs) + -- sat <- return True -- Leave it like this until you fix type constraint generation case sat of True -> case tmOracle tm_cs of Left eq -> pprInTcRnIf (ptext (sLit "this is inconsistent:") <+> ppr eq) >> return False From git at git.haskell.org Wed Jun 24 17:41:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 24 Jun 2015 17:41:09 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: Fixed a bug in strictness analysis (fe5502d) Message-ID: <20150624174109.9EAD13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/fe5502daf983977d62313224b8c13c0154d7a2d6/ghc >--------------------------------------------------------------- commit fe5502daf983977d62313224b8c13c0154d7a2d6 Author: George Karachalias Date: Wed Jun 24 19:41:03 2015 +0200 Fixed a bug in strictness analysis >--------------------------------------------------------------- fe5502daf983977d62313224b8c13c0154d7a2d6 compiler/deSugar/Check.hs | 13 ++++++------- 1 file changed, 6 insertions(+), 7 deletions(-) diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs index 7c62156..309a08c 100644 --- a/compiler/deSugar/Check.hs +++ b/compiler/deSugar/Check.hs @@ -829,15 +829,14 @@ satisfiable :: [PmConstraint] -> PmM Bool satisfiable constraints = do let (ty_cs, tm_cs, bot_cs) = splitConstraints constraints sat <- tyOracle (listToBag ty_cs) - -- sat <- return True -- Leave it like this until you fix type constraint generation case sat of True -> case tmOracle tm_cs of - Left eq -> pprInTcRnIf (ptext (sLit "this is inconsistent:") <+> ppr eq) >> return False + Left eq -> return False Right (residual, (expr_eqs, mapping)) -> let answer = isNothing bot_cs || -- just term eqs ==> OK (success) notNull residual || -- something we cannot reason about -- gives inaccessible while it shouldn't notNull expr_eqs || -- something we cannot reason about - isForced (fromJust bot_cs) mapping + notForced (fromJust bot_cs) mapping -- Was not evaluated before in return answer False -> return False -- inconsistent type constraints @@ -1357,10 +1356,10 @@ getValuePmExpr env (PmExprCon c es) = PmExprCon c (map (getValuePmExpr env) es) getValuePmExpr env (PmExprEq e1 e2) = PmExprEq (getValuePmExpr env e1) (getValuePmExpr env e2) getValuePmExpr _ other_expr = other_expr -isForced :: Id -> PmVarEnv -> Bool -isForced x env = case getValuePmExpr env (PmExprVar x) of - PmExprVar _ -> False - _other_expr -> True +notForced :: Id -> PmVarEnv -> Bool +notForced x env = case getValuePmExpr env (PmExprVar x) of + PmExprVar _ -> True + _other_expr -> False -- ---------------------------------------------------------------------------- From git at git.haskell.org Wed Jun 24 20:53:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 24 Jun 2015 20:53:48 +0000 (UTC) Subject: [commit: ghc] master: Drop prefix from package keys. (ece2c43) Message-ID: <20150624205348.57B763A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ece2c4349718cf89b291ff3c962cbda4805bab43/ghc >--------------------------------------------------------------- commit ece2c4349718cf89b291ff3c962cbda4805bab43 Author: Edward Z. Yang Date: Tue Jun 23 10:41:45 2015 -0700 Drop prefix from package keys. Summary: Contains Cabal submodule update, as Cabal is responsible generating package keys. We also have to update some output. Also comes with a documentation update for ghc-pkg in the user manual for --package-key. Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: simonpj, austin Subscribers: thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1011 GHC Trac Issues: #10550 >--------------------------------------------------------------- ece2c4349718cf89b291ff3c962cbda4805bab43 docs/users_guide/packages.xml | 15 +++++++++++++++ libraries/Cabal | 2 +- testsuite/tests/cabal/cabal07/all.T | 2 +- testsuite/tests/cabal/cabal07/cabal07.stderr | 2 +- testsuite/tests/ghci/scripts/T5979.stderr | 6 +++--- testsuite/tests/ghci/scripts/all.T | 2 +- .../tests/safeHaskell/check/pkg01/ImpSafeOnly07.stderr | 8 ++++---- .../tests/safeHaskell/check/pkg01/ImpSafeOnly08.stderr | 4 ++-- testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout | 6 +++--- testsuite/tests/th/TH_Roles2.stderr | 6 +++--- 10 files changed, 34 insertions(+), 19 deletions(-) diff --git a/docs/users_guide/packages.xml b/docs/users_guide/packages.xml index 7d7200a..555c67f 100644 --- a/docs/users_guide/packages.xml +++ b/docs/users_guide/packages.xml @@ -1118,6 +1118,21 @@ ghc-pkg dot | tred | dot -Tpdf >pkgs.pdf necessarily holds). + + + + + + + + + + Causes ghc-pkg to interpret arguments + as package keys (e.g., an identifier like + I5BErHzyOm07EBNpKBEeUv). Package keys are + used to prefix symbol names GHC produces (e.g., 6VWy06pWzzJq9evDvK2d4w6_DataziByteStringziInternal_unsafePackLenChars_info), so if you need to figure out what package a symbol belongs to, use ghc-pkg with this flag. + + diff --git a/libraries/Cabal b/libraries/Cabal index 9e9e437..03530bf 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit 9e9e4370bbca6af032794225fe5638124acf2d85 +Subproject commit 03530bf99d96f8e8ab00cd18a18222eeba064734 diff --git a/testsuite/tests/cabal/cabal07/all.T b/testsuite/tests/cabal/cabal07/all.T index b2d2680..2286f30 100644 --- a/testsuite/tests/cabal/cabal07/all.T +++ b/testsuite/tests/cabal/cabal07/all.T @@ -4,7 +4,7 @@ else: cleanup = '' def normaliseContainersPackage(str): - return re.sub('containers-[^@]+ at conta_[A-Za-z0-9]+', 'containers-@conta_', str) + return re.sub('containers-[^@]+@[A-Za-z0-9]+', 'containers-@', str) test('cabal07', normalise_errmsg_fun(normaliseContainersPackage), diff --git a/testsuite/tests/cabal/cabal07/cabal07.stderr b/testsuite/tests/cabal/cabal07/cabal07.stderr index ded86e1..39f80ff 100644 --- a/testsuite/tests/cabal/cabal07/cabal07.stderr +++ b/testsuite/tests/cabal/cabal07/cabal07.stderr @@ -1,6 +1,6 @@ Q.hs:3:8: Could not find module ?Data.Set? - It is a member of the hidden package ?containers-@conta_?. + It is a member of the hidden package ?containers-@?. Perhaps you need to add ?containers? to the build-depends in your .cabal file. Use -v to see a list of the files searched for. diff --git a/testsuite/tests/ghci/scripts/T5979.stderr b/testsuite/tests/ghci/scripts/T5979.stderr index 9be8573..b4abfbd 100644 --- a/testsuite/tests/ghci/scripts/T5979.stderr +++ b/testsuite/tests/ghci/scripts/T5979.stderr @@ -2,6 +2,6 @@ : Could not find module ?Control.Monad.Trans.State? Perhaps you meant - Control.Monad.Trans.State (from transformers-0.4.2.0 at trans_) - Control.Monad.Trans.Class (from transformers-0.4.2.0 at trans_) - Control.Monad.Trans.Cont (from transformers-0.4.2.0 at trans_) + Control.Monad.Trans.State (from transformers-@) + Control.Monad.Trans.Class (from transformers-@) + Control.Monad.Trans.Cont (from transformers-@) diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T index 4094a9e..384868e 100755 --- a/testsuite/tests/ghci/scripts/all.T +++ b/testsuite/tests/ghci/scripts/all.T @@ -1,7 +1,7 @@ # coding=utf8 def normaliseTransformersPackageKey(str): - return re.sub('trans_[A-Za-z0-9]+', 'trans_', str) + return re.sub('transformers-[^@]+@[A-Za-z0-9]+', 'transformers-@', str) setTestOpts(when(compiler_profiled(), skip)) diff --git a/testsuite/tests/safeHaskell/check/pkg01/ImpSafeOnly07.stderr b/testsuite/tests/safeHaskell/check/pkg01/ImpSafeOnly07.stderr index 8ee9335..a89ff72 100644 --- a/testsuite/tests/safeHaskell/check/pkg01/ImpSafeOnly07.stderr +++ b/testsuite/tests/safeHaskell/check/pkg01/ImpSafeOnly07.stderr @@ -1,6 +1,6 @@ -: - The package (base-4.8.2.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.5.0) is required to be trusted but it isn't! +: error: + The package (base-4.8.2.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 8ee9335..f4013c0 100644 --- a/testsuite/tests/safeHaskell/check/pkg01/ImpSafeOnly08.stderr +++ b/testsuite/tests/safeHaskell/check/pkg01/ImpSafeOnly08.stderr @@ -1,6 +1,6 @@ : - The package (base-4.8.2.0) is required to be trusted but it isn't! + The package (bytestring-0.10.5.0) is required to be trusted but it isn't! : - The package (bytestring-0.10.5.0) is required to be trusted but it isn't! + The package (base-4.8.2.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 62f18d1..12223e5 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.8.2.0* bytestring-0.10.6.0* deepseq-1.4.1.1 ghc-prim-0.4.0.0 integer-gmp-1.0.0.0 +package dependencies: array-0.5.1.0 bytestring-0.10.6.0* deepseq-1.4.1.1 base-4.8.2.0* ghc-prim-0.4.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.8.2.0* bytestring-0.10.6.0* deepseq-1.4.1.1 ghc-prim-0.4.0.0 integer-gmp-1.0.0.0 +package dependencies: array-0.5.1.0 bytestring-0.10.6.0* deepseq-1.4.1.1 base-4.8.2.0* ghc-prim-0.4.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.8.2.0 bytestring-0.10.6.0* deepseq-1.4.1.1 ghc-prim-0.4.0.0 integer-gmp-1.0.0.0 +package dependencies: array-0.5.1.0 bytestring-0.10.6.0* deepseq-1.4.1.1 base-4.8.2.0 ghc-prim-0.4.0.0 integer-gmp-1.0.0.0 trusted: trustworthy require own pkg trusted: False diff --git a/testsuite/tests/th/TH_Roles2.stderr b/testsuite/tests/th/TH_Roles2.stderr index 97694f2..1c0a217 100644 --- a/testsuite/tests/th/TH_Roles2.stderr +++ b/testsuite/tests/th/TH_Roles2.stderr @@ -4,9 +4,9 @@ TYPE CONSTRUCTORS data T (a :: k) COERCION AXIOMS Dependent modules: [] -Dependent packages: [array-0.5.1.0, base-4.8.2.0, deepseq-1.4.1.1, - ghc-prim-0.3.1.0, integer-gmp-1.0.0.0, pretty-1.1.2.0, - template-haskell-2.10.0.0] +Dependent packages: [array-0.5.1.0, deepseq-1.4.1.1, + pretty-1.1.2.0, base-4.8.2.0, ghc-prim-0.4.0.0, + integer-gmp-1.0.0.0, template-haskell-2.10.0.0] ==================== Typechecker ==================== From git at git.haskell.org Wed Jun 24 21:23:42 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 24 Jun 2015 21:23:42 +0000 (UTC) Subject: [commit: ghc] master: Clean outdated ext-core references in comments. (aa26731) Message-ID: <20150624212342.ED88D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/aa267317bb7b1a71c090234efa7b0edbf64ccadf/ghc >--------------------------------------------------------------- commit aa267317bb7b1a71c090234efa7b0edbf64ccadf Author: Sergei Trofimovich Date: Sun Jun 21 21:11:22 2015 +0100 Clean outdated ext-core references in comments. Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- aa267317bb7b1a71c090234efa7b0edbf64ccadf compiler/typecheck/TcRnTypes.hs | 2 +- testsuite/.gitignore | 1 - 2 files changed, 1 insertion(+), 2 deletions(-) diff --git a/compiler/typecheck/TcRnTypes.hs b/compiler/typecheck/TcRnTypes.hs index 3ec6f2b..411294b 100644 --- a/compiler/typecheck/TcRnTypes.hs +++ b/compiler/typecheck/TcRnTypes.hs @@ -334,7 +334,7 @@ data TcGblEnv = TcGblEnv { tcg_mod :: Module, -- ^ Module being compiled tcg_src :: HscSource, - -- ^ What kind of module (regular Haskell, hs-boot, ext-core) + -- ^ What kind of module (regular Haskell, hs-boot, hsig) tcg_sig_of :: Maybe Module, -- ^ Are we being compiled as a signature of an implementation? tcg_mod_name :: Maybe (Located ModuleName), diff --git a/testsuite/.gitignore b/testsuite/.gitignore index 10b1bfe..09a9dcf 100644 --- a/testsuite/.gitignore +++ b/testsuite/.gitignore @@ -630,7 +630,6 @@ mk/ghcconfig*_inplace_bin_ghc-stage2.exe.mk /tests/dynlibs/T5373B /tests/dynlibs/T5373C /tests/dynlibs/T5373D -/tests/ext-core/T7239.hcr /tests/ffi/should_run/1288 /tests/ffi/should_run/1679 /tests/ffi/should_run/2276 From git at git.haskell.org Wed Jun 24 21:34:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 24 Jun 2015 21:34:38 +0000 (UTC) Subject: [commit: ghc] master: driver: pass '-fPIC' option to all CC invocations (4d1316a) Message-ID: <20150624213438.C1B313A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4d1316a56cb2e763ef6b47f95e529ae799b4c5ff/ghc >--------------------------------------------------------------- commit 4d1316a56cb2e763ef6b47f95e529ae799b4c5ff Author: Sergei Trofimovich Date: Wed Jun 24 22:10:47 2015 +0100 driver: pass '-fPIC' option to all CC invocations Reported by mitchty: When porting ghc to alpine linux (rumors say they build all binaries as Position Independent Executables to leverage global ASLR) linker issued obscure errors: Tiny example: $ echo 'main = print "hello"' > a.hs $ ghc -fforce-recomp a.hs -fPIC -dynamic -optl-pie -o a ld: /tmp/ghc2142_0/ghc2142_5.o: relocation R_X86_64_32 against `ZCMain_main_closure' can not be used when making a shared object; recompile with -fPIC /tmp/ghc2142_0/ghc2142_5.o: error adding symbols: Bad value collect2: error: ld returned 1 exit status There is two entry points in CC driver: 'runPhase' (CC) and 'mkExtraObj' 'mkExtraObj' does not handle most of 'runPhase's complexity. Ideally it should. This patch only adds -fPIC propagation to 'mkExtraObj'. Please merge to stable branch. Signed-off-by: Sergei Trofimovich >--------------------------------------------------------------- 4d1316a56cb2e763ef6b47f95e529ae799b4c5ff compiler/main/DriverPipeline.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs index 1a21202..e2cfd2a 100644 --- a/compiler/main/DriverPipeline.hs +++ b/compiler/main/DriverPipeline.hs @@ -1623,12 +1623,14 @@ mkExtraObj dflags extn xs oFile <- newTempName dflags "o" writeFile cFile xs let rtsDetails = getPackageDetails dflags rtsPackageKey + pic_c_flags = picCCOpts dflags SysTools.runCc dflags ([Option "-c", FileOption "" cFile, Option "-o", FileOption "" oFile] - ++ map (FileOption "-I") (includeDirs rtsDetails)) + ++ map (FileOption "-I") (includeDirs rtsDetails) + ++ map Option pic_c_flags) return oFile -- When linking a binary, we need to create a C main() function that From git at git.haskell.org Thu Jun 25 09:48:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 25 Jun 2015 09:48:45 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: [ongoing] working on a different traversal (dc1b465) Message-ID: <20150625094845.07E8C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/dc1b465a3cbe04ebc633e6a27f196c4d4927b8ed/ghc >--------------------------------------------------------------- commit dc1b465a3cbe04ebc633e6a27f196c4d4927b8ed Author: George Karachalias Date: Thu Jun 25 11:49:10 2015 +0200 [ongoing] working on a different traversal >--------------------------------------------------------------- dc1b465a3cbe04ebc633e6a27f196c4d4927b8ed compiler/deSugar/Check.hs | 91 ++++++++++++++++++++++++++++++++++------------- 1 file changed, 66 insertions(+), 25 deletions(-) diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs index 309a08c..10fde24 100644 --- a/compiler/deSugar/Check.hs +++ b/compiler/deSugar/Check.hs @@ -402,40 +402,83 @@ patVectProc vec vsa = do mb_d <- anySatValSetAbs (divergent usD vec vsa) return (mb_c, mb_d, uncovered usU vec vsa) --- ---------------------------------------------------------------------------- --- | Main function 1 (covered) +--- ---------------------------------------------------------------------------- +data WhatToTo = WTD { wtd_empty :: ValSetAbs -- What to return at the end of the vector + , wtd_mismatch :: ValSetAbs -> ValSetAbs -- ConCon case: what if there is a mismatch? + , wtd_cons :: UniqSupply -> PatVec -> ValAbs -> ValSetAbs -> ValSetAbs } -- FOR NOW -covered :: UniqSupply -> PatVec -> ValSetAbs -> ValSetAbs --- | TODO: After you change the representation of patterns --- traverse :: WhatToTo -> UniqSupply -> ValSetAbs -> ValSetAbs --- --- data WhatToTo = WTD { wtd_empty :: Bool -- True <=> return Singleton --- -- False <=> return Empty --- , wtd_mismatch :: Bool -- True <=> return argument VSA --- -- False <=> return Empty --- , wtd_cons :: PatVec -> ValAbs -> ValSetAbs -> ValSetAbs } --- traverse f us [] vsa = ... --- traverse f us (Guard .. : ps) vsa = .. --- traverse f us (non-gd : ps) vsa = traverse_non_gd f us non_gd ps vs +traverse :: WhatToTo -> UniqSupply -> PatVec -> ValSetAbs -> ValSetAbs +-- | Empty pattern vector +-- Traverse the rest of the Value Set Abstraction +-- to make sure that it is a Singleton +traverse wtd us [] vsa = traverse_non_gd wtd us Nothing vsa + +-- | The Pattern Vector starts with a guard +-- Highest priority (Do not even inspect the Value Set Abstraction) +traverse wtd us (pat@(GBindAbs p e) : ps) vsa + = cs `mkConstraint` (tailValSetAbs $ traverse wtd usupply2 (p++ps) (VarAbs y `mkCons` vsa)) + where + (usupply1, usupply2) = splitUniqSupply usupply + y = mkPmId usupply1 (pmPatType pat) + cs = [TmConstraint y e] +-- | The Pattern Vector starts with a Variable/Constructor pattern +-- Go deeper in the Value Set Abstraction until you meet a cons +traverse wtd us (non_gd : ps) vsa = traverse_non_gd wtd us (Just (non_gd,ps)) vs + + +traverse_non_gd :: WhatToTo -> UniqSupply -> Maybe (Pattern, PatVec) -> ValSetAbs -> ValSetAbs +traverse_non_gd wtd us non_gd vsa = + case vsa of + Empty -> Empty + Singleton -> ASSERT (isNothing non_gd) (wtd_empty wtd) + Union vsa1 vsa2 -> let (us1, us2) = splitUniqSupply us + in mkUnion (traverse_non_gd wtd us1 non_gd vsa) + (traverse_non_gd wtd us2 non_gd vsa) + Constraint cs vsa -> mkConstraint cs (traverse_non_gd wtd us non_gd vsa) + Cons vs vsa -> ASSERT (isJust non_gd) $ + let (p:ps) = fromJust non_gd + in traverseCons wtd us p ps va vsa + +traverseCons :: WhatToTo -> UniqSupply + -> Pattern -> PatternVec + -> ValAbs -> ValSetAbs + -> ValSetAbs +traverseCons wtd us p ps va vsa + = -- = case vsa of --- Empty -> Empty --- Singleton -> ASSERT( null pv ) Singleton --- Union vsa1 vsa2 -> Union (traverse f us1 vsa1) (traverse f us2 vsa2) --- Constraint cs vsa -> mkConstraint cs (traverse f us vsa) --- Cons va vsa -> traverseCons f us pv va vsa +-- Empty -> -- Empty +-- Singleton -> -- ASSERT( null pv ) Singleton +-- Union vsa1 vsa2 -> -- Union (traverse f us1 vsa1) (traverse f us2 vsa2) +-- Constraint cs vsa -> -- mkConstraint cs (traverse f us vsa) +-- Cons va vsa -> -- traverseCons f us pv va vsa + +wtdCovered :: WhatToDo +wtdCovered = WTD { wtd_empty = Singleton + , wtd_mismatch = const Empty + , wtd_cons = undefined {- ??? -} } +wtdUncovered :: WhatToDo +wtdUncovered = WTD { wtd_empty = Empty + , wtd_mismatch = id + , wtd_cons = undefined {- ??? -} } +wtdDivergent :: WhatToDo +wtdDivergent = WTD { wtd_empty = Empty + , wtd_mismatch = const Empty + , wtd_cons = undefined {- ??? -} } -- traverse2 f us (p gs : pv) va vsa = .... -- -- traverse2 f us (x : pv) va vsa = .... -- traverse2 f us (p gd : pv) va vsa = .... - --- -- -- covered pv us vsa = traverse (coveredCons pv) us vsa +--- ---------------------------------------------------------------------------- +-- | Main function 1 (covered) + +covered :: UniqSupply -> PatVec -> ValSetAbs -> ValSetAbs -- CEmpty (New case because of representation) covered _usupply _vec Empty = Empty @@ -454,8 +497,7 @@ covered usupply vec (Constraint cs vsa) -- CGuard covered usupply (pat@(GBindAbs p e) : ps) vsa - | vsa' <- tailValSetAbs $ covered usupply2 (p++ps) (VarAbs y `mkCons` vsa) - = cs `mkConstraint` vsa' + = cs `mkConstraint` (tailValSetAbs $ covered usupply2 (p++ps) (VarAbs y `mkCons` vsa)) where (usupply1, usupply2) = splitUniqSupply usupply y = mkPmId usupply1 (pmPatType pat) @@ -557,8 +599,7 @@ divergent usupply vec (Constraint cs vsa) = cs `mkConstraint` divergent usupply -- DGuard divergent usupply (pat@(GBindAbs p e) : ps) vsa - | vsa' <- tailValSetAbs $ divergent usupply2 (p++ps) (VarAbs y `mkCons` vsa) - = cs `mkConstraint` vsa' + = cs `mkConstraint` (tailValSetAbs $ divergent usupply2 (p++ps) (VarAbs y `mkCons` vsa)) where (usupply1, usupply2) = splitUniqSupply usupply y = mkPmId usupply1 (pmPatType pat) From git at git.haskell.org Thu Jun 25 09:58:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 25 Jun 2015 09:58:49 +0000 (UTC) Subject: [commit: ghc] wip/impredicativity: Implement third rule of InstanceOf canon (40fd9a6) Message-ID: <20150625095849.67BCB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/impredicativity Link : http://ghc.haskell.org/trac/ghc/changeset/40fd9a6bb2fe78e1c9324112714129bf8b3305a4/ghc >--------------------------------------------------------------- commit 40fd9a6bb2fe78e1c9324112714129bf8b3305a4 Author: Alejandro Serrano Date: Thu Jun 25 11:55:51 2015 +0200 Implement third rule of InstanceOf canon Rule InstanceOf sigma2 (forall a. Q1 => tau1) ----> forall a. (Q1 => InstanceOf sigma2 tau1) - Print more information to ease debug in MkCore. >--------------------------------------------------------------- 40fd9a6bb2fe78e1c9324112714129bf8b3305a4 compiler/coreSyn/MkCore.hs | 2 +- compiler/deSugar/DsBinds.hs | 5 +++++ compiler/typecheck/TcCanonical.hs | 9 ++++++++- compiler/typecheck/TcEvidence.hs | 35 ++++++++++++++++++++++++++++------- compiler/typecheck/TcHsSyn.hs | 9 +++++---- compiler/typecheck/TcSMonad.hs | 35 +++++++++++++++++++++++++++++++++++ compiler/typecheck/TcType.hs | 4 ++++ 7 files changed, 86 insertions(+), 13 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 40fd9a6bb2fe78e1c9324112714129bf8b3305a4 From git at git.haskell.org Thu Jun 25 10:53:15 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 25 Jun 2015 10:53:15 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: More (a938d3f) Message-ID: <20150625105315.A13F03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/a938d3fb17978425a0ddcb7eced0158f8381326f/ghc >--------------------------------------------------------------- commit a938d3fb17978425a0ddcb7eced0158f8381326f Author: Simon Peyton Jones Date: Thu Jun 25 11:53:45 2015 +0100 More >--------------------------------------------------------------- a938d3fb17978425a0ddcb7eced0158f8381326f compiler/deSugar/Check.hs | 34 +++++++++++++++++++++++----------- 1 file changed, 23 insertions(+), 11 deletions(-) diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs index 10fde24..d04da40 100644 --- a/compiler/deSugar/Check.hs +++ b/compiler/deSugar/Check.hs @@ -94,6 +94,20 @@ data Abstraction = P | V -- Used to parameterise PmPat type ValAbs = PmPat 'V -- Value Abstraction type Pattern = PmPat 'P -- Pattern +{- +data PatVec = PVNil + | GuardCons Guard PatVec + | PatCons (PmPat PatVec) PatVec + +data ValueVec = VNil + | VCons (PmPat ValueVec) ValueVec + +data PmPat rec_pats + = ConAbs { ... + , cabs_args :: rec_pats } + | VarAbs Id +-} + type PatVec = [Pattern] -- Just a type synonym for pattern vectors ps type ValueVec = [ValAbs] -- Just a type synonym for velue vectors as @@ -245,10 +259,10 @@ falsePmPat = nullaryPmConPat falseDataCon nilPmPat :: Type -> PmPat abs nilPmPat ty = mkPmConPat nilDataCon [ty] [] [] [] -mkListPmPat :: Type -> [PmPat abs] -> [PmPat abs] -> [PmPat abs] -mkListPmPat ty xs ys = [ConAbs { cabs_con = consDataCon, cabs_arg_tys = [ty] +mkListPmPat :: Type -> [PmPat abs] -> [PmPat abs] -> PmPat abs +mkListPmPat ty xs ys = ConAbs { cabs_con = consDataCon, cabs_arg_tys = [ty] , cabs_tvs = [], cabs_dicts = [] - , cabs_args = xs++ys }] + , cabs_args = xs++ys } mkPmConPat :: DataCon -> [Type] -> [TyVar] -> [EvVar] -> [PmPat abs] -> PmPat abs mkPmConPat con arg_tys ex_tvs dicts args @@ -413,7 +427,7 @@ traverse :: WhatToTo -> UniqSupply -> PatVec -> ValSetAbs -> ValSetAbs -- | Empty pattern vector -- Traverse the rest of the Value Set Abstraction -- to make sure that it is a Singleton -traverse wtd us [] vsa = traverse_non_gd wtd us Nothing vsa +traverse wtd us [] vsa = ASSERT( vsaArity vsa == 0 ) vsa -- | The Pattern Vector starts with a guard -- Highest priority (Do not even inspect the Value Set Abstraction) @@ -426,21 +440,19 @@ traverse wtd us (pat@(GBindAbs p e) : ps) vsa -- | The Pattern Vector starts with a Variable/Constructor pattern -- Go deeper in the Value Set Abstraction until you meet a cons -traverse wtd us (non_gd : ps) vsa = traverse_non_gd wtd us (Just (non_gd,ps)) vs +traverse wtd us (non_gd : ps) vsa = traverse_non_gd wtd us non_gd ps vs -traverse_non_gd :: WhatToTo -> UniqSupply -> Maybe (Pattern, PatVec) -> ValSetAbs -> ValSetAbs -traverse_non_gd wtd us non_gd vsa = +traverse_non_gd :: WhatToTo -> UniqSupply -> Pattern -> PatVec -> ValSetAbs -> ValSetAbs +traverse_non_gd wtd us non_gd ps vsa = case vsa of Empty -> Empty - Singleton -> ASSERT (isNothing non_gd) (wtd_empty wtd) + Singleton -> wtd_empty wtd Union vsa1 vsa2 -> let (us1, us2) = splitUniqSupply us in mkUnion (traverse_non_gd wtd us1 non_gd vsa) (traverse_non_gd wtd us2 non_gd vsa) Constraint cs vsa -> mkConstraint cs (traverse_non_gd wtd us non_gd vsa) - Cons vs vsa -> ASSERT (isJust non_gd) $ - let (p:ps) = fromJust non_gd - in traverseCons wtd us p ps va vsa + Cons vs vsa -> traverseCons wtd us non_gd ps va vsa traverseCons :: WhatToTo -> UniqSupply -> Pattern -> PatternVec From git at git.haskell.org Thu Jun 25 10:57:43 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 25 Jun 2015 10:57:43 +0000 (UTC) Subject: [commit: ghc] wip/impredicativity: Add refinement to tcExpr for applications (84db266) Message-ID: <20150625105743.349553A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/impredicativity Link : http://ghc.haskell.org/trac/ghc/changeset/84db2660bac247507f97c9576f5e668bfe22494f/ghc >--------------------------------------------------------------- commit 84db2660bac247507f97c9576f5e668bfe22494f Author: Alejandro Serrano Date: Thu Jun 25 12:29:08 2015 +0200 Add refinement to tcExpr for applications >--------------------------------------------------------------- 84db2660bac247507f97c9576f5e668bfe22494f compiler/typecheck/TcExpr.hs | 40 ++++++++++++++++++++++++++-------------- 1 file changed, 26 insertions(+), 14 deletions(-) diff --git a/compiler/typecheck/TcExpr.hs b/compiler/typecheck/TcExpr.hs index a0fc088..2a39b40 100644 --- a/compiler/typecheck/TcExpr.hs +++ b/compiler/typecheck/TcExpr.hs @@ -874,6 +874,7 @@ tcApp (SectionL arg1 op) res_ty ; result <- tcAppWorker reqd_args op [arg1] res_ty ; return $ consumeTcAppResult result $ \op' [arg1'] -> SectionL arg1' op' } +tcApp expr _ = pprPanic "tcApp shall not be called on " (ppr expr) tcAppWorker' :: LHsExpr Name -> [LHsExpr Name] -> TcRhoType -> TcM TcAppResult @@ -1029,23 +1030,34 @@ tc_app fun args fun_ty res_ty special ; traceTc "tc_app/2" (vcat [ppr expected_arg_tys, ppr actual_res_ty]) - -- Typecheck the result, thereby propagating - -- info (if any) from result into the argument types - -- Both actual_res_ty and res_ty are deeply skolemised - -- Rather like tcWrapResult, but (perhaps for historical reasons) - -- we do this before typechecking the arguments - ; ev_res <- addErrCtxtM (funResCtxt True (unLoc fun) actual_res_ty res_ty) $ - emitWanted AppOrigin (mkInstanceOfPred actual_res_ty res_ty) - -- Typecheck the arguments ; args1 <- tcArgs fun args expected_arg_tys - -- Return the pieces of the result - ; return $ NormalTcAppResult - (mkLHsWrapCo co_fun fun1) -- Instantiated function - args1 -- Arguments - -- Coercion to expected result type - (mkHsWrap (mkWpInstanceOf actual_res_ty ev_res)) } + -- Both actual_res_ty and res_ty are deeply skolemised + -- Split in cases depending on whether res_ty is a variable or not + -- When it is, generate a equality constraint instead of instantiation + -- This is needed to compile some programs such as + -- > data S a = S a + -- > f :: [Char] -> S a + -- > f x = S (error x) + -- Without it, the `a` coming from `f` cannot be unified with + -- the second type variable of `error` + ; case getTyVar_maybe res_ty of + { Nothing + -> do { ev_res <- addErrCtxtM (funResCtxt True (unLoc fun) actual_res_ty res_ty) $ + emitWanted AppOrigin (mkInstanceOfPred actual_res_ty res_ty) + ; return $ NormalTcAppResult + (mkLHsWrapCo co_fun fun1) -- Instantiated function + args1 -- Arguments + -- Coercion to expected result type + (mkHsWrap (mkWpInstanceOf actual_res_ty ev_res)) } + ; Just _ + -> do { co_res <- addErrCtxtM (funResCtxt True (unLoc fun) actual_res_ty res_ty) $ + unifyType actual_res_ty res_ty + ; return $ NormalTcAppResult + (mkLHsWrapCo co_fun fun1) -- Instantiated function + args1 -- Arguments + (mkHsWrapCo co_res) } } } -- Coercion to expected result type mk_app_msg :: LHsExpr Name -> SDoc mk_app_msg fun = sep [ ptext (sLit "The function") <+> quotes (ppr fun) From git at git.haskell.org Thu Jun 25 12:37:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 25 Jun 2015 12:37:36 +0000 (UTC) Subject: [commit: ghc] wip/impredicativity: Fix wrong canonicalization of InstanceOf constraints (3606e9a) Message-ID: <20150625123736.3D36A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/impredicativity Link : http://ghc.haskell.org/trac/ghc/changeset/3606e9adbcb977b1a419c1ef60fae243b7157aa8/ghc >--------------------------------------------------------------- commit 3606e9adbcb977b1a419c1ef60fae243b7157aa8 Author: Alejandro Serrano Date: Thu Jun 25 14:34:34 2015 +0200 Fix wrong canonicalization of InstanceOf constraints Previously, constraints of the form > InstanceOf (forall a. F a => forall b. G a b => ty) that is, where the type is not directly of the form type variables then constraints then a forall-less type, were not handled correctly. This patch ensures that it now works, by replacing the equality constraint that was obtained in that situation with a more general InstanceOf constraint. The evidence generation and desugaring has been changed accordingly. >--------------------------------------------------------------- 3606e9adbcb977b1a419c1ef60fae243b7157aa8 compiler/deSugar/DsBinds.hs | 3 +-- compiler/typecheck/TcCanonical.hs | 6 +++--- compiler/typecheck/TcEvidence.hs | 16 +++++++++------- compiler/typecheck/TcExpr.hs | 30 +++++++++++++++++++----------- compiler/typecheck/TcHsSyn.hs | 4 ++-- 5 files changed, 34 insertions(+), 25 deletions(-) diff --git a/compiler/deSugar/DsBinds.hs b/compiler/deSugar/DsBinds.hs index 085c0e3..9d4d875 100644 --- a/compiler/deSugar/DsBinds.hs +++ b/compiler/deSugar/DsBinds.hs @@ -1166,8 +1166,7 @@ dsEvInstanceOf ty (EvInstanceOfInst qvars co qs) ; qs' <- mapM dsEvTerm qs ; let exprTy = mkCoreApps (Var bndr) (map Type qvars) exprEv = mkCoreApps exprTy qs' - ; expr <- dsTcCoercion co (\c -> mkCast exprEv (mkSubCo c)) - ; return (mkCoreLams [bndr] expr) } + ; return (mkCoreLams [bndr] (mkCoreApp (Var co) exprEv)) } dsEvInstanceOf ty (EvInstanceOfLet tyvars qvars qs rest) = do { bndr <- newSysLocalDs ty ; q_binds <- dsTcEvBinds qs diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index 9fd5393..fd7a191 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -1671,16 +1671,16 @@ can_instance_of (CInstanceOfCan { cc_ev = ev, cc_lhs = lhs, cc_rhs = rhs }) do { (qvars, q, ty) <- splitInst lhs -- generate new constraints ; new_ev_qs <- mapM (newWantedEvVarNC loc) q - ; let eq = mkTcEqPred ty rhs + ; let eq = mkInstanceOfPred ty rhs ; new_ev_ty <- newWantedEvVarNC loc eq -- compute the evidence for the instantiation ; let qvars' = map mkTyVarTy qvars - ; setWantedEvBind evar (mkInstanceOfInst lhs qvars' (ctEvCoercion new_ev_ty) + ; setWantedEvBind evar (mkInstanceOfInst lhs qvars' (ctEvId new_ev_ty) (map ctev_evar new_ev_qs)) -- emit new work ; emitWorkNC new_ev_qs ; traceTcS "can_instance_of/INST" (vcat [ ppr new_ev_ty, ppr new_ev_qs ]) - ; canEqNC new_ev_ty NomEq ty rhs } + ; canInstanceOfNC new_ev_ty } _ -> stopWith ev "Given/Derived instanceOf instantiation" | Just _ <- splitForAllTy_maybe rhs = case ev of diff --git a/compiler/typecheck/TcEvidence.hs b/compiler/typecheck/TcEvidence.hs index c5c9660..faac293 100644 --- a/compiler/typecheck/TcEvidence.hs +++ b/compiler/typecheck/TcEvidence.hs @@ -772,18 +772,20 @@ data EvCallStack data EvInstanceOf = EvInstanceOfVar EvId | EvInstanceOfEq TcCoercion -- ^ term witnessing equality - | EvInstanceOfInst [Type] TcCoercion [EvTerm] - | EvInstanceOfLet [TyVar] -- ^ type variables - [EvId] -- ^ constraint variables - TcEvBinds -- ^ inner bindings - EvId -- ^ inner instantiation constraint + | EvInstanceOfInst [Type] -- ^ type variables to apply + EvId -- ^ witness for inner instantiation + [EvTerm] -- ^ witness for inner constraints + | EvInstanceOfLet [TyVar] -- ^ type variables + [EvId] -- ^ constraint variables + TcEvBinds -- ^ inner bindings + EvId -- ^ inner instantiation constraint deriving ( Data.Data, Data.Typeable ) mkInstanceOfEq :: Type -> TcCoercion -> EvTerm mkInstanceOfEq ty co = EvInstanceOf ty (EvInstanceOfEq co) -mkInstanceOfInst :: Type -> [Type] -> TcCoercion -> [EvVar] -> EvTerm +mkInstanceOfInst :: Type -> [Type] -> EvId -> [EvVar] -> EvTerm mkInstanceOfInst ty vars co q = EvInstanceOf ty (EvInstanceOfInst vars co (map EvId q)) @@ -1056,7 +1058,7 @@ evVarsOfInstanceOf ev = case ev of EvInstanceOfVar v -> unitVarSet v EvInstanceOfEq co -> coVarsOfTcCo co - EvInstanceOfInst _ co q -> coVarsOfTcCo co `unionVarSet` evVarsOfTerms q + EvInstanceOfInst _ co q -> unitVarSet co `unionVarSet` evVarsOfTerms q EvInstanceOfLet _ qvars (EvBinds bs) co -> (foldrBag (unionVarSet . go_bind) (unitVarSet co) bs `minusVarSet` get_bndrs bs) `minusVarSet` mkVarSet qvars diff --git a/compiler/typecheck/TcExpr.hs b/compiler/typecheck/TcExpr.hs index 2a39b40..ea84eec 100644 --- a/compiler/typecheck/TcExpr.hs +++ b/compiler/typecheck/TcExpr.hs @@ -957,7 +957,7 @@ tcAppWorker special fun@(L loc (HsVar fun_name)) args res_ty , (actual_fun@(L loc (HsVar actual_fun_name)) : rest_args) <- args = do { -- Typing without ($) actual_fun_ty <- tc_app_get_fn_ty actual_fun_name - (tc_app_inst (length rest_args) res_ty) + (tc_app_unknown_fn (length rest_args) res_ty) ; result <- tc_app actual_fun rest_args actual_fun_ty res_ty special -- Build the ($) application ; dollar <- tcCheckId fun_name (mkFunTy actual_fun_ty actual_fun_ty) @@ -966,13 +966,13 @@ tcAppWorker special fun@(L loc (HsVar fun_name)) args res_ty | otherwise -- fallback case = do { fun_ty <- tc_app_get_fn_ty fun_name - (tc_app_inst (length args) res_ty) + (tc_app_unknown_fn (length args) res_ty) ; tc_app fun args fun_ty res_ty special } tcAppWorker special fun args res_ty -- Normal case, where the function is not a variable = do { -- Create function type schema - ; fun_ty <- tc_app_inst (length args) res_ty + ; fun_ty <- tc_app_unknown_fn (length args) res_ty -- Run with new type schema ; tc_app fun args fun_ty res_ty special } @@ -991,20 +991,28 @@ tc_app_get_fn_ty fun_name not_found ; return pat_ty } _ -> not_found -- Instantiate type - ; let (tvs, theta, rho) = tcSplitSigmaTy fun_ty - ; (subst, _tvs') <- tcInstTyVars tvs - ; let theta' = substTheta subst theta - rho' = substTy subst rho + ; (theta, rho) <- tc_app_inst fun_ty -- Run with instantiated type - ; _theta_w <- instCallConstraints (OccurrenceOf fun_name) theta' - ; return rho' } + ; _theta_w <- instCallConstraints (OccurrenceOf fun_name) theta + ; return rho } -tc_app_inst :: Int -> TcSigmaType -> TcM TcRhoType -tc_app_inst nb_args res_ty +tc_app_unknown_fn :: Int -> TcSigmaType -> TcM TcRhoType +tc_app_unknown_fn nb_args res_ty = do { args_tys <- replicateM nb_args (newFlexiTyVarTy openTypeKind) ; let fun_ty = mkFunTys args_tys res_ty ; return fun_ty } +tc_app_inst :: TcSigmaType -> TcM (ThetaType, TcRhoType) +tc_app_inst sigma + | Just _ <- splitForAllTy_maybe sigma + = do { let (tvs, theta, ty) = tcSplitSigmaTy sigma + ; (subst, _tvs') <- tcInstTyVars tvs + ; let theta' = substTheta subst theta + ty' = substTy subst ty + ; (theta'', ty'') <- tc_app_inst ty' + ; return (theta' ++ theta'', ty'') } +tc_app_inst ty = return ([], ty) + tc_app :: LHsExpr Name -> [LHsExpr Name] -> TcSigmaType -- type pushed for the function -> TcRhoType -- type pushed for the result diff --git a/compiler/typecheck/TcHsSyn.hs b/compiler/typecheck/TcHsSyn.hs index 0f38770..f9eacf6 100644 --- a/compiler/typecheck/TcHsSyn.hs +++ b/compiler/typecheck/TcHsSyn.hs @@ -1335,8 +1335,8 @@ zonkEvInstanceOf env (EvInstanceOfEq co) ; return (EvInstanceOfEq co') } zonkEvInstanceOf env (EvInstanceOfInst tys co q) = do { tys' <- mapM (zonkTcTypeToType env) tys - ; co' <- zonkTcCoToCo env co - ; q' <- mapM (zonkEvTerm env) q + ; let co' = zonkIdOcc env co + ; q' <- mapM (zonkEvTerm env) q ; return (EvInstanceOfInst tys' co' q') } zonkEvInstanceOf env (EvInstanceOfLet tys qvars bnds i) = do { let qvars' = map (zonkIdOcc env) qvars From git at git.haskell.org Thu Jun 25 13:37:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 25 Jun 2015 13:37:25 +0000 (UTC) Subject: [commit: ghc] wip/impredicativity: Add extra rule to InstanceOf canon + better variable flagging (eb9dff6) Message-ID: <20150625133725.3674F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/impredicativity Link : http://ghc.haskell.org/trac/ghc/changeset/eb9dff6556b69ac612d203224c89bccd91dbfbba/ghc >--------------------------------------------------------------- commit eb9dff6556b69ac612d203224c89bccd91dbfbba Author: Alejandro Serrano Date: Thu Jun 25 15:35:03 2015 +0200 Add extra rule to InstanceOf canon + better variable flagging - The new rule is InstanceOf (forall a. Q => a) ty --> Q[a -> alpha] /\ alpha ~ ty --> Q[ty] This is needed because in many cases when using type classes we come to a point where we have InstanceOf (forall a. C a => a) b and if b is a variable, we cannot continue further without this new rule, leaving unsolved constraints. - The flags for variables (whether on instantiation they will receive an instantiation or a equality constraint) have been rethought and flipped in some cases. >--------------------------------------------------------------- eb9dff6556b69ac612d203224c89bccd91dbfbba compiler/typecheck/TcBinds.hs | 2 +- compiler/typecheck/TcCanonical.hs | 25 +++++++++++++++++++++++++ compiler/typecheck/TcRnDriver.hs | 2 +- compiler/typecheck/TcRules.hs | 2 +- 4 files changed, 28 insertions(+), 3 deletions(-) diff --git a/compiler/typecheck/TcBinds.hs b/compiler/typecheck/TcBinds.hs index a818919..c00bd8f 100644 --- a/compiler/typecheck/TcBinds.hs +++ b/compiler/typecheck/TcBinds.hs @@ -387,7 +387,7 @@ tc_group top_lvl sig_fn prag_fn (Recursive, binds) thing_inside go :: [SCC (LHsBind Name)] -> TcM (LHsBinds TcId, thing) go (scc:sccs) = do { (binds1, ids1) <- tc_scc scc - ; let uids1 = map (\x -> (x, TcIdMonomorphic)) ids1 + ; let uids1 = map (\x -> (x, TcIdUnrestricted)) ids1 ; (binds2, thing) <- tcExtendLetEnv top_lvl uids1 $ go sccs ; return (binds1 `unionBags` binds2, thing) } diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index fd7a191..05d564e 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -1663,6 +1663,31 @@ can_instance_of (CInstanceOfCan { cc_ev = ev, cc_lhs = lhs, cc_rhs = rhs }) -- case InstanceOf (T ...) sigma --> T ... ~ sigma | Nothing <- getTyVar_maybe lhs, Nothing <- splitForAllTy_maybe lhs = can_instance_to_eq ev lhs rhs + -- case InstanceOf (forall a. Q => a) sigma, sigma without forall. + -- in this case, this is equivalent to Q[a -> sigma] + | (_:_, _, v) <- tcSplitSigmaTy lhs, Just _ <- getTyVar_maybe v + , Nothing <- splitForAllTy_maybe rhs + = case ev of + CtWanted { ctev_evar = evar, ctev_loc = loc } -> + do { (qvars, q, ty) <- splitInst lhs + -- generate new constraints + ; new_ev_qs <- mapM (newWantedEvVarNC loc) q + ; let qvars' = map mkTyVarTy qvars + -- generate inner instantiation + ; let inst = mkInstanceOfPred ty rhs + ; inst_ev <- newWantedEvVarNC loc inst + ; let eq = mkEqPred ty rhs + ; eq_ev <- newWantedEvVarNC loc eq + -- compute the evidence for the instantiation + ; setWantedEvBind (ctev_evar inst_ev) + (mkInstanceOfEq ty (ctEvCoercion eq_ev)) + ; setWantedEvBind evar (mkInstanceOfInst lhs qvars' (ctEvId inst_ev) + (map ctev_evar new_ev_qs)) + -- emit new work + ; emitWorkNC new_ev_qs + ; traceTcS "can_instance_of/INST/Top" (vcat [ ppr eq_ev, ppr new_ev_qs ]) + ; canEqNC eq_ev NomEq ty rhs } + _ -> stopWith ev "Given/Derived instanceOf instantiation" -- case InstanceOf (forall qvars. Q => ty) (T ...) | Nothing <- getTyVar_maybe rhs, Nothing <- splitForAllTy_maybe rhs , Just _ <- splitForAllTy_maybe lhs diff --git a/compiler/typecheck/TcRnDriver.hs b/compiler/typecheck/TcRnDriver.hs index 4fa8a4e..39f5814 100644 --- a/compiler/typecheck/TcRnDriver.hs +++ b/compiler/typecheck/TcRnDriver.hs @@ -1453,7 +1453,7 @@ runTcInteractive hsc_env thing_inside , NotTopLevel <- isClosedLetBndr id = Left (idName id, ATcId { tct_id = id , tct_closed = NotTopLevel - , tct_flavor = TcIdMonomorphic }) + , tct_flavor = TcIdUnrestricted }) | otherwise = Right thing diff --git a/compiler/typecheck/TcRules.hs b/compiler/typecheck/TcRules.hs index b948592..80db8c8 100644 --- a/compiler/typecheck/TcRules.hs +++ b/compiler/typecheck/TcRules.hs @@ -68,7 +68,7 @@ tcRule (HsRule name act hs_bndrs lhs fv_lhs rhs fv_rhs) -- the RULE. c.f. Trac #10072 ; let (id_bndrs, tv_bndrs) = partition isId vars - id_bndrs' = [(id_bndr, TcIdMonomorphic) | id_bndr <- id_bndrs] + id_bndrs' = [(id_bndr, TcIdUnrestricted) | id_bndr <- id_bndrs] ; (lhs', lhs_wanted, rhs', rhs_wanted, rule_ty) <- tcExtendTyVarEnv tv_bndrs $ tcExtendIdEnv id_bndrs' $ From git at git.haskell.org Thu Jun 25 14:20:59 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 25 Jun 2015 14:20:59 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: Finished traversal (907def8) Message-ID: <20150625142059.127363A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/907def8d13b22207f91490037b7d3326dbe4b5f6/ghc >--------------------------------------------------------------- commit 907def8d13b22207f91490037b7d3326dbe4b5f6 Author: George Karachalias Date: Thu Jun 25 15:52:53 2015 +0200 Finished traversal >--------------------------------------------------------------- 907def8d13b22207f91490037b7d3326dbe4b5f6 compiler/deSugar/Check.hs | 136 +++++++++++++++++++++++++--------------------- 1 file changed, 73 insertions(+), 63 deletions(-) diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs index d04da40..90cf37a 100644 --- a/compiler/deSugar/Check.hs +++ b/compiler/deSugar/Check.hs @@ -259,10 +259,11 @@ falsePmPat = nullaryPmConPat falseDataCon nilPmPat :: Type -> PmPat abs nilPmPat ty = mkPmConPat nilDataCon [ty] [] [] [] -mkListPmPat :: Type -> [PmPat abs] -> [PmPat abs] -> PmPat abs -mkListPmPat ty xs ys = ConAbs { cabs_con = consDataCon, cabs_arg_tys = [ty] +-- The result wont be a list after the change +mkListPmPat :: Type -> [PmPat abs] -> [PmPat abs] -> [PmPat abs] +mkListPmPat ty xs ys = [ConAbs { cabs_con = consDataCon, cabs_arg_tys = [ty] , cabs_tvs = [], cabs_dicts = [] - , cabs_args = xs++ys } + , cabs_args = xs++ys }] mkPmConPat :: DataCon -> [Type] -> [TyVar] -> [EvVar] -> [PmPat abs] -> PmPat abs mkPmConPat con arg_tys ex_tvs dicts args @@ -417,75 +418,84 @@ patVectProc vec vsa = do return (mb_c, mb_d, uncovered usU vec vsa) --- ---------------------------------------------------------------------------- -data WhatToTo = WTD { wtd_empty :: ValSetAbs -- What to return at the end of the vector +data WhatToDo = WTD { wtd_empty :: ValSetAbs -- What to return at the end of the vector , wtd_mismatch :: ValSetAbs -> ValSetAbs -- ConCon case: what if there is a mismatch? - , wtd_cons :: UniqSupply -> PatVec -> ValAbs -> ValSetAbs -> ValSetAbs } -- FOR NOW + , wtd_cons :: UniqSupply + -> Pattern -> DataCon -> PatVec + -> Id -> ValSetAbs -> ValSetAbs } +wtdC, wtdU, wtdD :: WhatToDo +wtdC = WTD { wtd_empty = Singleton, wtd_mismatch = const Empty, wtd_cons = consC wtdC } +wtdU = WTD { wtd_empty = Empty, wtd_mismatch = id, wtd_cons = consU wtdU } +wtdD = WTD { wtd_empty = Empty, wtd_mismatch = const Empty, wtd_cons = consD wtdD } -traverse :: WhatToTo -> UniqSupply -> PatVec -> ValSetAbs -> ValSetAbs +traverse_vsa :: WhatToDo -> UniqSupply -> PatVec -> ValSetAbs -> ValSetAbs +traverse_vsa wtd us [] vsa = ASSERT( vsaArity 0 vsa == 0 ) vsa +traverse_vsa wtd us (GBindAbs p e : ps) vsa = traverse_guard wtd us p e ps vsa +traverse_vsa wtd us (non_gd : ps) vsa = traverse_non_gd wtd us non_gd ps vsa --- | Empty pattern vector --- Traverse the rest of the Value Set Abstraction --- to make sure that it is a Singleton -traverse wtd us [] vsa = ASSERT( vsaArity vsa == 0 ) vsa - --- | The Pattern Vector starts with a guard --- Highest priority (Do not even inspect the Value Set Abstraction) -traverse wtd us (pat@(GBindAbs p e) : ps) vsa - = cs `mkConstraint` (tailValSetAbs $ traverse wtd usupply2 (p++ps) (VarAbs y `mkCons` vsa)) - where - (usupply1, usupply2) = splitUniqSupply usupply - y = mkPmId usupply1 (pmPatType pat) - cs = [TmConstraint y e] - --- | The Pattern Vector starts with a Variable/Constructor pattern --- Go deeper in the Value Set Abstraction until you meet a cons -traverse wtd us (non_gd : ps) vsa = traverse_non_gd wtd us non_gd ps vs - - -traverse_non_gd :: WhatToTo -> UniqSupply -> Pattern -> PatVec -> ValSetAbs -> ValSetAbs +traverse_non_gd :: WhatToDo -> UniqSupply -> Pattern -> PatVec -> ValSetAbs -> ValSetAbs traverse_non_gd wtd us non_gd ps vsa = case vsa of Empty -> Empty Singleton -> wtd_empty wtd Union vsa1 vsa2 -> let (us1, us2) = splitUniqSupply us - in mkUnion (traverse_non_gd wtd us1 non_gd vsa) - (traverse_non_gd wtd us2 non_gd vsa) - Constraint cs vsa -> mkConstraint cs (traverse_non_gd wtd us non_gd vsa) - Cons vs vsa -> traverseCons wtd us non_gd ps va vsa - -traverseCons :: WhatToTo -> UniqSupply - -> Pattern -> PatternVec - -> ValAbs -> ValSetAbs - -> ValSetAbs -traverseCons wtd us p ps va vsa - = --- = case vsa of --- Empty -> -- Empty --- Singleton -> -- ASSERT( null pv ) Singleton --- Union vsa1 vsa2 -> -- Union (traverse f us1 vsa1) (traverse f us2 vsa2) --- Constraint cs vsa -> -- mkConstraint cs (traverse f us vsa) --- Cons va vsa -> -- traverseCons f us pv va vsa - -wtdCovered :: WhatToDo -wtdCovered = WTD { wtd_empty = Singleton - , wtd_mismatch = const Empty - , wtd_cons = undefined {- ??? -} } -wtdUncovered :: WhatToDo -wtdUncovered = WTD { wtd_empty = Empty - , wtd_mismatch = id - , wtd_cons = undefined {- ??? -} } -wtdDivergent :: WhatToDo -wtdDivergent = WTD { wtd_empty = Empty - , wtd_mismatch = const Empty - , wtd_cons = undefined {- ??? -} } - --- traverse2 f us (p gs : pv) va vsa = .... --- --- traverse2 f us (x : pv) va vsa = .... --- traverse2 f us (p gd : pv) va vsa = .... --- --- covered pv us vsa = traverse (coveredCons pv) us vsa + in mkUnion (traverse_non_gd wtd us1 non_gd ps vsa1) + (traverse_non_gd wtd us2 non_gd ps vsa2) + Constraint cs vsa -> mkConstraint cs (traverse_non_gd wtd us non_gd ps vsa) + Cons va vsa -> traverse_cons wtd us non_gd ps va vsa + +traverse_guard :: WhatToDo -> UniqSupply + -> PatVec -> PmExpr -- ps <- e + -> PatVec -> ValSetAbs -> ValSetAbs +traverse_guard wtd us p e ps vsa + = mkConstraint [TmConstraint y e] . tailValSetAbs + $ traverse_vsa wtd us2 (p++ps) (VarAbs y `mkCons` vsa) + where + (us1, us2) = splitUniqSupply us + y = mkPmId us1 (pmPatType (GBindAbs p e)) + +traverse_cons :: WhatToDo -> UniqSupply + -> Pattern -> PatVec + -> ValAbs -> ValSetAbs + -> ValSetAbs +traverse_cons wtd us p ps va vsa + = case p of + VarAbs x -> mkCons va $ mkConstraint [TmConstraint x (valAbsToPmExpr va)] + $ traverse_vsa wtd us ps vsa + ConAbs { cabs_con = c1, cabs_args = args1 } -> case va of + ConAbs { cabs_con = c2, cabs_args = args2 } + | c1 /= c2 -> wtd_mismatch wtd (mkCons va vsa) + | otherwise -> wrapK c1 $ traverse_vsa wtd us (args1 ++ ps) (foldr mkCons vsa args2) + VarAbs x -> (wtd_cons wtd) us p c1 ps x vsa + GBindAbs {} -> panic "traverse_cons: guard" + +consC :: WhatToDo -> UniqSupply -> Pattern -> DataCon -> PatVec -> Id -> ValSetAbs -> ValSetAbs +consC wtd us cabs con ps x vsa + = traverse_cons wtd us2 cabs ps con_abs (mkConstraint all_cs vsa) + where + (us1, us2) = splitUniqSupply us + (con_abs, all_cs) = mkOneConFull x us1 con + +consU :: WhatToDo -> UniqSupply -> Pattern -> DataCon -> PatVec -> Id -> ValSetAbs -> ValSetAbs +consU wtd us cabs con ps x vsa + = traverse_non_gd wtd us2 cabs ps inst_vsa + where + (us1, us2) = splitUniqSupply us + cons_cs = zipWith (mkOneConFull x) (listSplitUniqSupply us1) (allConstructors con) + add_one (va,cs) valset = mkUnion valset $ mkCons va $ mkConstraint cs vsa + inst_vsa = foldr add_one Empty cons_cs + +consD :: WhatToDo -> UniqSupply -> Pattern -> DataCon -> PatVec -> Id -> ValSetAbs -> ValSetAbs +consD wtd us cabs con ps x vsa + = mkUnion (mkCons (VarAbs x) (mkConstraint [BtConstraint x] vsa)) + (traverse_cons wtd us2 cabs ps con_abs (mkConstraint all_cs vsa)) + where + (us1, us2) = splitUniqSupply us + (con_abs, all_cs) = mkOneConFull x us1 con + +-- ---------------------------------------------------------------------------- +-- ---------------------------------------------------------------------------- --- ---------------------------------------------------------------------------- -- | Main function 1 (covered) From git at git.haskell.org Thu Jun 25 14:21:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 25 Jun 2015 14:21:01 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: [ongoing] translation of guards (5919c36) Message-ID: <20150625142101.CDE543A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/5919c36e7b7ef5dd99d1ef29c2f6488583001dc6/ghc >--------------------------------------------------------------- commit 5919c36e7b7ef5dd99d1ef29c2f6488583001dc6 Author: George Karachalias Date: Thu Jun 25 16:21:20 2015 +0200 [ongoing] translation of guards >--------------------------------------------------------------- 5919c36e7b7ef5dd99d1ef29c2f6488583001dc6 compiler/deSugar/Check.hs | 29 +++++++++++++++++++++++++++++ 1 file changed, 29 insertions(+) diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs index 90cf37a..0a9cbda 100644 --- a/compiler/deSugar/Check.hs +++ b/compiler/deSugar/Check.hs @@ -378,6 +378,35 @@ translatePatVec pats = mapM translatePat pats translateEqnInfo :: EquationInfo -> UniqSM PatVec translateEqnInfo (EqnInfo { eqn_pats = ps }) = concat <$> translatePatVec ps + +-- A. What to do with lets? +-- B. write a function hsExprToPmExpr for better results? (it's a yes) +translateGuards :: [GuardStmt Id] -> UniqSM PatVec +translateGuards guards = concat <$> mapM translateGuard guards + +translateGuard :: GuardStmt Id -> UniqSM PatVec +translateGuard (BodyStmt e _ _ _) + | Just _ <- isTrueLHsExpr e = return [] + | otherwise = let e' = lhsExprToPmExpr e + ps = [truePmPat] + in return [GBindAbs ps e'] +translateGuard (LetStmt binds) + = undefined {- WHAT TO DO WITH THIS THEN? WE CARE OR NOT? -} +translateGuard (BindStmt p e _ _) + = do pats <- translatePat (unLoc p) + let e' = lhsExprToPmExpr e + return [GBindAbs pats e'] +translateGuard (LastStmt {}) = panic "translateGuard LastStmt" +translateGuard (ParStmt {}) = panic "translateGuard ParStmt" +translateGuard (TransStmt {}) = panic "translateGuard TransStmt" +translateGuard (RecStmt {}) = panic "translateGuard RecStmt" + +hsExprToPmExpr :: HsExpr Id -> PmExpr +hsExprToPmExpr = PmExprOther -- FOR NOW + +lhsExprToPmExpr :: LHsExpr Id -> PmExpr +lhsExprToPmExpr (L _ e) = hsExprToPmExpr e + -- ----------------------------------------------------------------------- translateConPatVec :: DataCon -> HsConPatDetails Id -> UniqSM PatVec From git at git.haskell.org Thu Jun 25 14:51:22 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 25 Jun 2015 14:51:22 +0000 (UTC) Subject: [commit: ghc] master: Improve kind-checking for 'deriving' clauses (9a34864) Message-ID: <20150625145122.A68FF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9a348640c5ddd63c3385d3722fb3ade38013a148/ghc >--------------------------------------------------------------- commit 9a348640c5ddd63c3385d3722fb3ade38013a148 Author: Simon Peyton Jones Date: Thu Jun 25 15:48:37 2015 +0100 Improve kind-checking for 'deriving' clauses The main payload is in 'mk_functor_like_constraints' in TcDeriv.inferConstraints. This is moving towards a fix for Trac #10561 >--------------------------------------------------------------- 9a348640c5ddd63c3385d3722fb3ade38013a148 compiler/typecheck/TcDeriv.hs | 44 ++++++++++++++++------ testsuite/tests/deriving/should_compile/T10561.hs | 19 ++++++++++ .../tests/deriving/should_compile/T10561.stderr | 5 +++ testsuite/tests/deriving/should_compile/all.T | 1 + testsuite/tests/deriving/should_fail/T9071.stderr | 7 +--- .../tests/deriving/should_fail/T9071_2.stderr | 7 +--- testsuite/tests/typecheck/should_fail/T9305.stderr | 7 +--- 7 files changed, 63 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 9a348640c5ddd63c3385d3722fb3ade38013a148 From git at git.haskell.org Thu Jun 25 14:51:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 25 Jun 2015 14:51:25 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #10562 (c7b6fb5) Message-ID: <20150625145125.D9D953A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c7b6fb59eca478650dcb391a6f424e3c42a155dc/ghc >--------------------------------------------------------------- commit c7b6fb59eca478650dcb391a6f424e3c42a155dc Author: Simon Peyton Jones Date: Thu Jun 25 15:49:09 2015 +0100 Test Trac #10562 >--------------------------------------------------------------- c7b6fb59eca478650dcb391a6f424e3c42a155dc testsuite/tests/typecheck/should_compile/T10562.hs | 14 ++++++++++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 2 files changed, 15 insertions(+) diff --git a/testsuite/tests/typecheck/should_compile/T10562.hs b/testsuite/tests/typecheck/should_compile/T10562.hs new file mode 100644 index 0000000..30b1b0c --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T10562.hs @@ -0,0 +1,14 @@ +{-# LANGUAGE GADTs, TypeFamilies #-} +module T10562 where + +type family Flip a + +data QueryRep qtyp a where + QAtom :: a -> QueryRep () a + QOp :: QueryRep (Flip qtyp) a -> QueryRep qtyp a + +instance Eq (QueryRep qtyp a) where + (==) = error "urk" + +instance (Ord a) => Ord (QueryRep qtyp a) where + compare (QOp a) (QOp b) = a `compare` b diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index 8165087..89227c6 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -463,3 +463,4 @@ test('T10494', normal, compile, ['']) test('T10493', normal, compile, ['']) test('T10428', normal, compile, ['']) test('RepArrow', normal, compile, ['']) +test('T10562', normal, compile, ['']) From git at git.haskell.org Thu Jun 25 18:26:42 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 25 Jun 2015 18:26:42 +0000 (UTC) Subject: [commit: ghc] master: Be aware of overlapping global STG registers in CmmSink (#10521) (a2f828a) Message-ID: <20150625182642.71EB03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a2f828a370b220839ad9b31a274c0198ef91b7fe/ghc >--------------------------------------------------------------- commit a2f828a370b220839ad9b31a274c0198ef91b7fe Author: Reid Barton Date: Thu Jun 25 13:53:57 2015 -0400 Be aware of overlapping global STG registers in CmmSink (#10521) Summary: On x86_64, commit e2f6bbd3a27685bc667655fdb093734cb565b4cf assigned the STG registers F1 and D1 the same hardware register (xmm1), and the same for the registers F2 and D2, etc. When mixing calls to functions involving Float#s and Double#s, this can cause wrong Cmm optimizations that assume the F1 and D1 registers are independent. Reviewers: simonpj, austin Reviewed By: austin Subscribers: simonpj, thomie, bgamari Differential Revision: https://phabricator.haskell.org/D993 GHC Trac Issues: #10521 >--------------------------------------------------------------- a2f828a370b220839ad9b31a274c0198ef91b7fe compiler/cmm/CmmExpr.hs | 37 +++++++++++++++------- compiler/cmm/CmmSink.hs | 15 ++++----- compiler/cmm/CmmUtils.hs | 36 +++++++++++++++++++++ compiler/codeGen/StgCmmUtils.hs | 16 ++++++---- includes/stg/MachRegs.h | 6 ++++ testsuite/.gitignore | 2 ++ testsuite/tests/codeGen/should_run/T10521.hs | 11 +++++++ testsuite/tests/codeGen/should_run/T10521.stdout | 1 + testsuite/tests/codeGen/should_run/T10521b.hs | 18 +++++++++++ .../should_run/{T5747.stdout => T10521b.stdout} | 0 testsuite/tests/codeGen/should_run/all.T | 2 ++ 11 files changed, 117 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 a2f828a370b220839ad9b31a274c0198ef91b7fe From git at git.haskell.org Thu Jun 25 18:26:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 25 Jun 2015 18:26:45 +0000 (UTC) Subject: [commit: ghc] master: Comments only (a7eee0d) Message-ID: <20150625182645.31ED23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a7eee0d8a25789ce1ef349304d27e2a5e22766b7/ghc >--------------------------------------------------------------- commit a7eee0d8a25789ce1ef349304d27e2a5e22766b7 Author: Reid Barton Date: Thu Jun 25 14:26:40 2015 -0400 Comments only >--------------------------------------------------------------- a7eee0d8a25789ce1ef349304d27e2a5e22766b7 libraries/base/tests/enum_processor.py | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/libraries/base/tests/enum_processor.py b/libraries/base/tests/enum_processor.py index 86c3d6c..53bea4c 100755 --- a/libraries/base/tests/enum_processor.py +++ b/libraries/base/tests/enum_processor.py @@ -1,5 +1,9 @@ #!/usr/bin/env python +# The rough equivalent of the traditional CPP: +# #define printTest(x) (do{ putStr ( " " ++ "x" ++ " = " ) ; print (x) }) +# which is not portable to clang. + import sys def process(s): From git at git.haskell.org Fri Jun 26 07:32:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 Jun 2015 07:32:46 +0000 (UTC) Subject: [commit: ghc] master: White space only (3edc186) Message-ID: <20150626073246.E21F03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3edc1868bff5597479c1ab4da5ca78bd89635d3d/ghc >--------------------------------------------------------------- commit 3edc1868bff5597479c1ab4da5ca78bd89635d3d Author: Simon Peyton Jones Date: Wed Jun 24 22:14:44 2015 +0100 White space only >--------------------------------------------------------------- 3edc1868bff5597479c1ab4da5ca78bd89635d3d compiler/basicTypes/MkId.hs | 0 1 file changed, 0 insertions(+), 0 deletions(-) From git at git.haskell.org Fri Jun 26 07:32:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 Jun 2015 07:32:49 +0000 (UTC) Subject: [commit: ghc] master: Improve pretty-printing for CoPat (9195927) Message-ID: <20150626073249.B5DCE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9195927d093504e233225dfb40f2f6b95a78925e/ghc >--------------------------------------------------------------- commit 9195927d093504e233225dfb40f2f6b95a78925e Author: Simon Peyton Jones Date: Wed Jun 24 22:19:33 2015 +0100 Improve pretty-printing for CoPat >--------------------------------------------------------------- 9195927d093504e233225dfb40f2f6b95a78925e compiler/hsSyn/HsPat.hs | 15 ++++++++++++--- 1 file changed, 12 insertions(+), 3 deletions(-) diff --git a/compiler/hsSyn/HsPat.hs b/compiler/hsSyn/HsPat.hs index 5d74edf..c146133 100644 --- a/compiler/hsSyn/HsPat.hs +++ b/compiler/hsSyn/HsPat.hs @@ -298,8 +298,17 @@ pprParendLPat :: (OutputableBndr name) => LPat name -> SDoc pprParendLPat (L _ p) = pprParendPat p pprParendPat :: (OutputableBndr name) => Pat name -> SDoc -pprParendPat p | hsPatNeedsParens p = parens (pprPat p) - | otherwise = pprPat p +pprParendPat p = getPprStyle $ \ sty -> + if need_parens sty p + then parens (pprPat p) + else pprPat p + where + need_parens sty p + | CoPat {} <- p -- In debug style we print the cast + , debugStyle sty = True -- (see pprHsWrapper) so parens are needed + | otherwise = hsPatNeedsParens p + -- But otherwise the CoPat is discarded, so it + -- is the pattern inside that matters. Sigh. pprPat :: (OutputableBndr name) => Pat name -> SDoc pprPat (VarPat var) = pprPatBndr var @@ -495,7 +504,7 @@ hsPatNeedsParens p@(ConPatOut {}) = conPatNeedsParens (pat_args p) hsPatNeedsParens (SigPatIn {}) = True hsPatNeedsParens (SigPatOut {}) = True hsPatNeedsParens (ViewPat {}) = True -hsPatNeedsParens (CoPat {}) = True +hsPatNeedsParens (CoPat _ p _) = hsPatNeedsParens p hsPatNeedsParens (WildPat {}) = False hsPatNeedsParens (VarPat {}) = False hsPatNeedsParens (LazyPat {}) = False From git at git.haskell.org Fri Jun 26 07:32:52 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 Jun 2015 07:32:52 +0000 (UTC) Subject: [commit: ghc] master: Use a Representaional coercion for data families (ff8a671) Message-ID: <20150626073252.7A9E93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ff8a67164b294b5eb6caee38ec59e7e400e025dc/ghc >--------------------------------------------------------------- commit ff8a67164b294b5eb6caee38ec59e7e400e025dc Author: Simon Peyton Jones Date: Wed Jun 24 22:35:32 2015 +0100 Use a Representaional coercion for data families When we have data instance T (a,b) = MkT a b we make a represntation type data TPair a b = MkT a b plus an axiom to connect the two ax a b :: T (a,b) ~R TPair a b Previously this was a Nominal equality, and that worked ok but seems illogical since Nominal equalities are between types that the programmer thinks of as being equal. But TPair is not visible to the programmer; indeed we call it the "representation TyCon". So a Representational equality seems more suitable here. >--------------------------------------------------------------- ff8a67164b294b5eb6caee38ec59e7e400e025dc compiler/hsSyn/HsUtils.hs | 6 ++-- compiler/typecheck/FamInst.hs | 1 + compiler/typecheck/TcEvidence.hs | 17 ++++++--- compiler/typecheck/TcExpr.hs | 2 +- compiler/typecheck/TcGenGenerics.hs | 2 +- compiler/typecheck/TcInstDcls.hs | 5 +-- compiler/typecheck/TcPat.hs | 43 +++++++++++++++-------- compiler/typecheck/TcUnify.hs | 10 +++--- compiler/types/FamInstEnv.hs | 11 ++++-- compiler/types/TyCon.hs | 8 +++-- compiler/vectorise/Vectorise/Generic/PAMethods.hs | 2 +- compiler/vectorise/Vectorise/Generic/PData.hs | 2 +- 12 files changed, 69 insertions(+), 40 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ff8a67164b294b5eb6caee38ec59e7e400e025dc From git at git.haskell.org Fri Jun 26 07:32:55 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 Jun 2015 07:32:55 +0000 (UTC) Subject: [commit: ghc] master: Allow recursive unwrapping of data families (0b7e538) Message-ID: <20150626073255.50C503A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0b7e538a09bc958474ec704063eaa08836e9270e/ghc >--------------------------------------------------------------- commit 0b7e538a09bc958474ec704063eaa08836e9270e Author: Simon Peyton Jones Date: Wed Jun 24 22:54:27 2015 +0100 Allow recursive unwrapping of data families When doing strictness analysis, we need to look inside products. To avoid unpacking infinitely, we must be careful about infinite types. That in turn is controlled by TyCon.checkRecTc. For data families like data instance T (a,b) = MkT a (T b) we want to unpack the thing recursively for types like T (Int, (Int, (Int, Int))) This patch elaborates the checkRecTc mechanism in TyCon, to maintain a *count* of how many times a TyCon has shown up, rather than just a boolean. A simple change, and a useful one. Fixes Trac #10482. >--------------------------------------------------------------- 0b7e538a09bc958474ec704063eaa08836e9270e compiler/typecheck/FamInst.hs | 43 +++++++++++++++++++++++++------------------ compiler/types/Coercion.hs | 11 ++++++----- compiler/types/FamInstEnv.hs | 17 ++++++++--------- compiler/types/TyCon.hs | 40 +++++++++++++++++++++++++++++----------- 4 files changed, 68 insertions(+), 43 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 0b7e538a09bc958474ec704063eaa08836e9270e From git at git.haskell.org Fri Jun 26 07:32:58 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 Jun 2015 07:32:58 +0000 (UTC) Subject: [commit: ghc] master: Minor fix to free-vars in RnTypes (cc0dba1) Message-ID: <20150626073258.02B783A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cc0dba1e4da6857a740b866d3f8a12d8549dc452/ghc >--------------------------------------------------------------- commit cc0dba1e4da6857a740b866d3f8a12d8549dc452 Author: Simon Peyton Jones Date: Wed Jun 24 23:29:11 2015 +0100 Minor fix to free-vars in RnTypes A type wild-card should't appear in the "uses" free-variable set. >--------------------------------------------------------------- cc0dba1e4da6857a740b866d3f8a12d8549dc452 compiler/rename/RnTypes.hs | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/compiler/rename/RnTypes.hs b/compiler/rename/RnTypes.hs index 743f460..3766ed1 100644 --- a/compiler/rename/RnTypes.hs +++ b/compiler/rename/RnTypes.hs @@ -285,7 +285,9 @@ rnHsTyKi isType _doc (HsWildCardTy (AnonWildCard PlaceHolder)) do { loc <- getSrcSpanM ; uniq <- newUnique ; let name = mkInternalName uniq (mkTyVarOcc "_") loc - ; return (HsWildCardTy (AnonWildCard name), unitFV name) } + ; return (HsWildCardTy (AnonWildCard name), emptyFVs) } + -- emptyFVs: this occurrence does not refer to a + -- binding, so don't treat it as a free variable rnHsTyKi isType doc (HsWildCardTy (NamedWildCard rdr_name)) = ASSERT( isType ) @@ -297,7 +299,9 @@ rnHsTyKi isType doc (HsWildCardTy (NamedWildCard rdr_name)) failWith $ text "Unexpected wild card:" <+> quotes (ppr rdr_name) $$ docOfHsDocContext doc ; name <- rnTyVar isType rdr_name - ; return (HsWildCardTy (NamedWildCard name), unitFV name) } + ; return (HsWildCardTy (NamedWildCard name), emptyFVs) } + -- emptyFVs: this occurrence does not refer to a + -- binding, so don't treat it as a free variable -------------- rnHsTyKiForAll :: Bool -> HsDocContext -> HsType RdrName From git at git.haskell.org Fri Jun 26 07:33:00 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 Jun 2015 07:33:00 +0000 (UTC) Subject: [commit: ghc] master: Fix addDataConStrictness (9014a7e) Message-ID: <20150626073300.CB2AA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9014a7ee6c1182df62dfd343e0a2269b0b4988d0/ghc >--------------------------------------------------------------- commit 9014a7ee6c1182df62dfd343e0a2269b0b4988d0 Author: Simon Peyton Jones Date: Wed Jun 24 23:43:41 2015 +0100 Fix addDataConStrictness See Note [Add demands for strict constructors]. The new bit is the test for isAbsDmd in addDataConStrictness. There was a cryptic note that said that this function should add a seqDmd even for Absent arguments, but that is definitely a bad thing (as the Note now says), causing unused arguments to be passed to the worker. Easy fix! >--------------------------------------------------------------- 9014a7ee6c1182df62dfd343e0a2269b0b4988d0 compiler/stranal/DmdAnal.hs | 25 ++++++++++++++----------- 1 file changed, 14 insertions(+), 11 deletions(-) diff --git a/compiler/stranal/DmdAnal.hs b/compiler/stranal/DmdAnal.hs index a345e45..a0e5fef 100644 --- a/compiler/stranal/DmdAnal.hs +++ b/compiler/stranal/DmdAnal.hs @@ -431,10 +431,7 @@ in this case. In other words, for locally-bound lambdas we can infer one-shotness. --} - -{- Note [Add demands for strict constructors] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Consider this program (due to Roman): @@ -462,17 +459,23 @@ because X is strict, so its argument must be evaluated. And if we because the seq is discarded (very early) since X is strict! +We achieve the effect using addDataConStrictness. It is called at a +case expression, such as the pattern match on (X a) in the example +above. After computing how 'a' is used in the alternatives, we add an +extra 'seqDmd' to it. The case alternative isn't itself strict in the +sub-components, but simply evaluating the scrutinee to HNF does force +those sub-components. + +If the argument is not used at all in the alternative (i.e. it is +Absent), then *don't* add a 'seqDmd'. If we do, it makes it look used +and hence it'll be passed to the worker when it doesn't need to be. +Hence the isAbsDmd test in addDataConStrictness. + There is the usual danger of reboxing, which as usual we ignore. But if X is monomorphic, and has an UNPACK pragma, then this optimisation is even more important. We don't want the wrapper to rebox an unboxed argument, and pass an Int to $wfoo! -We add these extra strict demands to the demand on the *scrutinee* of -the case expression; hence the use of addDataConStrictness when -forming scrut_dmd. The case alternatives aren't strict in their -sub-components, but simply evaluating the scrutinee to HNF does force -those sub-components. - ************************************************************************ * * @@ -1101,9 +1104,9 @@ addDataConStrictness con ds zipWith add ds strs where strs = dataConRepStrictness con - add dmd str | isMarkedStrict str = dmd `bothDmd` seqDmd + add dmd str | isMarkedStrict str + , not (isAbsDmd dmd) = dmd `bothDmd` seqDmd | otherwise = dmd - -- Yes, even if 'dmd' is Absent! findBndrsDmds :: AnalEnv -> DmdType -> [Var] -> (DmdType, [Demand]) -- Return the demands on the Ids in the [Var] From git at git.haskell.org Fri Jun 26 07:33:03 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 Jun 2015 07:33:03 +0000 (UTC) Subject: [commit: ghc] master: Don't float out alpha[sig] ~ Int (b69dc73) Message-ID: <20150626073303.789263A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b69dc7311bacff8e434bc4f3883ad64d60c0a7f1/ghc >--------------------------------------------------------------- commit b69dc7311bacff8e434bc4f3883ad64d60c0a7f1 Author: Simon Peyton Jones Date: Thu Jun 25 09:13:30 2015 +0100 Don't float out alpha[sig] ~ Int This is just a small twiddle to TcSimplify.usefulToFloat See Note [Which equalities to float]. >--------------------------------------------------------------- b69dc7311bacff8e434bc4f3883ad64d60c0a7f1 compiler/typecheck/TcSimplify.hs | 45 ++++++++++++++++++++++++++-------------- 1 file changed, 29 insertions(+), 16 deletions(-) diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs index 2bcf5eb..9d73940 100644 --- a/compiler/typecheck/TcSimplify.hs +++ b/compiler/typecheck/TcSimplify.hs @@ -1578,22 +1578,21 @@ usefulToFloat is_useful_pred ct -- The constraint is un-flattened and de-canon -- Float out alpha ~ ty, or ty ~ alpha -- which might be unified outside - -- See Note [Do not float kind-incompatible equalities] + -- See Note [Which equalities to float] is_meta_var_eq pred | EqPred NomEq ty1 ty2 <- classifyPredType pred - , let k1 = typeKind ty1 - k2 = typeKind ty2 = case (tcGetTyVar_maybe ty1, tcGetTyVar_maybe ty2) of - (Just tv1, _) | isMetaTyVar tv1 - , k2 `isSubKind` k1 - -> True - (_, Just tv2) | isMetaTyVar tv2 - , k1 `isSubKind` k2 - -> True - _ -> False + (Just tv1, _) -> float_tv_eq tv1 ty2 + (_, Just tv2) -> float_tv_eq tv2 ty1 + _ -> False | otherwise = False + float_tv_eq tv1 ty2 -- See Note [Which equalities to float] + = isMetaTyVar tv1 + && typeKind ty2 `isSubKind` tyVarKind tv1 + && (not (isSigTyVar tv1) || isTyVarTy ty2) + {- Note [Float equalities from under a skolem binding] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Which of the simple equalities can we float out? Obviously, only @@ -1617,12 +1616,26 @@ We had a very complicated rule previously, but this is nice and simple. (To see the notes, look at this Note in a version of TcSimplify prior to Oct 2014). -Note [Do not float kind-incompatible equalities] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -If we have (t::* ~ s::*->*), we'll get a Derived insoluble equality. -If we float the equality outwards, we'll get *another* Derived -insoluble equality one level out, so the same error will be reported -twice. So we refrain from floating such equalities. +Note [Which equalities to float] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Which equalities should we float? We want to float ones where there +is a decent chance that floating outwards will allow unification to +happen. In particular: + + Float out equalities of form (alpaha ~ ty) or (ty ~ alpha), where + + * alpha is a meta-tyvar + + * And the equality is kind-compatible + + e.g. Consider (alpha:*) ~ (s:*->*) + From this we already get a Derived insoluble equality. If we + floated it, we'll get *another* Derived insoluble equality one + level out, so the same error will be reported twice. + + * And 'alpha' is not a SigTv with 'ty' being a non-tyvar. In that + case, floating out won't help either, and it may affect grouping + of error messages. Note [Skolem escape] ~~~~~~~~~~~~~~~~~~~~ From git at git.haskell.org Fri Jun 26 07:33:06 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 Jun 2015 07:33:06 +0000 (UTC) Subject: [commit: ghc] master: Add module header to test (97e313c) Message-ID: <20150626073306.39F063A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/97e313cd7a95bba5dd5c2409b5a9c286db3510d1/ghc >--------------------------------------------------------------- commit 97e313cd7a95bba5dd5c2409b5a9c286db3510d1 Author: Simon Peyton Jones Date: Thu Jun 25 09:14:21 2015 +0100 Add module header to test ..to avoid irrelevant 'main is not defined' error message >--------------------------------------------------------------- 97e313cd7a95bba5dd5c2409b5a9c286db3510d1 testsuite/tests/parser/unicode/T2302.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/testsuite/tests/parser/unicode/T2302.hs b/testsuite/tests/parser/unicode/T2302.hs index c40c704..a23d808 100644 --- a/testsuite/tests/parser/unicode/T2302.hs +++ b/testsuite/tests/parser/unicode/T2302.hs @@ -1 +1,2 @@ +module T2302 where f = ? From git at git.haskell.org Fri Jun 26 07:33:08 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 Jun 2015 07:33:08 +0000 (UTC) Subject: [commit: ghc] master: Get rid of irrelevant impredicative polymoprhism (95fc6d5) Message-ID: <20150626073308.F1A433A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/95fc6d5940582c8a42cd8f65b7e21b6e6370ea83/ghc >--------------------------------------------------------------- commit 95fc6d5940582c8a42cd8f65b7e21b6e6370ea83 Author: Simon Peyton Jones Date: Thu Jun 25 09:21:13 2015 +0100 Get rid of irrelevant impredicative polymoprhism These tests aren't about impredicativity >--------------------------------------------------------------- 95fc6d5940582c8a42cd8f65b7e21b6e6370ea83 testsuite/tests/rename/should_fail/mc13.hs | 4 ++-- testsuite/tests/rename/should_fail/mc14.hs | 2 +- testsuite/tests/rename/should_fail/rnfail049.hs | 2 +- testsuite/tests/rename/should_fail/rnfail050.hs | 2 +- 4 files changed, 5 insertions(+), 5 deletions(-) diff --git a/testsuite/tests/rename/should_fail/mc13.hs b/testsuite/tests/rename/should_fail/mc13.hs index 6069e0f..a07a183 100644 --- a/testsuite/tests/rename/should_fail/mc13.hs +++ b/testsuite/tests/rename/should_fail/mc13.hs @@ -1,4 +1,4 @@ --- Test for transform list comp which should work for monad comp aswell: +-- Test for transform list comp which should work for monad comp as well: -- -- Test trying to use a function bound in the list comprehension as the transform function @@ -6,7 +6,7 @@ module RnFail048 where -functions :: [forall a. [a] -> [a]] +functions :: [[a] -> [a]] functions = [take 4, take 5] output = [() | f <- functions, then f] diff --git a/testsuite/tests/rename/should_fail/mc14.hs b/testsuite/tests/rename/should_fail/mc14.hs index 71ccbf9..47d903b 100644 --- a/testsuite/tests/rename/should_fail/mc14.hs +++ b/testsuite/tests/rename/should_fail/mc14.hs @@ -8,7 +8,7 @@ module RnFail049 where import Data.List(inits, tails) -functions :: [forall a. [a] -> [[a]]] +functions :: [[a] -> [[a]]] functions = [inits, tails] output = [() | f <- functions, then group using f] diff --git a/testsuite/tests/rename/should_fail/rnfail049.hs b/testsuite/tests/rename/should_fail/rnfail049.hs index 6123856..0d426a4 100644 --- a/testsuite/tests/rename/should_fail/rnfail049.hs +++ b/testsuite/tests/rename/should_fail/rnfail049.hs @@ -6,7 +6,7 @@ module RnFail049 where import Data.List(inits, tails) -functions :: [forall a. [a] -> [[a]]] +functions :: [[a] -> [[a]]] functions = [inits, tails] output = [() | f <- functions, then group using f] diff --git a/testsuite/tests/rename/should_fail/rnfail050.hs b/testsuite/tests/rename/should_fail/rnfail050.hs index b148acb..0618b93 100644 --- a/testsuite/tests/rename/should_fail/rnfail050.hs +++ b/testsuite/tests/rename/should_fail/rnfail050.hs @@ -4,7 +4,7 @@ module RnFail048 where -functions :: [forall a. [a] -> [a]] +functions :: [[a] -> [a]] functions = [take 4, take 5] output = [() | f <- functions, then f] From git at git.haskell.org Fri Jun 26 07:33:11 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 Jun 2015 07:33:11 +0000 (UTC) Subject: [commit: ghc] master: Get rid of irrlevant result type signature (2f16a3b) Message-ID: <20150626073311.AE68E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2f16a3b8745fe53c1be431db755c574b1464edde/ghc >--------------------------------------------------------------- commit 2f16a3b8745fe53c1be431db755c574b1464edde Author: Simon Peyton Jones Date: Thu Jun 25 09:17:27 2015 +0100 Get rid of irrlevant result type signature Result type-sigs are now illegal, but that's not what this test is about >--------------------------------------------------------------- 2f16a3b8745fe53c1be431db755c574b1464edde testsuite/tests/rename/should_fail/T2310.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/rename/should_fail/T2310.hs b/testsuite/tests/rename/should_fail/T2310.hs index 6094b8e..10c9cbc 100644 --- a/testsuite/tests/rename/should_fail/T2310.hs +++ b/testsuite/tests/rename/should_fail/T2310.hs @@ -2,4 +2,4 @@ module Foo where -foo = let c = \ x :: a -> (x :: a) in co +foo = let c = \ (x :: a) -> (x :: a) in co From git at git.haskell.org Fri Jun 26 07:33:14 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 Jun 2015 07:33:14 +0000 (UTC) Subject: [commit: ghc] master: Treat out-of-scope variables as holes (fb7b692) Message-ID: <20150626073314.897963A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fb7b6922573af76a954d939c85e6af7c39a19896/ghc >--------------------------------------------------------------- commit fb7b6922573af76a954d939c85e6af7c39a19896 Author: Simon Peyton Jones Date: Wed Jun 24 23:27:59 2015 +0100 Treat out-of-scope variables as holes This patch implements the idea in Trac #10569. * An out-of-scope variable is treated as a typed expression hole. * That is, we don't report it in the type checker, not the renamer, and we when we do report it, we give its type. * Moreover, we can defer the error to runtime with -fdefer-typed-holes In implementation terms: * The renamer turns an unbound variable into a HsUnboundVar * The type checker emits a Hole constraint for a HsUnboundVar, and turns it back into a HsVar It was a bit painful to implement because a whole raft of error messages change slightly. But there was absolutely nothing hard in principle. Holes are reported with a bunch of possibly-useful context, notably the "relevant bindings". I found that this was distracting clutter in the very common case of a mis-typed variable that is only accidentally not in scope, so I've arranged to print the context information only for true holes, that is ones starting with an underscore. Unbound data constructors use in patterns, like f (D x) = x are still reportd by the renamer, and abort compilation before type checking. >--------------------------------------------------------------- fb7b6922573af76a954d939c85e6af7c39a19896 compiler/deSugar/Coverage.hs | 20 ++-- compiler/deSugar/DsExpr.hs | 2 +- compiler/hsSyn/HsExpr.hs | 45 +++++---- compiler/rename/RnEnv.hs | 60 +++++++----- compiler/rename/RnExpr.hs | 48 ++++++---- compiler/typecheck/TcErrors.hs | 195 +++++++++++++++++++++----------------- compiler/typecheck/TcExpr.hs | 18 ++-- compiler/typecheck/TcRnTypes.hs | 27 +++--- compiler/typecheck/TcRules.hs | 5 +- compiler/typecheck/TcSMonad.hs | 7 +- compiler/typecheck/TcSimplify.hs | 17 ++-- compiler/typecheck/TcType.hs | 23 +++++ docs/users_guide/glasgow_exts.xml | 41 +++++++- 13 files changed, 313 insertions(+), 195 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc fb7b6922573af76a954d939c85e6af7c39a19896 From git at git.haskell.org Fri Jun 26 07:33:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 Jun 2015 07:33:17 +0000 (UTC) Subject: [commit: ghc] master: Error message wibbles from out-of-scope changes (b98ff25) Message-ID: <20150626073317.ECE2D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b98ff25f4c8cb4bf18b784c848fabaaa6e4b11b8/ghc >--------------------------------------------------------------- commit b98ff25f4c8cb4bf18b784c848fabaaa6e4b11b8 Author: Simon Peyton Jones Date: Thu Jun 25 09:25:39 2015 +0100 Error message wibbles from out-of-scope changes The patch "Treat out-of-scope variables as holes" makes lots of error messages change a bit. This patch has all the change. >--------------------------------------------------------------- b98ff25f4c8cb4bf18b784c848fabaaa6e4b11b8 .../tests/arrows/should_fail/arrowfail002.stderr | 2 +- testsuite/tests/driver/T1372/T1372.stderr | 2 +- testsuite/tests/ghc-api/annotations/T10268.stderr | 4 +-- testsuite/tests/ghc-api/annotations/T10278.stderr | 4 --- testsuite/tests/ghc-api/annotations/T10280.stderr | 8 +++--- testsuite/tests/ghc-api/annotations/T10312.stderr | 6 ----- testsuite/tests/ghc-api/annotations/T10313.stderr | 4 --- testsuite/tests/ghc-api/annotations/T10357.stderr | 31 +++++++++++++--------- testsuite/tests/ghc-api/annotations/T10399.stderr | 2 -- testsuite/tests/ghci/prog009/ghci.prog009.stderr | 8 +++--- testsuite/tests/ghci/prog012/prog012.stderr | 2 +- testsuite/tests/ghci/scripts/T10248.stderr | 4 +-- testsuite/tests/ghci/scripts/T2816.stderr | 2 +- testsuite/tests/ghci/scripts/T5564.stderr | 4 +-- testsuite/tests/ghci/scripts/ghci036.stderr | 16 +++++------ testsuite/tests/ghci/scripts/ghci038.stderr | 4 +-- .../tests/indexed-types/should_fail/T7786.stderr | 26 +++++++++++++++++- testsuite/tests/module/mod101.stderr | 4 +-- testsuite/tests/module/mod102.stderr | 4 +-- testsuite/tests/module/mod120.stderr | 2 +- testsuite/tests/module/mod121.stderr | 4 +-- testsuite/tests/module/mod125.stderr | 2 +- testsuite/tests/module/mod126.stderr | 2 +- testsuite/tests/module/mod130.stderr | 3 ++- testsuite/tests/module/mod132.stderr | 4 +-- testsuite/tests/module/mod136.stderr | 4 +-- testsuite/tests/module/mod138.stderr | 2 +- testsuite/tests/module/mod147.stderr | 3 ++- testsuite/tests/module/mod158.stderr | 2 +- testsuite/tests/module/mod160.stderr | 4 +-- testsuite/tests/module/mod36.stderr | 2 +- testsuite/tests/module/mod71.stderr | 2 +- testsuite/tests/module/mod72.stderr | 2 +- testsuite/tests/module/mod87.stderr | 3 ++- testsuite/tests/module/mod97.stderr | 3 ++- .../tests/parser/should_fail/readFail001.stderr | 20 +++++--------- .../tests/parser/should_fail/readFail042.stderr | 8 ++---- .../tests/parser/should_fail/readFail043.stderr | 20 +++----------- testsuite/tests/parser/unicode/T2302.stderr | 2 +- .../partial-sigs/should_compile/T10403.stderr | 4 +-- .../partial-sigs/should_compile/T10438.stderr | 2 +- .../WarningWildcardInstantiations.stderr | 22 +++++++-------- .../InstantiatedNamedWildcardsInConstraints.stderr | 6 ++--- .../should_fail/NamedWildcardsEnabled.stderr | 8 +++--- .../PartialTypeSignaturesDisabled.stderr | 8 +++--- .../partial-sigs/should_fail/TidyClash.stderr | 8 +++--- .../partial-sigs/should_fail/Trac10045.stderr | 6 ++--- .../should_fail/WildcardInstantiations.stderr | 22 +++++++-------- .../WildcardsInPatternAndExprSig.stderr | 20 +++++++------- .../should_fail/RnStaticPointersFail02.stderr | 7 ++++- testsuite/tests/rename/should_fail/T2310.stderr | 9 ++----- testsuite/tests/rename/should_fail/T2993.stderr | 4 +-- testsuite/tests/rename/should_fail/T7937.stderr | 4 +-- testsuite/tests/rename/should_fail/T9177.hs | 3 +++ testsuite/tests/rename/should_fail/T9177.stderr | 16 +++-------- testsuite/tests/rename/should_fail/T9177a.hs | 6 +++++ testsuite/tests/rename/should_fail/T9177a.stderr | 4 +++ testsuite/tests/rename/should_fail/all.T | 1 + testsuite/tests/rename/should_fail/mc13.stderr | 2 +- testsuite/tests/rename/should_fail/mc14.stderr | 14 +++++++++- .../tests/rename/should_fail/rnfail022.stderr | 4 +-- .../tests/rename/should_fail/rnfail024.stderr | 4 +-- .../tests/rename/should_fail/rnfail049.stderr | 2 +- .../tests/rename/should_fail/rnfail050.stderr | 2 +- testsuite/tests/safeHaskell/ghci/p10.stderr | 2 +- testsuite/tests/safeHaskell/ghci/p16.stderr | 10 +++---- testsuite/tests/safeHaskell/ghci/p4.stderr | 5 ++-- testsuite/tests/safeHaskell/ghci/p6.stderr | 6 ++--- testsuite/tests/safeHaskell/ghci/p9.stderr | 2 +- testsuite/tests/th/TH_linePragma.stderr | 2 +- .../tests/typecheck/should_compile/T10072.stderr | 4 +-- .../tests/typecheck/should_compile/T9497a.stderr | 4 +-- .../tests/typecheck/should_compile/holes.stderr | 16 +++++------ .../tests/typecheck/should_compile/holes2.stderr | 6 ++--- .../tests/typecheck/should_compile/holes3.stderr | 16 +++++------ .../tests/typecheck/should_fail/T9497d.stderr | 4 +-- .../tests/typecheck/should_fail/tcfail011.stderr | 2 +- .../tests/typecheck/should_fail/tcfail049.stderr | 2 +- .../tests/typecheck/should_fail/tcfail050.stderr | 3 ++- 79 files changed, 257 insertions(+), 246 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b98ff25f4c8cb4bf18b784c848fabaaa6e4b11b8 From git at git.haskell.org Fri Jun 26 07:33:20 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 Jun 2015 07:33:20 +0000 (UTC) Subject: [commit: ghc] master: Tiny refactor plus comments (0aaea5b) Message-ID: <20150626073320.9D2353A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0aaea5b8345fc4b061b97df8bcaa7c6b07594719/ghc >--------------------------------------------------------------- commit 0aaea5b8345fc4b061b97df8bcaa7c6b07594719 Author: Simon Peyton Jones Date: Fri Jun 26 08:31:37 2015 +0100 Tiny refactor plus comments >--------------------------------------------------------------- 0aaea5b8345fc4b061b97df8bcaa7c6b07594719 compiler/typecheck/TcDeriv.hs | 10 +++++++--- 1 file changed, 7 insertions(+), 3 deletions(-) diff --git a/compiler/typecheck/TcDeriv.hs b/compiler/typecheck/TcDeriv.hs index bbb9dc3..9045e39 100644 --- a/compiler/typecheck/TcDeriv.hs +++ b/compiler/typecheck/TcDeriv.hs @@ -1817,8 +1817,7 @@ simplifyDeriv pred tvs theta -- We use *non-overlappable* (vanilla) skolems -- See Note [Overlap and deriving] - ; let subst_skol = zipTopTvSubst tvs_skols $ map mkTyVarTy tvs - skol_set = mkVarSet tvs_skols + ; let skol_set = mkVarSet tvs_skols doc = ptext (sLit "deriving") <+> parens (ppr pred) ; wanted <- mapM (\(PredOrigin t o) -> newWanted o (substTy skol_subst t)) theta @@ -1839,13 +1838,18 @@ simplifyDeriv pred tvs theta | otherwise = Right ct where p = ctPred ct + ; traceTc "simplifyDeriv 2" $ + vcat [ ppr tvs_skols, ppr residual_simple, ppr good, ppr bad ] + -- If we are deferring type errors, simply ignore any insoluble -- constraints. They'll come up again when we typecheck the -- generated instance declaration ; defer <- goptM Opt_DeferTypeErrors ; unless defer (reportAllUnsolved (residual_wanted { wc_simple = bad })) - ; let min_theta = mkMinimalBySCs (bagToList good) + ; let min_theta = mkMinimalBySCs (bagToList good) + subst_skol = zipTopTvSubst tvs_skols $ map mkTyVarTy tvs + -- The reverse substitution (sigh) ; return (substTheta subst_skol min_theta) } {- From git at git.haskell.org Fri Jun 26 08:31:57 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 Jun 2015 08:31:57 +0000 (UTC) Subject: [commit: ghc] master: Fix for crash in setnumcapabilities001 (be0ce87) Message-ID: <20150626083157.5FE103A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/be0ce8718ea40b091e69dd48fe6bc62b6b551154/ghc >--------------------------------------------------------------- commit be0ce8718ea40b091e69dd48fe6bc62b6b551154 Author: Simon Marlow Date: Fri Jun 19 14:41:32 2015 +0100 Fix for crash in setnumcapabilities001 getNewNursery() was unconditionally incrementing next_nursery, which is normally fine but it broke an assumption in storageAddCapabilities(). This manifested as an occasional crash in the setnumcapabilities001 test. >--------------------------------------------------------------- be0ce8718ea40b091e69dd48fe6bc62b6b551154 rts/sm/Storage.c | 18 ++++++++++++------ 1 file changed, 12 insertions(+), 6 deletions(-) diff --git a/rts/sm/Storage.c b/rts/sm/Storage.c index 7779601..6e9b063 100644 --- a/rts/sm/Storage.c +++ b/rts/sm/Storage.c @@ -576,6 +576,7 @@ allocNursery (bdescr *tail, W_ blocks) STATIC_INLINE void assignNurseryToCapability (Capability *cap, nat n) { + ASSERT(n < n_nurseries); cap->r.rNursery = &nurseries[n]; cap->r.rCurrentNursery = nurseries[n].blocks; newNurseryBlock(nurseries[n].blocks); @@ -726,14 +727,19 @@ resizeNurseries (W_ blocks) rtsBool getNewNursery (Capability *cap) { - StgWord i = atomic_inc(&next_nursery, 1) - 1; - if (i >= n_nurseries) { - return rtsFalse; + StgWord i; + + for(;;) { + i = next_nursery; + if (i >= n_nurseries) { + return rtsFalse; + } + if (cas(&next_nursery, i, i+1) == i) { + assignNurseryToCapability(cap, i); + return rtsTrue; + } } - assignNurseryToCapability(cap, i); - return rtsTrue; } - /* ----------------------------------------------------------------------------- move_STACK is called to update the TSO structure after it has been moved from one place to another. From git at git.haskell.org Fri Jun 26 08:32:01 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 Jun 2015 08:32:01 +0000 (UTC) Subject: [commit: ghc] master: Fix deadlock (#10545) (111ba4b) Message-ID: <20150626083201.8B0383A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/111ba4beda4ffc48381723da12e5b237d7f9ac59/ghc >--------------------------------------------------------------- commit 111ba4beda4ffc48381723da12e5b237d7f9ac59 Author: Simon Marlow Date: Fri Jun 19 15:12:24 2015 +0100 Fix deadlock (#10545) yieldCapability() was not prepared to be called by a Task that is not either a worker or a bound Task. This could happen if we ended up in yieldCapability via this call stack: performGC() scheduleDoGC() requestSync() yieldCapability() and there were a few other ways this could happen via requestSync. The fix is to handle this case in yieldCapability(): when the Task is not a worker or a bound Task, we put it on the returning_workers queue, where it will be woken up again. Summary of changes: * `yieldCapability`: factored out subroutine waitForWorkerCapability` * `waitForReturnCapability` renamed to `waitForCapability`, and factored out subroutine `waitForReturnCapability` * `releaseCapabilityAndQueue` worker renamed to `enqueueWorker`, does not take a lock and no longer tests if `!isBoundTask()` * `yieldCapability` adjusted for refactorings, only change in behavior is when it is not a worker or bound task. Test Plan: * new test concurrent/should_run/performGC * validate Reviewers: niteria, austin, ezyang, bgamari Subscribers: thomie, bgamari Differential Revision: https://phabricator.haskell.org/D997 GHC Trac Issues: #10545 >--------------------------------------------------------------- 111ba4beda4ffc48381723da12e5b237d7f9ac59 rts/Capability.c | 301 +++++++---- rts/Capability.h | 8 +- rts/RtsAPI.c | 2 +- rts/Schedule.c | 14 +- rts/Task.h | 11 + testsuite/tests/concurrent/should_run/RandomPGC.hs | 597 +++++++++++++++++++++ testsuite/tests/concurrent/should_run/all.T | 4 + testsuite/tests/concurrent/should_run/performGC.hs | 24 + .../tests/concurrent/should_run/performGC.stdout | 400 ++++++++++++++ 9 files changed, 1231 insertions(+), 130 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 111ba4beda4ffc48381723da12e5b237d7f9ac59 From git at git.haskell.org Fri Jun 26 08:57:53 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 Jun 2015 08:57:53 +0000 (UTC) Subject: [commit: ghc] wip/impredicativity: Convert InstanceOf constraints to eqs. in RULES (1065f0d) Message-ID: <20150626085753.6667D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/impredicativity Link : http://ghc.haskell.org/trac/ghc/changeset/1065f0d539f79b4f01386d9cc7db495b6932116a/ghc >--------------------------------------------------------------- commit 1065f0d539f79b4f01386d9cc7db495b6932116a Author: Alejandro Serrano Date: Fri Jun 26 10:54:59 2015 +0200 Convert InstanceOf constraints to eqs. in RULES When type checking RULES, constraints are gathered for both the left-hand side and the right-hand side. In most cases, this leads to a bunch of InstanceOf constraints in both sides. Later, the constraints for the left-hand side are taken as givens for solving the right-hand ones. Alas, we do not know yet how to treat InstanceOf constraints in givens. The best solution is to convert them to equalities as we do for generalization prior to the solving. >--------------------------------------------------------------- 1065f0d539f79b4f01386d9cc7db495b6932116a compiler/typecheck/TcCanonical.hs | 1 + compiler/typecheck/TcRules.hs | 10 ++++++++-- compiler/typecheck/TcSimplify.hs | 4 ++-- 3 files changed, 11 insertions(+), 4 deletions(-) diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index 05d564e..5701963 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -1707,6 +1707,7 @@ can_instance_of (CInstanceOfCan { cc_ev = ev, cc_lhs = lhs, cc_rhs = rhs }) ; traceTcS "can_instance_of/INST" (vcat [ ppr new_ev_ty, ppr new_ev_qs ]) ; canInstanceOfNC new_ev_ty } _ -> stopWith ev "Given/Derived instanceOf instantiation" + -- case InstanceOf ty (forall qvars. Q => ty) | Just _ <- splitForAllTy_maybe rhs = case ev of CtWanted { ctev_evar = evar, ctev_loc = loc } -> diff --git a/compiler/typecheck/TcRules.hs b/compiler/typecheck/TcRules.hs index 80db8c8..9972af0 100644 --- a/compiler/typecheck/TcRules.hs +++ b/compiler/typecheck/TcRules.hs @@ -303,11 +303,16 @@ simplifyRule name lhs_wanted rhs_wanted do { -- First solve the LHS and *then* solve the RHS -- See Note [Solve order for RULES] lhs_resid <- solveWanteds lhs_wanted + ; lhs_inst <- fmap andManyCts $ + mapM instantiateWC (bagToList (wc_simple lhs_resid)) + ; lhs_inst_resid <- solveWanteds lhs_resid { wc_simple = lhs_inst } ; rhs_resid <- solveWanteds rhs_wanted - ; return (insolubleWC lhs_resid || insolubleWC rhs_resid) } + ; return (insolubleWC lhs_inst_resid || insolubleWC rhs_resid) } ; zonked_lhs_simples <- zonkSimples (wc_simple lhs_wanted) - ; let (q_cts, non_q_cts) = partitionBag quantify_me zonked_lhs_simples + ; (zonked_lhs_inst, _) <- runTcS $ fmap andManyCts $ + mapM instantiateWC (bagToList zonked_lhs_simples) + ; let (q_cts, non_q_cts) = partitionBag quantify_me zonked_lhs_inst quantify_me -- Note [RULE quantification over equalities] | insoluble = quantify_insol | otherwise = quantify_normal @@ -325,6 +330,7 @@ simplifyRule name lhs_wanted rhs_wanted , text "lhs_wantd" <+> ppr lhs_wanted , text "rhs_wantd" <+> ppr rhs_wanted , text "zonked_lhs_simples" <+> ppr zonked_lhs_simples + , text "zonked_lhs_inst" <+> ppr zonked_lhs_inst , text "q_cts" <+> ppr q_cts , text "non_q_cts" <+> ppr non_q_cts ] diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs index 94b5e2f..64b6e57 100644 --- a/compiler/typecheck/TcSimplify.hs +++ b/compiler/typecheck/TcSimplify.hs @@ -8,8 +8,8 @@ module TcSimplify( simplifyTop, simplifyInteractive, solveWantedsTcM, - -- For Rules we need these twoo - solveWanteds, runTcS + -- For Rules we need these three + solveWanteds, runTcS, instantiateWC ) where #include "HsVersions.h" From git at git.haskell.org Fri Jun 26 11:22:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 Jun 2015 11:22:49 +0000 (UTC) Subject: [commit: ghc] master: GHCi docs: layout rule is respected inside :{ :} (7c8ffd3) Message-ID: <20150626112249.205CE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7c8ffd3d8c328d5ca145fe15638ec5c952782132/ghc >--------------------------------------------------------------- commit 7c8ffd3d8c328d5ca145fe15638ec5c952782132 Author: Thomas Miedema Date: Wed Jun 24 12:52:16 2015 +0200 GHCi docs: layout rule is respected inside :{ :} Summary: I don't know if or when this changed, but the documentation on :{ :} (multiline input) seems out of date. Layout rule works fine. I added a regression test. Reviewers: austin Subscribers: thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1013 >--------------------------------------------------------------- 7c8ffd3d8c328d5ca145fe15638ec5c952782132 docs/users_guide/ghci.xml | 20 ++++++++------------ testsuite/tests/ghci/scripts/ghci023.script | 11 +++++++++++ testsuite/tests/ghci/scripts/ghci023.stdout | 2 ++ 3 files changed, 21 insertions(+), 12 deletions(-) diff --git a/docs/users_guide/ghci.xml b/docs/users_guide/ghci.xml index d3b65ef..a1271e1 100644 --- a/docs/users_guide/ghci.xml +++ b/docs/users_guide/ghci.xml @@ -437,10 +437,10 @@ Prelude> The variable's type is not polymorphic, is not (), and is an instance of - Show + Show. - . + Of course, you can also bind normal non-IO expressions @@ -477,9 +477,9 @@ Prelude> However, this quickly gets tedious when defining functions with multiple clauses, or groups of mutually recursive functions, because the complete definition has to be given on a single line, - using explicit braces and semicolons instead of layout: + using explicit semicolons instead of layout: -Prelude> let { f op n [] = n ; f op n (h:t) = h `op` f op n t } +Prelude> let f op n [] = n ; f op n (h:t) = h `op` f op n t Prelude> f (+) 0 [1..3] 6 Prelude> @@ -489,18 +489,14 @@ Prelude> :} (each on a single line of its own): Prelude> :{ -Prelude| let { g op n [] = n -Prelude| ; g op n (h:t) = h `op` g op n t -Prelude| } +Prelude| let g op n [] = n +Prelude| g op n (h:t) = h `op` g op n t Prelude| :} Prelude> g (*) 1 [1..3] 6 Such multiline commands can be used with any GHCi command, - and the lines between :{ and - :} are simply merged into a single line for - interpretation. That implies that each such group must form a single - valid command when merged, and that no layout rule is used. + and note that the layout rule is in effect. The main purpose of multiline commands is not to replace module loading but to make definitions in .ghci-files (see ) more readable and maintainable. @@ -575,7 +571,7 @@ Prelude> Explicit braces and semicolons can be used instead of - layout, as usual: + layout: Prelude> do { diff --git a/testsuite/tests/ghci/scripts/ghci023.script b/testsuite/tests/ghci/scripts/ghci023.script index dd77433..a21fcb6 100644 --- a/testsuite/tests/ghci/scripts/ghci023.script +++ b/testsuite/tests/ghci/scripts/ghci023.script @@ -9,6 +9,17 @@ putStrLn "-- via stdin" } :} print (f 0,f 1,y) + +putStrLn "-- layout rule instead of explicit braces and semicolons works too" +:{ + let + g 0 = 1 + g 1 = w + where w = 2 + z = 3 +:} +print (g 0,g 1,z) + :{ :browse Data.Maybe diff --git a/testsuite/tests/ghci/scripts/ghci023.stdout b/testsuite/tests/ghci/scripts/ghci023.stdout index 010fe50..61a859a 100644 --- a/testsuite/tests/ghci/scripts/ghci023.stdout +++ b/testsuite/tests/ghci/scripts/ghci023.stdout @@ -1,6 +1,8 @@ -- testing ghci multiline commands :{ .. :} -- via stdin (1,2,3) +-- layout rule instead of explicit braces and semicolons works too +(1,2,3) catMaybes :: [Maybe a] -> [a] fromJust :: Maybe a -> a fromMaybe :: a -> Maybe a -> a From git at git.haskell.org Fri Jun 26 13:44:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 Jun 2015 13:44:23 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: Translate (HsExpr Id) to PmExpr for better precision (dd68bd7) Message-ID: <20150626134423.AE3BC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/dd68bd7db36de4849dc7a36222bb3e6dc41afd56/ghc >--------------------------------------------------------------- commit dd68bd7db36de4849dc7a36222bb3e6dc41afd56 Author: George Karachalias Date: Fri Jun 26 14:54:14 2015 +0200 Translate (HsExpr Id) to PmExpr for better precision * NOTE: Replacing 'PmExprOther' with 'hsExprToPmExpr' in 'translatePat' gives no better results at the moment because all expressions we generate are OpApp/HsApp, which hsExprToPmExpr leaves untouched. We may improve it in the future though so it is better to use 'hsExprToPmExpr' instead of wrapping it unconditionally with a PmExprOther. >--------------------------------------------------------------- dd68bd7db36de4849dc7a36222bb3e6dc41afd56 compiler/deSugar/Check.hs | 124 +++++++++++++++++++++++++++++++++++++--------- 1 file changed, 100 insertions(+), 24 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc dd68bd7db36de4849dc7a36222bb3e6dc41afd56 From git at git.haskell.org Fri Jun 26 13:44:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 Jun 2015 13:44:26 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: Finished 'translateGuard' (856ab33) Message-ID: <20150626134426.770933A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/856ab33f19e775a4eb986a81815e9d7c78c8b0b6/ghc >--------------------------------------------------------------- commit 856ab33f19e775a4eb986a81815e9d7c78c8b0b6 Author: George Karachalias Date: Fri Jun 26 15:44:37 2015 +0200 Finished 'translateGuard' >--------------------------------------------------------------- 856ab33f19e775a4eb986a81815e9d7c78c8b0b6 compiler/deSugar/Check.hs | 40 ++++++++++++++++++++++++++-------------- 1 file changed, 26 insertions(+), 14 deletions(-) diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs index 4b925a8..90d5b2e 100644 --- a/compiler/deSugar/Check.hs +++ b/compiler/deSugar/Check.hs @@ -405,21 +405,33 @@ translateGuards :: [GuardStmt Id] -> UniqSM PatVec translateGuards guards = concat <$> mapM translateGuard guards translateGuard :: GuardStmt Id -> UniqSM PatVec -translateGuard (BodyStmt e _ _ _) +translateGuard (BodyStmt e _ _ _) = translateBoolGuard e +translateGuard (LetStmt binds) = translateLet binds +translateGuard (BindStmt p e _ _) = translateBind p e +translateGuard (LastStmt {}) = panic "translateGuard LastStmt" +translateGuard (ParStmt {}) = panic "translateGuard ParStmt" +translateGuard (TransStmt {}) = panic "translateGuard TransStmt" +translateGuard (RecStmt {}) = panic "translateGuard RecStmt" + +translateLet :: HsLocalBinds Id -> UniqSM PatVec +translateLet binds = return [] -- NOT CORRECT: A let cannot fail so in a way we + -- are fine with it but it can bind things which we do not bring in scope. + -- Hence, they are free while they shouldn't. More constraints would make it + -- more expressive but omitting some is always safe (Is it? Make sure it is) + +translateBind :: LPat Id -> LHsExpr Id -> UniqSM PatVec +translateBind (L _ p) e = do + ps <- translatePat p + let expr = lhsExprToPmExpr e + return [GBindAbs ps expr] + +translateBoolGuard :: LHsExpr Id -> UniqSM PatVec +translateBoolGuard e | Just _ <- isTrueLHsExpr e = return [] - | otherwise = let e' = lhsExprToPmExpr e - ps = [truePmPat] - in return [GBindAbs ps e'] -translateGuard (LetStmt binds) - = undefined {- WHAT TO DO WITH THIS THEN? WE CARE OR NOT? -} -translateGuard (BindStmt p e _ _) - = do pats <- translatePat (unLoc p) - let e' = lhsExprToPmExpr e - return [GBindAbs pats e'] -translateGuard (LastStmt {}) = panic "translateGuard LastStmt" -translateGuard (ParStmt {}) = panic "translateGuard ParStmt" -translateGuard (TransStmt {}) = panic "translateGuard TransStmt" -translateGuard (RecStmt {}) = panic "translateGuard RecStmt" + -- The formal thing to do would be to generate (True <- True) + -- but it is trivial to solve so instead we give back an empty + -- PatVec for efficiency + | otherwise = return [GBindAbs [truePmPat] (lhsExprToPmExpr e)] -- ----------------------------------------------------------------------- -- | Transform source expressions (HsExpr Id) to PmExpr From git at git.haskell.org Fri Jun 26 15:43:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 Jun 2015 15:43:38 +0000 (UTC) Subject: [commit: ghc] wip/gadtpm: [ongoing] working on external interface (comments mainly) (e012452) Message-ID: <20150626154338.6B2B03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/gadtpm Link : http://ghc.haskell.org/trac/ghc/changeset/e0124521dd73d09e2aeb23165f15c4a377193519/ghc >--------------------------------------------------------------- commit e0124521dd73d09e2aeb23165f15c4a377193519 Author: George Karachalias Date: Fri Jun 26 17:44:04 2015 +0200 [ongoing] working on external interface (comments mainly) >--------------------------------------------------------------- e0124521dd73d09e2aeb23165f15c4a377193519 compiler/deSugar/Check.hs | 66 +++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 66 insertions(+) diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs index 90d5b2e..944a72e 100644 --- a/compiler/deSugar/Check.hs +++ b/compiler/deSugar/Check.hs @@ -396,6 +396,72 @@ translateEqnInfo :: EquationInfo -> UniqSM PatVec translateEqnInfo (EqnInfo { eqn_pats = ps }) = concat <$> translatePatVec ps +dsSrcVector :: [Pat Id] -> [GuardStmt Id] -> DsM PatVec +dsSrcVector pats guards = liftUs $ do + ps_vec <- concat <$> translatePatVec pats + gd_vec <- translateGuards guards + return (ps_vec ++ gd_vec) + +-- | Instead of [EquationInfo] +-- eqn_pats :: [Pat Id] +-- eqn_rhs :: MatchResult +-- Use the type: +-- ([Pat Id], [GuardStmt Id]) +-- +-- It contains the same information about patters but also +-- the Guard statements instead of the opaque to us MatchResult +-- +-- It is also suitable for all possible forms: case expressions, let-bindings, +-- lambda bindings, do-expressions, etc. + +-- This is not OK. we can have: +-- +-- p1 .. pn | g1 -> ... +-- | g2 -> ... +-- ... +-- | gm -> ... + +-- Which should be translated to this I think: +-- +-- p1 .. pn | g1 -> ... +-- p1 .. pn | g2 -> ... +-- ... +-- p1 .. pn | gm -> ... + + +-- check2 :: [Type] -> [([Pat Id], [GuardStmt Id])] -> DsM PmResult +-- check2 tys pats_guards +-- | null pats_guards = return ([],[],[]) -- If we have an empty match, do not reason at all +-- | otherwise = do +-- usupply <- getUniqueSupplyM +-- (rs,is,us) <- check'2 pats_guards (initial_uncovered usupply tys) +-- return (rs, is, valSetAbsToList us) +-- +-- check'2 :: [([Pat Id], [GuardStmt Id])] -> ValSetAbs -> DsM ([EquationInfo], [EquationInfo], ValSetAbs) +-- check'2 [] missing = +-- +-- +-- check' :: [EquationInfo] -> ValSetAbs -> DsM ([EquationInfo], [EquationInfo], ValSetAbs) +-- check' [] missing = do +-- missing' <- pruneValSetAbs missing +-- return ([], [], missing') +-- check' (eq:eqs) missing = do +-- -- Translate and process current clause +-- translated <- liftUs (translateEqnInfo eq) +-- (c, d, us ) <- patVectProc translated missing +-- (rs, is, us') <- check' eqs us +-- return $ case (c,d) of +-- (True, _) -> ( rs, is, us') +-- (False, True) -> ( rs, eq:is, us') +-- (False, False) -> (eq:rs, is, us') + + + + + + + + -- ----------------------------------------------------------------------- -- | Transform source guards (GuardStmt Id) to PmPats (Pattern) From git at git.haskell.org Fri Jun 26 16:53:09 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 Jun 2015 16:53:09 +0000 (UTC) Subject: [commit: ghc] master: Comments only (cbd9278) Message-ID: <20150626165309.60A733A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cbd9278c45929f8e680e5c711a4502e9ee345e56/ghc >--------------------------------------------------------------- commit cbd9278c45929f8e680e5c711a4502e9ee345e56 Author: Simon Peyton Jones Date: Fri Jun 26 08:35:11 2015 +0100 Comments only >--------------------------------------------------------------- cbd9278c45929f8e680e5c711a4502e9ee345e56 compiler/typecheck/TcRules.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/typecheck/TcRules.hs b/compiler/typecheck/TcRules.hs index f36c476..3625db1 100644 --- a/compiler/typecheck/TcRules.hs +++ b/compiler/typecheck/TcRules.hs @@ -282,7 +282,7 @@ Deciding which equalities to quantify over is tricky: F is a type function. The difficulty is that it's hard to tell what is insoluble! -So we see whether the simplificaiotn step yielded any type errors, +So we see whether the simplification step yielded any type errors, and if so refrain from quantifying over *any* equalities. -} From git at git.haskell.org Fri Jun 26 16:53:12 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 Jun 2015 16:53:12 +0000 (UTC) Subject: [commit: ghc] master: Small doc fixes (caf9d42) Message-ID: <20150626165312.21FA13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/caf9d427d423a8ff63fd4c5a1332d058004751ff/ghc >--------------------------------------------------------------- commit caf9d427d423a8ff63fd4c5a1332d058004751ff Author: Simon Peyton Jones Date: Fri Jun 26 11:36:02 2015 +0100 Small doc fixes >--------------------------------------------------------------- caf9d427d423a8ff63fd4c5a1332d058004751ff docs/users_guide/safe_haskell.xml | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/docs/users_guide/safe_haskell.xml b/docs/users_guide/safe_haskell.xml index 1cb98ad..814f5c9 100644 --- a/docs/users_guide/safe_haskell.xml +++ b/docs/users_guide/safe_haskell.xml @@ -555,7 +555,7 @@ The module was compiled with - All of M's direct safe importsare trusted by + All of M's direct safe importsare trusted by C @@ -688,14 +688,14 @@ imports! - + Buggle only imports Prelude, which is compiled with . Prelude resides in the base package, which C trusts, and (we'll assume) all of Prelude's imports are trusted. So C trusts Prelude, and so C also trusts Buggle. (While Prelude is typically imported implicitly, it still obeys the same rules outlined here). - + From git at git.haskell.org Fri Jun 26 16:53:16 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 Jun 2015 16:53:16 +0000 (UTC) Subject: [commit: ghc] master: Improve CPR behavior for strict constructors (0696fc6) Message-ID: <20150626165316.4EAC83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0696fc6d4de28cb589f6c751b8491911a5baf774/ghc >--------------------------------------------------------------- commit 0696fc6d4de28cb589f6c751b8491911a5baf774 Author: Simon Peyton Jones Date: Fri Jun 26 11:40:01 2015 +0100 Improve CPR behavior for strict constructors When working on Trac #10482 I noticed that we could give constructor arguments the CPR property if they are use strictly. This is documented carefully in Note [CPR in a product case alternative] and also Note [Initial CPR for strict binders] There are a bunch of intersting examples in Note [CPR examples] which I have added to the test suite as T10482a. I also added a test for #10482 itself. >--------------------------------------------------------------- 0696fc6d4de28cb589f6c751b8491911a5baf774 compiler/stranal/DmdAnal.hs | 284 +++++++++++++++------ testsuite/tests/stranal/T10482a.hs | 61 +++++ testsuite/tests/stranal/should_compile/Makefile | 12 + testsuite/tests/stranal/should_compile/T10482.hs | 14 + .../tests/stranal/should_compile/T10482.stdout | 1 + testsuite/tests/stranal/should_compile/T10482a.hs | 63 +++++ .../tests/stranal/should_compile/T10482a.stdout | 4 + testsuite/tests/stranal/should_compile/all.T | 6 + 8 files changed, 369 insertions(+), 76 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 0696fc6d4de28cb589f6c751b8491911a5baf774 From git at git.haskell.org Fri Jun 26 16:53:19 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 Jun 2015 16:53:19 +0000 (UTC) Subject: [commit: ghc] master: closeOverKinds *before* oclose in coverage check (7c07cf1) Message-ID: <20150626165319.9A4573A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7c07cf16ab5d5bdfb64efb1d4fc5f20cf7437437/ghc >--------------------------------------------------------------- commit 7c07cf16ab5d5bdfb64efb1d4fc5f20cf7437437 Author: Simon Peyton Jones Date: Fri Jun 26 14:28:45 2015 +0100 closeOverKinds *before* oclose in coverage check Combining functional dependencies with kind-polymorphism is devilishly tricky! It's all documented in Note [Closing over kinds in coverage] Fixes Trac #10564 >--------------------------------------------------------------- 7c07cf16ab5d5bdfb64efb1d4fc5f20cf7437437 compiler/typecheck/FunDeps.hs | 85 ++++++++++++++++++---- testsuite/tests/typecheck/should_compile/T10564.hs | 20 +++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 3 files changed, 91 insertions(+), 15 deletions(-) diff --git a/compiler/typecheck/FunDeps.hs b/compiler/typecheck/FunDeps.hs index 830873c..3b44caa 100644 --- a/compiler/typecheck/FunDeps.hs +++ b/compiler/typecheck/FunDeps.hs @@ -387,10 +387,15 @@ checkInstCoverage be_liberal clas theta inst_taus rs_tvs = tyVarsOfTypes rs conservative_ok = rs_tvs `subVarSet` closeOverKinds ls_tvs - liberal_ok = rs_tvs `subVarSet` closeOverKinds (oclose theta ls_tvs) - -- closeOverKinds: see Note [Closing over kinds in coverage] - - msg = vcat [ sep [ ptext (sLit "The") + liberal_ok = rs_tvs `subVarSet` oclose theta (closeOverKinds ls_tvs) + -- closeOverKinds: see Note [Closing over kinds in coverage] + + msg = vcat [ -- text "ls_tvs" <+> ppr ls_tvs + -- , text "closed ls_tvs" <+> ppr (closeOverKinds ls_tvs) + -- , text "theta" <+> ppr theta + -- , text "oclose" <+> ppr (oclose theta (closeOverKinds ls_tvs)) + -- , text "rs_tvs" <+> ppr rs_tvs + sep [ ptext (sLit "The") <+> ppWhen be_liberal (ptext (sLit "liberal")) <+> ptext (sLit "coverage condition fails in class") <+> quotes (ppr clas) @@ -406,22 +411,70 @@ checkInstCoverage be_liberal clas theta inst_taus , ppWhen (not be_liberal && liberal_ok) $ ptext (sLit "Using UndecidableInstances might help") ] -{- -Note [Closing over kinds in coverage] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +{- Note [Closing over kinds in coverage] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Suppose we have a fundep (a::k) -> b Then if 'a' is instantiated to (x y), where x:k2->*, y:k2, then fixing x really fixes k2 as well, and so k2 should be added to the lhs tyvars in the fundep check. Example (Trac #8391), using liberal coverage + data Foo a = ... -- Foo :: forall k. k -> * + class Bar a b | a -> b + instance Bar a (Foo a) + + In the instance decl, (a:k) does fix (Foo k a), but only if we notice + that (a:k) fixes k. Trac #10109 is another example. + +Here is a more subtle example, from HList-0.4.0.0 (Trac #10564) + + class HasFieldM (l :: k) r (v :: Maybe *) + | l r -> v where ... + class HasFieldM1 (b :: Maybe [*]) (l :: k) r v + | b l r -> v where ... + class HMemberM (e1 :: k) (l :: [k]) (r :: Maybe [k]) + | e1 l -> r + + data Label :: k -> * + type family LabelsOf (a :: [*]) :: * + + instance (HMemberM (Label {k} (l::k)) (LabelsOf xs) b, + HasFieldM1 b l (r xs) v) + => HasFieldM l (r xs) v where + +Is the instance OK? Does {l,r,xs} determine v? Well: + + * From the instance constraint HMemberM (Label k l) (LabelsOf xs) b, + plus the fundep "| el l -> r" in class HMameberM, + we get {l,k,xs} -> b + + * Note the 'k'!! We must call closeOverKinds on the seed set + ls_tvs = {l,r,xs}, BEFORE doing oclose, else the {l,k,xs}->b + fundep won't fire. This was the reason for #10564. + + * So starting from seeds {l,r,xs,k} we do oclose to get + first {l,r,xs,k,b}, via the HMemberM constraint, and then + {l,r,xs,k,b,v}, via the HasFieldM1 constraint. + + * And that fixes v. + +However, we must closeOverKinds whenever augmenting the seed set +in oclose! Consider Trac #10109: + + data Succ a -- Succ :: forall k. k -> * + class Add (a :: k1) (b :: k2) (ab :: k3) | a b -> ab + instance (Add a b ab) => Add (Succ {k1} (a :: k1)) + b + (Succ {k3} (ab :: k3}) - type Foo a = a -- Foo :: forall k. k -> k - class Bar a b | a -> b - instance Bar a (Foo a) +We start with seed set {a:k1,b:k2} and closeOverKinds to {a,k1,b,k2}. +Now use the fundep to extend to {a,k1,b,k2,ab}. But we need to +closeOverKinds *again* now to {a,k1,b,k2,ab,k3}, so that we fix all +the variables free in (Succ {k3} ab). -In the instance decl, (a:k) does fix (Foo k a), but only if we notice -that (a:k) fixes k. Trac #10109 is another example. +Bottom line: + * closeOverKinds on initial seeds (in checkInstCoverage) + * and closeOverKinds whenever extending those seeds (in oclose) Note [The liberal coverage condition] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -451,12 +504,14 @@ oclose preds fixed_tvs extend fixed_tvs = foldl add fixed_tvs tv_fds where add fixed_tvs (ls,rs) - | ls `subVarSet` fixed_tvs = fixed_tvs `unionVarSet` rs + | ls `subVarSet` fixed_tvs = fixed_tvs `unionVarSet` closeOverKinds rs | otherwise = fixed_tvs + -- closeOverKinds: see Note [Closing over kinds in coverage] tv_fds :: [(TyVarSet,TyVarSet)] - tv_fds = [ (tyVarsOfTypes xs, tyVarsOfTypes ys) - | (xs, ys) <- concatMap determined preds ] + tv_fds = [ (tyVarsOfTypes ls, tyVarsOfTypes rs) + | pred <- preds + , (ls, rs) <- determined pred ] determined :: PredType -> [([Type],[Type])] determined pred diff --git a/testsuite/tests/typecheck/should_compile/T10564.hs b/testsuite/tests/typecheck/should_compile/T10564.hs new file mode 100644 index 0000000..7b19f00 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T10564.hs @@ -0,0 +1,20 @@ +{-# LANGUAGE FlexibleInstances, FlexibleContexts, UndecidableInstances, + DataKinds, TypeFamilies, KindSignatures, PolyKinds, FunctionalDependencies #-} + +module T10564 where + +class HasFieldM (l :: k) r (v :: Maybe *) + | l r -> v + +class HasFieldM1 (b :: Maybe [*]) (l :: k) r v + | b l r -> v + +class HMemberM (e1 :: k) (l :: [k]) (r :: Maybe [k]) + | e1 l -> r + +data Label a +type family LabelsOf (a :: [*]) :: [*] + +instance (HMemberM (Label (l::k)) (LabelsOf xs) b, + HasFieldM1 b l (r xs) v) + => HasFieldM l (r xs) v where diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index 89227c6..178f9f3 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -464,3 +464,4 @@ test('T10493', normal, compile, ['']) test('T10428', normal, compile, ['']) test('RepArrow', normal, compile, ['']) test('T10562', normal, compile, ['']) +test('T10564', normal, compile, ['']) From git at git.haskell.org Fri Jun 26 16:53:22 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 Jun 2015 16:53:22 +0000 (UTC) Subject: [commit: ghc] master: Kill off sizePred (614ba3c) Message-ID: <20150626165322.941CB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/614ba3c57be611a053c8c95698020de68df29558/ghc >--------------------------------------------------------------- commit 614ba3c57be611a053c8c95698020de68df29558 Author: Simon Peyton Jones Date: Fri Jun 26 14:34:42 2015 +0100 Kill off sizePred It really isn't needed, and life is simpler without >--------------------------------------------------------------- 614ba3c57be611a053c8c95698020de68df29558 compiler/typecheck/TcCanonical.hs | 10 +++++++-- compiler/typecheck/TcInstDcls.hs | 4 ++-- compiler/typecheck/TcRnTypes.hs | 10 +++++---- compiler/typecheck/TcType.hs | 45 ++++++++++++--------------------------- 4 files changed, 30 insertions(+), 39 deletions(-) diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index 9bd2f70..e91304a 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -318,8 +318,14 @@ newSCWorkFromFlavored :: CtEvidence -> Class -> [Xi] -> TcS () -- Returns superclasses, see Note [Adding superclasses] newSCWorkFromFlavored flavor cls xis | CtGiven { ctev_evar = evar, ctev_loc = loc } <- flavor - = do { let size = sizePred (mkClassPred cls xis) - loc' = case ctLocOrigin loc of + = do { let size = sizeTypes xis + loc' | isCTupleClass cls + = loc -- For tuple predicates, just take them apart, without + -- adding their (large) size into the chain. When we + -- get down to a base predicate, we'll include its size. + -- Trac #10335 + | otherwise + = case ctLocOrigin loc of GivenOrigin InstSkol -> loc { ctl_origin = GivenOrigin (InstSC size) } GivenOrigin (InstSC n) diff --git a/compiler/typecheck/TcInstDcls.hs b/compiler/typecheck/TcInstDcls.hs index 9a0093d..2c9a980 100644 --- a/compiler/typecheck/TcInstDcls.hs +++ b/compiler/typecheck/TcInstDcls.hs @@ -999,7 +999,7 @@ tcSuperClasses dfun_id cls tyvars dfun_evs inst_tys dfun_ev_binds _fam_envs sc_t ; return (ids, listToBag binds, listToBag implics) } where loc = getSrcSpan dfun_id - size = sizePred (mkClassPred cls inst_tys) + size = sizeTypes inst_tys tc_super (sc_pred, n) = do { (sc_implic, sc_ev_id) <- checkInstConstraints $ \_ -> emitWanted (ScOrigin size) sc_pred @@ -1096,7 +1096,7 @@ generate a guaranteed-non-bottom superclass witness from: (sc3) a call of a dfun (always returns a dictionary constructor) The tricky case is (sc2). We proceed by induction on the size of -the (type of) the dictionary, defined by TcValidity.sizePred. +the (type of) the dictionary, defined by TcValidity.sizeTypes. Let's suppose we are building a dictionary of size 3, and suppose the Superclass Invariant holds of smaller dictionaries. Then if we have a smaller dictionary, its immediate superclasses diff --git a/compiler/typecheck/TcRnTypes.hs b/compiler/typecheck/TcRnTypes.hs index 6c3c73e..c2d5da0 100644 --- a/compiler/typecheck/TcRnTypes.hs +++ b/compiler/typecheck/TcRnTypes.hs @@ -2067,9 +2067,10 @@ data SkolemInfo | ClsSkol Class -- Bound at a class decl | InstSkol -- Bound at an instance decl - | InstSC TypeSize -- A "given" constraint obtained by superclass selection - -- from an InstSkol, giving the largest class from - -- which we made a superclass selection in the chain + | InstSC TypeSize -- A "given" constraint obtained by superclass selection. + -- If (C ty1 .. tyn) is the largest class from + -- which we made a superclass selection in the chain, + -- then TypeSize = sizeTypes [ty1, .., tyn] -- See Note [Solving superclass constraints] in TcInstDcls | DataSkol -- Bound at a data type declaration @@ -2193,7 +2194,8 @@ data CtOrigin | ViewPatOrigin | ScOrigin TypeSize -- Typechecking superclasses of an instance declaration - -- whose head has the given size + -- If the instance head is C ty1 .. tyn + -- then TypeSize = sizeTypes [ty1, .., tyn] -- See Note [Solving superclass constraints] in TcInstDcls | DerivOrigin -- Typechecking deriving diff --git a/compiler/typecheck/TcType.hs b/compiler/typecheck/TcType.hs index c3e12c3..37bf470 100644 --- a/compiler/typecheck/TcType.hs +++ b/compiler/typecheck/TcType.hs @@ -149,7 +149,7 @@ module TcType ( pprType, pprParendType, pprTypeApp, pprTyThingCategory, pprTheta, pprThetaArrowTy, pprClassPred, - TypeSize, sizePred, sizeType, sizeTypes + TypeSize, sizeType, sizeTypes ) where @@ -1872,40 +1872,23 @@ is irreducible. See Trac #5581. type TypeSize = IntWithInf -sizeType :: Type -> TypeSize +sizeType, size_type :: Type -> TypeSize -- Size of a type: the number of variables and constructors -sizeType ty | Just exp_ty <- tcView ty = sizeType exp_ty -sizeType (TyVarTy {}) = 1 -sizeType (TyConApp tc tys) +-- Ignore kinds altogether +sizeType ty | isKind ty = 0 + | otherwise = size_type ty + +size_type ty | Just exp_ty <- tcView ty = size_type exp_ty +size_type (TyVarTy {}) = 1 +size_type (TyConApp tc tys) | isTypeFamilyTyCon tc = infinity -- Type-family applications can -- expand to any arbitrary size | otherwise = sizeTypes tys + 1 -sizeType (LitTy {}) = 1 -sizeType (FunTy arg res) = sizeType arg + sizeType res + 1 -sizeType (AppTy fun arg) = sizeType fun + sizeType arg -sizeType (ForAllTy _ ty) = sizeType ty +size_type (LitTy {}) = 1 +size_type (FunTy arg res) = size_type arg + size_type res + 1 +size_type (AppTy fun arg) = size_type fun + size_type arg +size_type (ForAllTy _ ty) = size_type ty sizeTypes :: [Type] -> TypeSize --- IA0_NOTE: Avoid kinds. -sizeTypes xs = sum (map sizeType tys) - where tys = filter (not . isKind) xs - --- Note [Size of a predicate] --- ~~~~~~~~~~~~~~~~~~~~~~~~~~ --- We are considering whether class constraints terminate. --- Equality constraints and constraints for the implicit --- parameter class always termiante so it is safe to say "size 0". --- (Implicit parameter constraints always terminate because --- there are no instances for them---they are only solved by --- "local instances" in expressions). --- See Trac #4200. -sizePred :: PredType -> TypeSize -sizePred p - = case classifyPredType p of - ClassPred cls tys - | isIPClass cls -> 0 -- See Note [Size of a predicate] - | isCTupleClass cls -> maximum (0 : map sizePred tys) - | otherwise -> sizeTypes tys - EqPred {} -> 0 -- See Note [Size of a predicate] - IrredPred ty -> sizeType ty +sizeTypes tys = sum (map sizeType tys) From git at git.haskell.org Fri Jun 26 16:53:25 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 Jun 2015 16:53:25 +0000 (UTC) Subject: [commit: ghc] master: Make fvType ignore kinds (8e34783) Message-ID: <20150626165325.529B43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8e347839be4d52b6f74cc11e18e5820f88969c80/ghc >--------------------------------------------------------------- commit 8e347839be4d52b6f74cc11e18e5820f88969c80 Author: Simon Peyton Jones Date: Fri Jun 26 15:56:35 2015 +0100 Make fvType ignore kinds TcValidity.fvTypes works in partnership with sizeTypes, and hence should ignore kinds in exactly the same way. It wasn't doing so, which meant that validDerivPred said "No" when it should have said "Yes". That led to the bug reported in Trac #10524 comment:7. The error message is pretty terrible No instance for (Typeable T) but I'll fix that next >--------------------------------------------------------------- 8e347839be4d52b6f74cc11e18e5820f88969c80 compiler/typecheck/TcValidity.hs | 103 ++++++++++++++++++++++----------------- 1 file changed, 59 insertions(+), 44 deletions(-) diff --git a/compiler/typecheck/TcValidity.hs b/compiler/typecheck/TcValidity.hs index 663990f..355341a 100644 --- a/compiler/typecheck/TcValidity.hs +++ b/compiler/typecheck/TcValidity.hs @@ -908,21 +908,33 @@ instTypeErr cls tys msg 2 (quotes (pprClassPred cls tys))) 2 msg -{- -validDeivPred checks for OK 'deriving' context. See Note [Exotic +{- Note [Valid 'deriving' predicate] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +validDerivPred checks for OK 'deriving' context. See Note [Exotic derived instance contexts] in TcDeriv. However the predicate is here because it uses sizeTypes, fvTypes. -Also check for a bizarre corner case, when the derived instance decl -would look like - instance C a b => D (T a) where ... -Note that 'b' isn't a parameter of T. This gives rise to all sorts of -problems; in particular, it's hard to compare solutions for equality -when finding the fixpoint, and that means the inferContext loop does -not converge. See Trac #5287. +It checks for three things + + * No repeated variables (hasNoDups fvs) + + * No type constructors. This is done by comparing + sizeTypes tys == length (fvTypes tys) + sizeTypes counts variables and constructors; fvTypes returns variables. + So if they are the same, there must be no constructors. But there + might be applications thus (f (g x)). + + * Also check for a bizarre corner case, when the derived instance decl + would look like + instance C a b => D (T a) where ... + Note that 'b' isn't a parameter of T. This gives rise to all sorts of + problems; in particular, it's hard to compare solutions for equality + when finding the fixpoint, and that means the inferContext loop does + not converge. See Trac #5287. -} validDerivPred :: TyVarSet -> PredType -> Bool +-- See Note [Valid 'deriving' predicate] validDerivPred tv_set pred = case classifyPredType pred of ClassPred _ tys -> check_tys tys @@ -932,7 +944,8 @@ validDerivPred tv_set pred check_tys tys = hasNoDups fvs && sizeTypes tys == fromIntegral (length fvs) && all (`elemVarSet` tv_set) fvs - fvs = fvType pred + where + fvs = fvTypes tys {- ************************************************************************ @@ -1001,42 +1014,39 @@ The underlying idea is that context has fewer type constructors than the head. -} -leafTyConKeys :: [Unique] -leafTyConKeys = [eqTyConKey, coercibleTyConKey, ipClassNameKey] - checkInstTermination :: [TcType] -> ThetaType -> TcM () -- See Note [Paterson conditions] checkInstTermination tys theta = check_preds theta where - fvs = fvTypes tys - size = sizeTypes tys + head_fvs = fvTypes tys + head_size = sizeTypes tys check_preds :: [PredType] -> TcM () check_preds preds = mapM_ check preds check :: PredType -> TcM () check pred - = case tcSplitTyConApp_maybe pred of - Just (tc, tys) - | getUnique tc `elem` leafTyConKeys - -> return () -- You can't get from equalities or implicit - -- params to class predicates, so this is safe - - | isTupleTyCon tc + = case classifyPredType pred of + EqPred {} -> return () -- See Trac #4200. + IrredPred {} -> check2 pred (sizeType pred) + ClassPred cls tys + | isIPClass cls + -> return () -- You can't get to class predicates from implicit params + + | isCTupleClass cls -- Look inside tuple predicates; Trac #8359 -> check_preds tys - -- Look inside tuple predicates; Trac #8359 - _other -- All others: other ClassPreds, IrredPred - | not (null bad_tvs) -> addErrTc (noMoreMsg bad_tvs what) - | sizePred pred >= size -> addErrTc (smallerMsg what) - | otherwise -> return () + | otherwise + -> check2 pred (sizeTypes tys) -- Other ClassPreds + + check2 pred pred_size + | not (null bad_tvs) = addErrTc (noMoreMsg bad_tvs what) + | pred_size >= head_size = addErrTc (smallerMsg what) + | otherwise = return () where what = ptext (sLit "constraint") <+> quotes (ppr pred) - bad_tvs = filterOut isKindVar (fvType pred \\ fvs) - -- Rightly or wrongly, we only check for - -- excessive occurrences of *type* variables. - -- e.g. type instance Demote {T k} a = T (Demote {k} (Any {k})) + bad_tvs = fvType pred \\ head_fvs smallerMsg :: SDoc -> SDoc smallerMsg what @@ -1248,10 +1258,7 @@ checkFamInstRhs lhsTys famInsts | otherwise = Nothing where what = ptext (sLit "type family application") <+> quotes (pprType (TyConApp tc tys)) - bad_tvs = filterOut isKindVar (fvTypes tys \\ fvs) - -- Rightly or wrongly, we only check for - -- excessive occurrences of *type* variables. - -- e.g. type instance Demote {T k} a = T (Demote {k} (Any {k})) + bad_tvs = fvTypes tys \\ fvs checkValidFamPats :: TyCon -> [TyVar] -> [Type] -> TcM () -- Patterns in a 'type instance' or 'data instance' decl should @@ -1314,15 +1321,23 @@ famPatErr fam_tc tvs pats -} -- Free variables of a type, retaining repetitions, and expanding synonyms -fvType :: Type -> [TyVar] -fvType ty | Just exp_ty <- tcView ty = fvType exp_ty -fvType (TyVarTy tv) = [tv] -fvType (TyConApp _ tys) = fvTypes tys -fvType (LitTy {}) = [] -fvType (FunTy arg res) = fvType arg ++ fvType res -fvType (AppTy fun arg) = fvType fun ++ fvType arg -fvType (ForAllTy tyvar ty) = filter (/= tyvar) (fvType ty) +-- Ignore kinds altogether: rightly or wrongly, we only check for +-- excessive occurrences of *type* variables. +-- e.g. type instance Demote {T k} a = T (Demote {k} (Any {k})) +-- +-- c.f. sizeType, which is often called side by side with fvType +fvType, fv_type :: Type -> [TyVar] +fvType ty | isKind ty = [] + | otherwise = fv_type ty + +fv_type ty | Just exp_ty <- tcView ty = fv_type exp_ty +fv_type (TyVarTy tv) = [tv] +fv_type (TyConApp _ tys) = fvTypes tys +fv_type (LitTy {}) = [] +fv_type (FunTy arg res) = fv_type arg ++ fv_type res +fv_type (AppTy fun arg) = fv_type fun ++ fv_type arg +fv_type (ForAllTy tyvar ty) = filter (/= tyvar) (fv_type ty) fvTypes :: [Type] -> [TyVar] -fvTypes tys = concat (map fvType tys) +fvTypes tys = concat (map fvType tys) From git at git.haskell.org Fri Jun 26 16:53:28 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 Jun 2015 16:53:28 +0000 (UTC) Subject: [commit: ghc] master: Better tracing and tiny refactoring (a64a26f) Message-ID: <20150626165328.467B93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a64a26f0a1a864522937caaf68687baf1a5f9bcb/ghc >--------------------------------------------------------------- commit a64a26f0a1a864522937caaf68687baf1a5f9bcb Author: Simon Peyton Jones Date: Fri Jun 26 15:57:28 2015 +0100 Better tracing and tiny refactoring >--------------------------------------------------------------- a64a26f0a1a864522937caaf68687baf1a5f9bcb compiler/typecheck/TcInteract.hs | 29 ++++++++++++++++++----------- 1 file changed, 18 insertions(+), 11 deletions(-) diff --git a/compiler/typecheck/TcInteract.hs b/compiler/typecheck/TcInteract.hs index fca57d7..b68dd34 100644 --- a/compiler/typecheck/TcInteract.hs +++ b/compiler/typecheck/TcInteract.hs @@ -14,7 +14,7 @@ import TcCanonical import TcFlatten import VarSet import Type -import Kind ( isKind, isConstraintKind ) +import Kind ( isKind ) import InstEnv( DFunInstType, lookupInstEnv, instanceDFunId ) import CoAxiom(sfInteractTop, sfInteractInert) @@ -1620,12 +1620,19 @@ instance Outputable LookupInstResult where where ss = text $ if s then "[safe]" else "[unsafe]" -matchClassInst :: DynFlags -> InertSet -> Class -> [Type] -> CtLoc -> TcS LookupInstResult +matchClassInst, match_class_inst + :: DynFlags -> InertSet -> Class -> [Type] -> CtLoc -> TcS LookupInstResult + +matchClassInst dflags inerts clas tys loc + = do { traceTcS "matchClassInst" $ vcat [ text "pred =" <+> ppr (mkClassPred clas tys) ] + ; res <- match_class_inst dflags inerts clas tys loc + ; traceTcS "matchClassInst result" $ ppr res + ; return res } -- First check whether there is an in-scope Given that could -- match this constraint. In that case, do not use top-level -- instances. See Note [Instance and Given overlap] -matchClassInst dflags inerts clas tys loc +match_class_inst dflags inerts clas tys loc | not (xopt Opt_IncoherentInstances dflags) , let matchable_givens = matchableGivens loc pred inerts , not (isEmptyBag matchable_givens) @@ -1636,7 +1643,7 @@ matchClassInst dflags inerts clas tys loc where pred = mkClassPred clas tys -matchClassInst _ _ clas [ ty ] _ +match_class_inst _ _ clas [ ty ] _ | className clas == knownNatClassName , Just n <- isNumLitTy ty = makeDict (EvNum n) @@ -1672,20 +1679,19 @@ matchClassInst _ _ clas [ ty ] _ = panicTcS (text "Unexpected evidence for" <+> ppr (className clas) $$ vcat (map (ppr . idType) (classMethods clas))) -matchClassInst _ _ clas ts _ +match_class_inst _ _ clas ts _ | isCTupleClass clas , let data_con = tyConSingleDataCon (classTyCon clas) tuple_ev = EvDFunApp (dataConWrapId data_con) ts = return (GenInst ts tuple_ev True) -- The dfun is the data constructor! -matchClassInst _ _ clas [k,t] _ +match_class_inst _ _ clas [k,t] _ | className clas == typeableClassName = matchTypeableClass clas k t -matchClassInst dflags _ clas tys loc - = do { traceTcS "matchClassInst" $ vcat [ text "pred =" <+> ppr pred ] - ; instEnvs <- getInstEnvs +match_class_inst dflags _ clas tys loc + = do { instEnvs <- getInstEnvs ; let safeOverlapCheck = safeHaskell dflags `elem` [Sf_Safe, Sf_Trustworthy] (matches, unify, unsafeOverlaps) = lookupInstEnv True instEnvs clas tys safeHaskFail = safeOverlapCheck && not (null unsafeOverlaps) @@ -1815,15 +1821,16 @@ matchTypeableClass clas k t -- See Note [No Typeable for qualified types] | isForAllTy t = return NoInstance + -- Is the type of the form `C => t`? - | Just (t1,_) <- splitFunTy_maybe t, - isConstraintKind (typeKind t1) = return NoInstance + | isJust (tcSplitPredFunTy_maybe t) = return NoInstance | eqType k typeNatKind = doTyLit knownNatClassName | eqType k typeSymbolKind = doTyLit knownSymbolClassName | Just (tc, ks) <- splitTyConApp_maybe t , all isKind ks = doTyCon tc ks + | Just (f,kt) <- splitAppTy_maybe t = doTyApp f kt | otherwise = return NoInstance From git at git.haskell.org Fri Jun 26 16:53:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 Jun 2015 16:53:31 +0000 (UTC) Subject: [commit: ghc] master: Improve error message for Typeable k (T k) (ceb3c84) Message-ID: <20150626165331.1BDD53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ceb3c8448dfba23aa98a710f846304158c1c584b/ghc >--------------------------------------------------------------- commit ceb3c8448dfba23aa98a710f846304158c1c584b Author: Simon Peyton Jones Date: Fri Jun 26 16:00:19 2015 +0100 Improve error message for Typeable k (T k) GHC can't yest build a TypeRep for a type involving kind variables. (We await kinds = types for that.) But the error message was terrible, as fixing #10524 reminded me. This improves it a lot. >--------------------------------------------------------------- ceb3c8448dfba23aa98a710f846304158c1c584b compiler/typecheck/TcErrors.hs | 32 +++++++++++----------- .../tests/annotations/should_fail/annfail08.stderr | 10 +++---- .../tests/deriving/should_fail/drvfail007.stderr | 4 +-- testsuite/tests/driver/T2182.stderr | 20 ++++++-------- .../tests/ghci.debugger/scripts/break003.stderr | 5 ++-- testsuite/tests/ghci/scripts/Defer02.stderr | 6 ++-- testsuite/tests/ghci/scripts/T2182ghci.stderr | 25 +++++++---------- .../should_fail/AnnotatedConstraint.stderr | 5 ++-- testsuite/tests/rebindable/rebindable6.stderr | 12 ++++---- .../tests/typecheck/should_fail/T2846b.stderr | 5 ++-- testsuite/tests/typecheck/should_fail/T6022.stderr | 3 +- .../tests/typecheck/should_fail/T9858a.stderr | 2 +- .../tests/typecheck/should_fail/T9858b.stderr | 2 +- testsuite/tests/typecheck/should_fail/T9999.stderr | 7 ++--- .../should_fail/TcStaticPointersFail02.stderr | 2 +- .../tests/typecheck/should_fail/tcfail046.stderr | 6 ++-- 16 files changed, 65 insertions(+), 81 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ceb3c8448dfba23aa98a710f846304158c1c584b From git at git.haskell.org Fri Jun 26 16:53:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 Jun 2015 16:53:34 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #10524 (0e1e798) Message-ID: <20150626165334.D61013A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0e1e7987bdcec0e9be309cbe97fa1c92551997f7/ghc >--------------------------------------------------------------- commit 0e1e7987bdcec0e9be309cbe97fa1c92551997f7 Author: Simon Peyton Jones Date: Fri Jun 26 16:00:45 2015 +0100 Test Trac #10524 >--------------------------------------------------------------- 0e1e7987bdcec0e9be309cbe97fa1c92551997f7 testsuite/tests/deriving/should_fail/T10524.hs | 8 ++++++++ testsuite/tests/deriving/should_fail/T10524.stderr | 10 ++++++++++ testsuite/tests/deriving/should_fail/all.T | 1 + 3 files changed, 19 insertions(+) diff --git a/testsuite/tests/deriving/should_fail/T10524.hs b/testsuite/tests/deriving/should_fail/T10524.hs new file mode 100644 index 0000000..43d93bf --- /dev/null +++ b/testsuite/tests/deriving/should_fail/T10524.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE DeriveDataTypeable #-} +{-# LANGUAGE PolyKinds #-} +module T10524 where + +import Data.Data + +newtype WrappedFunctor f a = WrapFunctor (f a) deriving (Data, Typeable) + diff --git a/testsuite/tests/deriving/should_fail/T10524.stderr b/testsuite/tests/deriving/should_fail/T10524.stderr new file mode 100644 index 0000000..1569972 --- /dev/null +++ b/testsuite/tests/deriving/should_fail/T10524.stderr @@ -0,0 +1,10 @@ + +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)) diff --git a/testsuite/tests/deriving/should_fail/all.T b/testsuite/tests/deriving/should_fail/all.T index adc72fc..2e25113 100644 --- a/testsuite/tests/deriving/should_fail/all.T +++ b/testsuite/tests/deriving/should_fail/all.T @@ -54,3 +54,4 @@ test('T9071_2', normal, compile_fail, ['']) test('T9687', normal, compile_fail, ['']) test('T8984', normal, compile_fail, ['']) +test('T10524', normal, compile_fail, ['']) From git at git.haskell.org Fri Jun 26 19:25:42 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 Jun 2015 19:25:42 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Be aware of overlapping global STG registers in CmmSink (#10521) (7707e54) Message-ID: <20150626192542.53D273A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/7707e54c0e3e3dc7bd7b0f44a9567770340ace31/ghc >--------------------------------------------------------------- commit 7707e54c0e3e3dc7bd7b0f44a9567770340ace31 Author: Reid Barton Date: Thu Jun 25 13:53:57 2015 -0400 Be aware of overlapping global STG registers in CmmSink (#10521) Summary: On x86_64, commit e2f6bbd3a27685bc667655fdb093734cb565b4cf assigned the STG registers F1 and D1 the same hardware register (xmm1), and the same for the registers F2 and D2, etc. When mixing calls to functions involving Float#s and Double#s, this can cause wrong Cmm optimizations that assume the F1 and D1 registers are independent. Reviewers: simonpj, austin Reviewed By: austin Subscribers: simonpj, thomie, bgamari Differential Revision: https://phabricator.haskell.org/D993 GHC Trac Issues: #10521 (cherry picked from commit a2f828a370b220839ad9b31a274c0198ef91b7fe) >--------------------------------------------------------------- 7707e54c0e3e3dc7bd7b0f44a9567770340ace31 compiler/cmm/CmmExpr.hs | 37 +++++++++++++++------- compiler/cmm/CmmSink.hs | 15 ++++----- compiler/cmm/CmmUtils.hs | 36 +++++++++++++++++++++ compiler/codeGen/StgCmmUtils.hs | 16 ++++++---- includes/stg/MachRegs.h | 6 ++++ testsuite/.gitignore | 2 ++ testsuite/tests/codeGen/should_run/T10521.hs | 11 +++++++ testsuite/tests/codeGen/should_run/T10521.stdout | 1 + testsuite/tests/codeGen/should_run/T10521b.hs | 18 +++++++++++ .../should_run/{T5747.stdout => T10521b.stdout} | 0 testsuite/tests/codeGen/should_run/all.T | 2 ++ 11 files changed, 117 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 7707e54c0e3e3dc7bd7b0f44a9567770340ace31 From git at git.haskell.org Fri Jun 26 19:25:45 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 Jun 2015 19:25:45 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Make enum01/enum02/enum03 tests clang-compatible (c6f8d11) Message-ID: <20150626192545.6EE8F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/c6f8d11bc12e69ff71e0a33ac72a6578085c0faa/ghc >--------------------------------------------------------------- commit c6f8d11bc12e69ff71e0a33ac72a6578085c0faa Author: Reid Barton Date: Tue Jun 16 16:39:15 2015 -0500 Make enum01/enum02/enum03 tests clang-compatible ... by entirely replacing the use of CPP by a custom preprocessor; clang -E -traditional has no stringification mechanism at all. Reviewed By: thomie, austin Differential Revision: https://phabricator.haskell.org/D957 GHC Trac Issues: #9399 (cherry picked from commit b98ca17e12c7efdc906f4901f25e6263a5399be1) >--------------------------------------------------------------- c6f8d11bc12e69ff71e0a33ac72a6578085c0faa libraries/base/tests/all.T | 6 +++--- libraries/base/tests/enum01.hs | 7 +++++-- libraries/base/tests/enum02.hs | 7 +++++-- libraries/base/tests/enum03.hs | 7 +++++-- libraries/base/tests/enum_processor.py | 24 ++++++++++++++++++++++++ 5 files changed, 42 insertions(+), 9 deletions(-) diff --git a/libraries/base/tests/all.T b/libraries/base/tests/all.T index 1154a53..1c90d14 100644 --- a/libraries/base/tests/all.T +++ b/libraries/base/tests/all.T @@ -77,9 +77,9 @@ test('dynamic002', normal, compile_and_run, ['']) test('dynamic003', extra_run_opts('+RTS -K32m -RTS'), compile_and_run, ['']) test('dynamic004', omit_ways(['normal', 'threaded1', 'ghci']), compile_and_run, ['']) test('dynamic005', normal, compile_and_run, ['']) -test('enum01', when(fast(), skip), compile_and_run, ['-cpp']) -test('enum02', when(fast(), skip), compile_and_run, ['-cpp']) -test('enum03', when(fast(), skip), compile_and_run, ['-cpp']) +test('enum01', when(fast(), skip), compile_and_run, ['']) +test('enum02', when(fast(), skip), compile_and_run, ['']) +test('enum03', when(fast(), skip), compile_and_run, ['']) test('enum04', normal, compile_and_run, ['']) test('exceptionsrun001', normal, compile_and_run, ['']) test('exceptionsrun002', normal, compile_and_run, ['']) diff --git a/libraries/base/tests/enum01.hs b/libraries/base/tests/enum01.hs index 0f26173..0ae39b1 100644 --- a/libraries/base/tests/enum01.hs +++ b/libraries/base/tests/enum01.hs @@ -1,5 +1,9 @@ -- !!! Testing the Prelude's Enum instances. -{-# LANGUAGE CPP #-} +{-# OPTIONS_GHC -F -pgmF ./enum_processor.py #-} +-- The processor is a non-CPP-based equivalent of +-- #define printTest(x) (do{ putStr ( " " ++ "x" ++ " = " ) ; print (x) }) +-- which is not portable to clang + module Main(main) where import Control.Exception @@ -82,7 +86,6 @@ main = do OK - on with the regression testing. -} -#define printTest(x) (do{ putStr ( " " ++ "x" ++ " = " ) ; print (x) }) testEnumInt :: IO () diff --git a/libraries/base/tests/enum02.hs b/libraries/base/tests/enum02.hs index 23de6eb..f7e843c 100644 --- a/libraries/base/tests/enum02.hs +++ b/libraries/base/tests/enum02.hs @@ -1,5 +1,9 @@ -- !!! Testing the Int Enum instances. -{-# LANGUAGE CPP #-} +{-# OPTIONS_GHC -F -pgmF ./enum_processor.py #-} +-- The processor is a non-CPP-based equivalent of +-- #define printTest(x) (do{ putStr ( " " ++ "x" ++ " = " ) ; print (x) }) +-- which is not portable to clang + module Main(main) where import Control.Exception @@ -15,7 +19,6 @@ main = do putStrLn "Testing Enum Int64:" testEnumInt64 -#define printTest(x) (do{ putStr ( " " ++ "x" ++ " = " ) ; print (x) }) testEnumInt8 :: IO () testEnumInt8 = do diff --git a/libraries/base/tests/enum03.hs b/libraries/base/tests/enum03.hs index 1cbe309..181354a 100644 --- a/libraries/base/tests/enum03.hs +++ b/libraries/base/tests/enum03.hs @@ -1,5 +1,9 @@ -- !!! Testing the Word Enum instances. -{-# LANGUAGE CPP #-} +{-# OPTIONS_GHC -F -pgmF ./enum_processor.py #-} +-- The processor is a non-CPP-based equivalent of +-- #define printTest(x) (do{ putStr ( " " ++ "x" ++ " = " ) ; print (x) }) +-- which is not portable to clang + module Main(main) where import Control.Exception @@ -17,7 +21,6 @@ main = do testEnumWord64 -#define printTest(x) (do{ putStr ( " " ++ "x" ++ " = " ) ; print (x) }) testEnumWord8 :: IO () testEnumWord8 = do diff --git a/libraries/base/tests/enum_processor.py b/libraries/base/tests/enum_processor.py new file mode 100755 index 0000000..86c3d6c --- /dev/null +++ b/libraries/base/tests/enum_processor.py @@ -0,0 +1,24 @@ +#!/usr/bin/env python + +import sys + +def process(s): + while True: + start = s.find('printTest') + if start == -1: + return s + j0 = j = s.index('(', start) + 1 + depth = 1 + while depth > 0: + if s[j] == '(': + depth += 1 + if s[j] == ')': + depth -= 1 + j += 1 + argument = s[j0:j-1] + expansion = '(do{ putStr ( " " ++ "%s" ++ " = " ) ; print (%s) })' \ + % (argument, argument) + s = s[:start] + expansion + s[j:] + +_, _, inputFile, outputFile = sys.argv +open(outputFile, 'w').write(process(open(inputFile, 'r').read())) From git at git.haskell.org Fri Jun 26 19:25:48 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 Jun 2015 19:25:48 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Comments only (0d939ca) Message-ID: <20150626192548.414573A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/0d939ca1c3d5a2076cf7e5930ae633a16bd7a2e0/ghc >--------------------------------------------------------------- commit 0d939ca1c3d5a2076cf7e5930ae633a16bd7a2e0 Author: Reid Barton Date: Thu Jun 25 14:26:40 2015 -0400 Comments only (cherry picked from commit a7eee0d8a25789ce1ef349304d27e2a5e22766b7) >--------------------------------------------------------------- 0d939ca1c3d5a2076cf7e5930ae633a16bd7a2e0 libraries/base/tests/enum_processor.py | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/libraries/base/tests/enum_processor.py b/libraries/base/tests/enum_processor.py index 86c3d6c..53bea4c 100755 --- a/libraries/base/tests/enum_processor.py +++ b/libraries/base/tests/enum_processor.py @@ -1,5 +1,9 @@ #!/usr/bin/env python +# The rough equivalent of the traditional CPP: +# #define printTest(x) (do{ putStr ( " " ++ "x" ++ " = " ) ; print (x) }) +# which is not portable to clang. + import sys def process(s): From git at git.haskell.org Fri Jun 26 19:25:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 Jun 2015 19:25:51 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Fix for crash in setnumcapabilities001 (6de9b6e) Message-ID: <20150626192551.1D5A93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/6de9b6eb59c7525255e6780c57fa361ec108fc88/ghc >--------------------------------------------------------------- commit 6de9b6eb59c7525255e6780c57fa361ec108fc88 Author: Simon Marlow Date: Fri Jun 19 14:41:32 2015 +0100 Fix for crash in setnumcapabilities001 getNewNursery() was unconditionally incrementing next_nursery, which is normally fine but it broke an assumption in storageAddCapabilities(). This manifested as an occasional crash in the setnumcapabilities001 test. (cherry picked from commit be0ce8718ea40b091e69dd48fe6bc62b6b551154) >--------------------------------------------------------------- 6de9b6eb59c7525255e6780c57fa361ec108fc88 rts/sm/Storage.c | 18 ++++++++++++------ 1 file changed, 12 insertions(+), 6 deletions(-) diff --git a/rts/sm/Storage.c b/rts/sm/Storage.c index 50926b7..297e584 100644 --- a/rts/sm/Storage.c +++ b/rts/sm/Storage.c @@ -549,6 +549,7 @@ allocNursery (bdescr *tail, W_ blocks) STATIC_INLINE void assignNurseryToCapability (Capability *cap, nat n) { + ASSERT(n < n_nurseries); cap->r.rNursery = &nurseries[n]; cap->r.rCurrentNursery = nurseries[n].blocks; newNurseryBlock(nurseries[n].blocks); @@ -699,14 +700,19 @@ resizeNurseries (W_ blocks) rtsBool getNewNursery (Capability *cap) { - StgWord i = atomic_inc(&next_nursery, 1) - 1; - if (i >= n_nurseries) { - return rtsFalse; + StgWord i; + + for(;;) { + i = next_nursery; + if (i >= n_nurseries) { + return rtsFalse; + } + if (cas(&next_nursery, i, i+1) == i) { + assignNurseryToCapability(cap, i); + return rtsTrue; + } } - assignNurseryToCapability(cap, i); - return rtsTrue; } - /* ----------------------------------------------------------------------------- move_STACK is called to update the TSO structure after it has been moved from one place to another. From git at git.haskell.org Fri Jun 26 19:25:54 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 26 Jun 2015 19:25:54 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Fix deadlock (#10545) (a6ef59c) Message-ID: <20150626192554.F239B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/a6ef59cdc1c2df3c4e4ff4dcdc929c3ea14864c2/ghc >--------------------------------------------------------------- commit a6ef59cdc1c2df3c4e4ff4dcdc929c3ea14864c2 Author: Simon Marlow Date: Fri Jun 19 15:12:24 2015 +0100 Fix deadlock (#10545) yieldCapability() was not prepared to be called by a Task that is not either a worker or a bound Task. This could happen if we ended up in yieldCapability via this call stack: performGC() scheduleDoGC() requestSync() yieldCapability() and there were a few other ways this could happen via requestSync. The fix is to handle this case in yieldCapability(): when the Task is not a worker or a bound Task, we put it on the returning_workers queue, where it will be woken up again. Summary of changes: * `yieldCapability`: factored out subroutine waitForWorkerCapability` * `waitForReturnCapability` renamed to `waitForCapability`, and factored out subroutine `waitForReturnCapability` * `releaseCapabilityAndQueue` worker renamed to `enqueueWorker`, does not take a lock and no longer tests if `!isBoundTask()` * `yieldCapability` adjusted for refactorings, only change in behavior is when it is not a worker or bound task. Test Plan: * new test concurrent/should_run/performGC * validate Reviewers: niteria, austin, ezyang, bgamari Subscribers: thomie, bgamari Differential Revision: https://phabricator.haskell.org/D997 GHC Trac Issues: #10545 (cherry picked from commit 111ba4beda4ffc48381723da12e5b237d7f9ac59) >--------------------------------------------------------------- a6ef59cdc1c2df3c4e4ff4dcdc929c3ea14864c2 rts/Capability.c | 301 +++++++---- rts/Capability.h | 8 +- rts/RtsAPI.c | 2 +- rts/Schedule.c | 14 +- rts/Task.h | 11 + testsuite/tests/concurrent/should_run/RandomPGC.hs | 597 +++++++++++++++++++++ testsuite/tests/concurrent/should_run/all.T | 4 + testsuite/tests/concurrent/should_run/performGC.hs | 24 + .../tests/concurrent/should_run/performGC.stdout | 400 ++++++++++++++ 9 files changed, 1231 insertions(+), 130 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a6ef59cdc1c2df3c4e4ff4dcdc929c3ea14864c2 From git at git.haskell.org Sat Jun 27 14:51:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 27 Jun 2015 14:51:33 +0000 (UTC) Subject: [commit: ghc] master: Test #10582 (8d221bb) Message-ID: <20150627145133.B6D7D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8d221bbd7af9610ded3071df53adecad72b0fc2e/ghc >--------------------------------------------------------------- commit 8d221bbd7af9610ded3071df53adecad72b0fc2e Author: Richard Eisenberg Date: Sat Jun 27 10:51:58 2015 -0400 Test #10582 >--------------------------------------------------------------- 8d221bbd7af9610ded3071df53adecad72b0fc2e testsuite/tests/parser/should_compile/T10582.hs | 6 ++++++ testsuite/tests/parser/should_compile/all.T | 1 + 2 files changed, 7 insertions(+) diff --git a/testsuite/tests/parser/should_compile/T10582.hs b/testsuite/tests/parser/should_compile/T10582.hs new file mode 100644 index 0000000..5cafd6b --- /dev/null +++ b/testsuite/tests/parser/should_compile/T10582.hs @@ -0,0 +1,6 @@ +{-# LANGUAGE Arrows #-} + +module T10582 where + +(|:) :: Int -> Int -> Int +(|:) = (+) diff --git a/testsuite/tests/parser/should_compile/all.T b/testsuite/tests/parser/should_compile/all.T index eec0a12..68845c1 100644 --- a/testsuite/tests/parser/should_compile/all.T +++ b/testsuite/tests/parser/should_compile/all.T @@ -101,3 +101,4 @@ test('T5682', normal, compile, ['']) test('T9723a', normal, compile, ['']) test('T9723b', normal, compile, ['']) test('T10188', normal, compile, ['']) +test('T10582', expect_broken(10582), compile, ['']) From git at git.haskell.org Sun Jun 28 00:33:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 28 Jun 2015 00:33:44 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: closeOverKinds *before* oclose in coverage check (29b43fc) Message-ID: <20150628003344.5FF9F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/29b43fc7714e888ab5a2f5ebda18c0ceb48dfc2b/ghc >--------------------------------------------------------------- commit 29b43fc7714e888ab5a2f5ebda18c0ceb48dfc2b Author: Simon Peyton Jones Date: Fri Jun 26 14:28:45 2015 +0100 closeOverKinds *before* oclose in coverage check Combining functional dependencies with kind-polymorphism is devilishly tricky! It's all documented in Note [Closing over kinds in coverage] Fixes Trac #10564 (cherry picked from commit 7c07cf16ab5d5bdfb64efb1d4fc5f20cf7437437) >--------------------------------------------------------------- 29b43fc7714e888ab5a2f5ebda18c0ceb48dfc2b compiler/typecheck/FunDeps.hs | 86 ++++++++++++++++++---- testsuite/tests/typecheck/should_compile/T10564.hs | 20 +++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 3 files changed, 91 insertions(+), 16 deletions(-) diff --git a/compiler/typecheck/FunDeps.hs b/compiler/typecheck/FunDeps.hs index a6e5552..dc2549b 100644 --- a/compiler/typecheck/FunDeps.hs +++ b/compiler/typecheck/FunDeps.hs @@ -399,10 +399,15 @@ checkInstCoverage be_liberal clas theta inst_taus rs_tvs = tyVarsOfTypes rs conservative_ok = rs_tvs `subVarSet` closeOverKinds ls_tvs - liberal_ok = rs_tvs `subVarSet` closeOverKinds (oclose theta ls_tvs) - -- closeOverKinds: see Note [Closing over kinds in coverage] - - msg = vcat [ sep [ ptext (sLit "The") + liberal_ok = rs_tvs `subVarSet` oclose theta (closeOverKinds ls_tvs) + -- closeOverKinds: see Note [Closing over kinds in coverage] + + msg = vcat [ -- text "ls_tvs" <+> ppr ls_tvs + -- , text "closed ls_tvs" <+> ppr (closeOverKinds ls_tvs) + -- , text "theta" <+> ppr theta + -- , text "oclose" <+> ppr (oclose theta (closeOverKinds ls_tvs)) + -- , text "rs_tvs" <+> ppr rs_tvs + sep [ ptext (sLit "The") <+> ppWhen be_liberal (ptext (sLit "liberal")) <+> ptext (sLit "coverage condition fails in class") <+> quotes (ppr clas) @@ -418,22 +423,70 @@ checkInstCoverage be_liberal clas theta inst_taus , ppWhen (not be_liberal && liberal_ok) $ ptext (sLit "Using UndecidableInstances might help") ] -{- -Note [Closing over kinds in coverage] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +{- Note [Closing over kinds in coverage] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Suppose we have a fundep (a::k) -> b Then if 'a' is instantiated to (x y), where x:k2->*, y:k2, then fixing x really fixes k2 as well, and so k2 should be added to the lhs tyvars in the fundep check. Example (Trac #8391), using liberal coverage + data Foo a = ... -- Foo :: forall k. k -> * + class Bar a b | a -> b + instance Bar a (Foo a) + + In the instance decl, (a:k) does fix (Foo k a), but only if we notice + that (a:k) fixes k. Trac #10109 is another example. + +Here is a more subtle example, from HList-0.4.0.0 (Trac #10564) + + class HasFieldM (l :: k) r (v :: Maybe *) + | l r -> v where ... + class HasFieldM1 (b :: Maybe [*]) (l :: k) r v + | b l r -> v where ... + class HMemberM (e1 :: k) (l :: [k]) (r :: Maybe [k]) + | e1 l -> r + + data Label :: k -> * + type family LabelsOf (a :: [*]) :: * + + instance (HMemberM (Label {k} (l::k)) (LabelsOf xs) b, + HasFieldM1 b l (r xs) v) + => HasFieldM l (r xs) v where + +Is the instance OK? Does {l,r,xs} determine v? Well: + + * From the instance constraint HMemberM (Label k l) (LabelsOf xs) b, + plus the fundep "| el l -> r" in class HMameberM, + we get {l,k,xs} -> b + + * Note the 'k'!! We must call closeOverKinds on the seed set + ls_tvs = {l,r,xs}, BEFORE doing oclose, else the {l,k,xs}->b + fundep won't fire. This was the reason for #10564. + + * So starting from seeds {l,r,xs,k} we do oclose to get + first {l,r,xs,k,b}, via the HMemberM constraint, and then + {l,r,xs,k,b,v}, via the HasFieldM1 constraint. + + * And that fixes v. + +However, we must closeOverKinds whenever augmenting the seed set +in oclose! Consider Trac #10109: + + data Succ a -- Succ :: forall k. k -> * + class Add (a :: k1) (b :: k2) (ab :: k3) | a b -> ab + instance (Add a b ab) => Add (Succ {k1} (a :: k1)) + b + (Succ {k3} (ab :: k3}) - type Foo a = a -- Foo :: forall k. k -> k - class Bar a b | a -> b - instance Bar a (Foo a) +We start with seed set {a:k1,b:k2} and closeOverKinds to {a,k1,b,k2}. +Now use the fundep to extend to {a,k1,b,k2,ab}. But we need to +closeOverKinds *again* now to {a,k1,b,k2,ab,k3}, so that we fix all +the variables free in (Succ {k3} ab). -In the instance decl, (a:k) does fix (Foo k a), but only if we notice -that (a:k) fixes k. Trac #10109 is another example. +Bottom line: + * closeOverKinds on initial seeds (in checkInstCoverage) + * and closeOverKinds whenever extending those seeds (in oclose) Note [The liberal coverage condition] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -466,13 +519,14 @@ oclose preds fixed_tvs where new_fixed_tvs = foldl extend fixed_tvs tv_fds extend fixed_tvs (ls,rs) - | ls `subVarSet` fixed_tvs = fixed_tvs `unionVarSet` rs + | ls `subVarSet` fixed_tvs = fixed_tvs `unionVarSet` closeOverKinds rs | otherwise = fixed_tvs + -- closeOverKinds: see Note [Closing over kinds in coverage] tv_fds :: [(TyVarSet,TyVarSet)] - tv_fds = [ (tyVarsOfTypes xs, tyVarsOfTypes ys) - | (xs, ys) <- concatMap determined preds - ] + tv_fds = [ (tyVarsOfTypes ls, tyVarsOfTypes rs) + | pred <- preds + , (ls, rs) <- determined pred ] determined :: PredType -> [([Type],[Type])] determined pred diff --git a/testsuite/tests/typecheck/should_compile/T10564.hs b/testsuite/tests/typecheck/should_compile/T10564.hs new file mode 100644 index 0000000..7b19f00 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T10564.hs @@ -0,0 +1,20 @@ +{-# LANGUAGE FlexibleInstances, FlexibleContexts, UndecidableInstances, + DataKinds, TypeFamilies, KindSignatures, PolyKinds, FunctionalDependencies #-} + +module T10564 where + +class HasFieldM (l :: k) r (v :: Maybe *) + | l r -> v + +class HasFieldM1 (b :: Maybe [*]) (l :: k) r v + | b l r -> v + +class HMemberM (e1 :: k) (l :: [k]) (r :: Maybe [k]) + | e1 l -> r + +data Label a +type family LabelsOf (a :: [*]) :: [*] + +instance (HMemberM (Label (l::k)) (LabelsOf xs) b, + HasFieldM1 b l (r xs) v) + => HasFieldM l (r xs) v where diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index 7bb37b4..bf0e0a0 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -445,3 +445,4 @@ test('T10195', normal, compile, ['']) test('T10109', normal, compile, ['']) test('T10335', normal, compile, ['']) test('T10489', normal, compile, ['']) +test('T10564', normal, compile, ['']) From git at git.haskell.org Sun Jun 28 00:33:47 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 28 Jun 2015 00:33:47 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: relnotes: More 7.10.2 release notes (9ea4ded) Message-ID: <20150628003347.1DF763A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/9ea4ded2ee7822aed05275c390c285f0a60a6ef6/ghc >--------------------------------------------------------------- commit 9ea4ded2ee7822aed05275c390c285f0a60a6ef6 Author: Austin Seipp Date: Sat Jun 27 19:34:17 2015 -0500 relnotes: More 7.10.2 release notes Signed-off-by: Austin Seipp >--------------------------------------------------------------- 9ea4ded2ee7822aed05275c390c285f0a60a6ef6 docs/users_guide/7.10.2-notes.xml | 39 +++++++++++++++++++++++++++++++++++++-- 1 file changed, 37 insertions(+), 2 deletions(-) diff --git a/docs/users_guide/7.10.2-notes.xml b/docs/users_guide/7.10.2-notes.xml index 4289d98..37a498a 100644 --- a/docs/users_guide/7.10.2-notes.xml +++ b/docs/users_guide/7.10.2-notes.xml @@ -47,6 +47,12 @@ + A bug which caused the simplifier to produce code which + segfaulted at runtime has been fixed (issue #10538). + + + + A type-system bug which could allow a user to write unsafeCoerce has been fixed (issue #9858). @@ -112,7 +118,7 @@ - The SMP runtime is now enabled on AArch64 (issue #10525). + The SMP runtime and GHCi are now enabled on AArch64 (issue #10525). @@ -152,6 +158,26 @@ + Support for PowerPC relocations has been added (issue + #10402). + + + + + A lurking bug in the code generator which could cause + incorrect assembly code to be generated due to register + aliasing issues has been fixed (issue #10521). + + + + + A bug in the runtime system which could cause a deadlock + when scheduling garbage collections has been fixed (issue + #10545). + + + + A bug which could cause compiled programs to loop forever when glibc's iconv implementation (gconv) wasn't available has been fixed, so these programs will now terminate with @@ -238,8 +264,17 @@ + A bug in the simplifier which can cause it to totally + fail to compile certain programs that get 'very large' + at compile time is known (issue + #10527). + + + + GHC's LLVM backend does not support LLVM 3.4 (issue #9929) + url="https://ghc.haskell.org/trac/ghc/ticket/9929">issue #9929). From git at git.haskell.org Sun Jun 28 16:31:33 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 28 Jun 2015 16:31:33 +0000 (UTC) Subject: [commit: ghc] master: Add -fcross-module-specialise flag (89834d6) Message-ID: <20150628163133.39A1E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/89834d6d99da564aa14e63f2f801f50a615ce322/ghc >--------------------------------------------------------------- commit 89834d6d99da564aa14e63f2f801f50a615ce322 Author: Ben Gamari Date: Sun Jun 28 18:26:42 2015 +0200 Add -fcross-module-specialise flag Summary: As of 7.10.1 we specialize INLINEABLE identifiers defined in other modules. This can expose issues (compiler bugs or otherwise) in some cases (e.g. Trac #10491) and therefore we now provide a way for the user to disable this optimization. Test Plan: Successfully compile Splice.hs from Trac #10491. Reviewers: simonpj, austin Reviewed By: simonpj Subscribers: simonpj, thomie, bgamari Differential Revision: https://phabricator.haskell.org/D999 GHC Trac Issues: #10491 >--------------------------------------------------------------- 89834d6d99da564aa14e63f2f801f50a615ce322 compiler/main/DynFlags.hs | 3 ++ compiler/specialise/Specialise.hs | 64 +++++++++++++++++++++++++++++++++------ docs/users_guide/flags.xml | 7 +++++ docs/users_guide/using.xml | 23 +++++++++++--- 4 files changed, 83 insertions(+), 14 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 89834d6d99da564aa14e63f2f801f50a615ce322 From git at git.haskell.org Sun Jun 28 16:31:36 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 28 Jun 2015 16:31:36 +0000 (UTC) Subject: [commit: ghc] master: Add -fcross-module-specialise flag (302d937) Message-ID: <20150628163136.1F4073A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/302d937782ccb3068244e948d49daff3435e05c0/ghc >--------------------------------------------------------------- commit 302d937782ccb3068244e948d49daff3435e05c0 Merge: 8d221bb 89834d6 Author: Ben Gamari Date: Sun Jun 28 18:32:07 2015 +0200 Add -fcross-module-specialise flag Summary: As of 7.10.1 we specialize INLINEABLE identifiers defined in other modules. This can expose issues (compiler bugs or otherwise) in some cases (e.g. Trac #10491) and therefore we now provide a way for the user to disable this optimization. Test Plan: Successfully compile Splice.hs from Trac #10491. Reviewers: simonpj, austin Reviewed By: simonpj Subscribers: simonpj, thomie, bgamari Differential Revision: https://phabricator.haskell.org/D999 GHC Trac Issues: #10491 >--------------------------------------------------------------- 302d937782ccb3068244e948d49daff3435e05c0 compiler/main/DynFlags.hs | 3 ++ compiler/specialise/Specialise.hs | 64 +++++++++++++++++++++++++++++++++------ docs/users_guide/flags.xml | 7 +++++ docs/users_guide/using.xml | 23 +++++++++++--- 4 files changed, 83 insertions(+), 14 deletions(-) From git at git.haskell.org Mon Jun 29 08:30:14 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 29 Jun 2015 08:30:14 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: Implement part 1 of OverloadedRecordFields (7f15a07) Message-ID: <20150629083014.5EC323A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/7f15a072e8d127fc3e497780d971b3cd1a2a0423/ghc >--------------------------------------------------------------- commit 7f15a072e8d127fc3e497780d971b3cd1a2a0423 Author: Adam Gundry Date: Fri Mar 27 15:40:50 2015 +0000 Implement part 1 of OverloadedRecordFields Summary: This implements the most recent variant of the OverloadedRecordFields extension, as described at https://ghc.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields/Redesign and with notes on the implementation at https://ghc.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields/Implementation This includes fairly wide-ranging changes in order to allow multiple records within the same module to use the same field names. Note that it does *not* allow record selectors to be used if they are ambiguous; subsequent parts will make this possible using orthogonal extensions, as described on the wiki pages. It is being pushed for review first because it touches the most parts of the codebase, and requires changes to several GHC API datatypes in order to distinguish between field labels (which may be overloaded) and selector function names (which are always unique). Haddock has been adapted to compile with the GHC API changes, but it will need further work to properly support modules that use the OverloadedRecordFields extension. Test Plan: New tests added in testsuite/tests/overloadedrecflds; these will be extended once the other parts are implemented. Reviewers: austin, simonpj, goldfire Subscribers: thomie, goldfire Differential Revision: https://phabricator.haskell.org/D761 >--------------------------------------------------------------- 7f15a072e8d127fc3e497780d971b3cd1a2a0423 utils/haddock | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/haddock b/utils/haddock index f9ae6aa..d137dae 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit f9ae6aaf269474228f368380966fc80b73587832 +Subproject commit d137dae000575e46a2144892329df1dfb5a28980 From git at git.haskell.org Mon Jun 29 08:30:17 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 29 Jun 2015 08:30:17 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: Merge remote-tracking branch 'origin/master' into wip/orf-reboot (f61ec3c) Message-ID: <20150629083017.A41CF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/f61ec3c82e265858ea0fe3fcdbd4dea07dec6061/ghc >--------------------------------------------------------------- commit f61ec3c82e265858ea0fe3fcdbd4dea07dec6061 Merge: 7f15a07 0a086c8 Author: Adam Gundry Date: Mon Jun 15 17:02:20 2015 +0100 Merge remote-tracking branch 'origin/master' into wip/orf-reboot Conflicts: compiler/basicTypes/DataCon.hs-boot compiler/basicTypes/RdrName.hs compiler/hsSyn/HsTypes.hs compiler/iface/MkIface.hs compiler/parser/RdrHsSyn.hs compiler/rename/RnEnv.hs compiler/rename/RnNames.hs compiler/rename/RnPat.hs compiler/rename/RnTypes.hs compiler/typecheck/TcRnMonad.hs compiler/typecheck/TcRnTypes.hs compiler/types/TyCon.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 f61ec3c82e265858ea0fe3fcdbd4dea07dec6061 From git at git.haskell.org Mon Jun 29 08:30:20 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 29 Jun 2015 08:30:20 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: Fix reporting of unused overloaded record fields (2c99538) Message-ID: <20150629083020.572603A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/2c99538438a3eef027822e2fa3bf6f30303ad50f/ghc >--------------------------------------------------------------- commit 2c99538438a3eef027822e2fa3bf6f30303ad50f Author: Adam Gundry Date: Thu Jun 18 20:29:43 2015 +0100 Fix reporting of unused overloaded record fields >--------------------------------------------------------------- 2c99538438a3eef027822e2fa3bf6f30303ad50f compiler/rename/RnEnv.hs | 50 ++++++++++++++++++++++++++++------------------ compiler/rename/RnNames.hs | 8 +------- 2 files changed, 32 insertions(+), 26 deletions(-) diff --git a/compiler/rename/RnEnv.hs b/compiler/rename/RnEnv.hs index 9e534ca..b304a08 100644 --- a/compiler/rename/RnEnv.hs +++ b/compiler/rename/RnEnv.hs @@ -39,6 +39,7 @@ module RnEnv ( addFvRn, mapFvRn, mapMaybeFvRn, mapFvRnCPS, warnUnusedMatches, warnUnusedTopBinds, warnUnusedLocalBinds, + mkFieldEnv, dataTcOccs, kindSigErr, perhapsForallMsg, unknownSubordinateErr, HsDocContext(..), docOfHsDocContext ) where @@ -1842,26 +1843,44 @@ warnUnusedGREs :: [GlobalRdrElt] -> RnM () warnUnusedGREs gres = mapM_ warnUnusedGRE gres warnUnusedLocals :: [Name] -> RnM () -warnUnusedLocals names = mapM_ warnUnusedLocal names +warnUnusedLocals names = do + fld_env <- mkFieldEnv <$> getGlobalRdrEnv + mapM_ (warnUnusedLocal fld_env) names -warnUnusedLocal :: Name -> RnM () -warnUnusedLocal name +warnUnusedLocal :: NameEnv (FieldLabelString, Name) -> Name -> RnM () +warnUnusedLocal fld_env name = when (reportable name) $ - addUnusedWarning name (nameSrcSpan name) + addUnusedWarning occ (nameSrcSpan name) (ptext (sLit "Defined but not used")) + where + occ = case lookupNameEnv fld_env name of + Just (fl, _) -> mkVarOccFS fl + Nothing -> nameOccName name --- AMG TODO: needs adapting to cope with FldParents warnUnusedGRE :: GlobalRdrElt -> RnM () -warnUnusedGRE (GRE { gre_name = name, gre_lcl = lcl, gre_imp = is }) - | lcl = warnUnusedLocal name +warnUnusedGRE gre@(GRE { gre_name = name, gre_lcl = lcl, gre_imp = is }) + | lcl = do fld_env <- mkFieldEnv <$> getGlobalRdrEnv + warnUnusedLocal fld_env name | otherwise = when (reportable name) (mapM_ warn is) where - warn spec = addUnusedWarning name span msg + occ = greOccName gre + warn spec = addUnusedWarning occ span msg where span = importSpecLoc spec pp_mod = quotes (ppr (importSpecModule spec)) msg = ptext (sLit "Imported from") <+> pp_mod <+> ptext (sLit "but not used") +-- | Make a map from selector names to field labels and parent tycon +-- names, to be used when reporting unused record fields. +mkFieldEnv :: GlobalRdrEnv -> NameEnv (FieldLabelString, Name) +mkFieldEnv rdr_env = mkNameEnv [ (gre_name gre, (lbl, par_is par)) + | gres <- occEnvElts rdr_env + , gre <- gres + , isOverloadedRecFldGRE gre + , let par = gre_par gre + Just lbl = par_lbl par + ] + reportable :: Name -> Bool reportable name | isWiredInName name = False -- Don't report unused wired-in names @@ -1869,19 +1888,12 @@ reportable name -- from Data.Tuple | otherwise = not (startsWithUnderscore (nameOccName name)) -addUnusedWarning :: Name -> SrcSpan -> SDoc -> RnM () -addUnusedWarning name span msg +addUnusedWarning :: OccName -> SrcSpan -> SDoc -> RnM () +addUnusedWarning occ span msg = addWarnAt span $ sep [msg <> colon, - nest 2 $ pprNonVarNameSpace (occNameSpace (nameOccName name)) - <+> quotes (ppr name)] - -{- - -- AMG TODO - where - pp_name | isOverloadedRecFldGRE gre = ppr (greOccName gre) - | otherwise = ppr (gre_name gre) --} + nest 2 $ pprNonVarNameSpace (occNameSpace occ) + <+> quotes (ppr occ)] addNameClashErrRn :: RdrName -> [GlobalRdrElt] -> RnM () addNameClashErrRn rdr_name gres diff --git a/compiler/rename/RnNames.hs b/compiler/rename/RnNames.hs index edb871b..976384f 100644 --- a/compiler/rename/RnNames.hs +++ b/compiler/rename/RnNames.hs @@ -1551,17 +1551,11 @@ warnUnusedImportDecls gbl_env -- both for warning about unnecessary ones, and for -- deciding the minimal ones rdr_env = tcg_rdr_env gbl_env + fld_env = mkFieldEnv rdr_env ; let usage :: [ImportDeclUsage] usage = findImportUsage user_imports rdr_env uses sel_uses fld_env - fld_env = mkNameEnv [ (gre_name gre, (lbl, par_is par)) - | gres <- occEnvElts rdr_env - , gre <- gres - , isOverloadedRecFldGRE gre - , let par = gre_par gre - Just lbl = par_lbl par ] - ; traceRn (vcat [ ptext (sLit "Uses:") <+> ppr uses , ptext (sLit "Selector uses:") <+> ppr (nameSetElems sel_uses) , ptext (sLit "Import usage") <+> ppr usage]) From git at git.haskell.org Mon Jun 29 08:30:23 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 29 Jun 2015 08:30:23 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: Merge remote-tracking branch 'origin/master' into wip/orf-reboot (7b8621e) Message-ID: <20150629083023.5090B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/7b8621ec14ac19b32cb85a10112c7c4debf6b557/ghc >--------------------------------------------------------------- commit 7b8621ec14ac19b32cb85a10112c7c4debf6b557 Merge: 2c99538 f2ffdc6 Author: Adam Gundry Date: Sat Jun 20 13:28:37 2015 +0100 Merge remote-tracking branch 'origin/master' into wip/orf-reboot >--------------------------------------------------------------- Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 7b8621ec14ac19b32cb85a10112c7c4debf6b557 From git at git.haskell.org Mon Jun 29 08:30:26 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 29 Jun 2015 08:30:26 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: Remove unnecessary Binary instance, since we don't serialize FieldLbl any more (87b361c) Message-ID: <20150629083026.0B44B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/87b361c8d4e5a29f587795d54ee8013b15738ebe/ghc >--------------------------------------------------------------- commit 87b361c8d4e5a29f587795d54ee8013b15738ebe Author: Adam Gundry Date: Sun Jun 21 16:02:54 2015 +0100 Remove unnecessary Binary instance, since we don't serialize FieldLbl any more >--------------------------------------------------------------- 87b361c8d4e5a29f587795d54ee8013b15738ebe compiler/basicTypes/FieldLabel.hs | 13 ------------- 1 file changed, 13 deletions(-) diff --git a/compiler/basicTypes/FieldLabel.hs b/compiler/basicTypes/FieldLabel.hs index 9af7f88..b22922b 100644 --- a/compiler/basicTypes/FieldLabel.hs +++ b/compiler/basicTypes/FieldLabel.hs @@ -51,7 +51,6 @@ module FieldLabel ( FieldLabelString import OccName import Name -import Binary import FastString import Outputable @@ -81,18 +80,6 @@ data FieldLbl a = FieldLabel { instance Outputable a => Outputable (FieldLbl a) where ppr fl = ppr (flLabel fl) <> braces (ppr (flSelector fl)) -instance Binary a => Binary (FieldLbl a) where - put_ bh (FieldLabel aa ab ac) = do - put_ bh aa - put_ bh ab - put_ bh ac - - get bh = do - aa <- get bh - ab <- get bh - ac <- get bh - return (FieldLabel aa ab ac) - -- | Record selector OccNames are built from the underlying field name and -- the name of the type constructor, to support overloaded record fields. From git at git.haskell.org Mon Jun 29 08:30:28 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 29 Jun 2015 08:30:28 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: Distinguish AllowDuplicateRecordFields from OverloadedRecordFields (b16c3ae) Message-ID: <20150629083028.C2CDC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/b16c3aef1be5e1e383c596ea95d6233244ffccad/ghc >--------------------------------------------------------------- commit b16c3aef1be5e1e383c596ea95d6233244ffccad Author: Adam Gundry Date: Sun Jun 21 16:50:37 2015 +0100 Distinguish AllowDuplicateRecordFields from OverloadedRecordFields >--------------------------------------------------------------- b16c3aef1be5e1e383c596ea95d6233244ffccad compiler/basicTypes/Avail.hs | 6 +++--- compiler/basicTypes/FieldLabel.hs | 6 +++--- compiler/basicTypes/RdrName.hs | 4 ++-- compiler/hsSyn/HsImpExp.hs | 4 ++-- compiler/hsSyn/HsPat.hs | 2 +- compiler/hsSyn/HsTypes.hs | 4 ++-- compiler/iface/IfaceSyn.hs | 4 ++-- compiler/main/DynFlags.hs | 5 ++++- compiler/rename/RnNames.hs | 8 ++++---- compiler/rename/RnPat.hs | 2 +- compiler/typecheck/TcExpr.hs | 4 ++-- .../tests/overloadedrecflds/ghci/overloadedrecfldsghci01.script | 4 ++-- .../overloadedrecflds/should_fail/OverloadedRecFldsFail04_A.hs | 2 +- .../overloadedrecflds/should_fail/OverloadedRecFldsFail06_A.hs | 2 +- .../overloadedrecflds/should_fail/overloadedrecfldsfail01.hs | 2 +- .../overloadedrecflds/should_fail/overloadedrecfldsfail02.hs | 2 +- .../overloadedrecflds/should_fail/overloadedrecfldsfail03.hs | 2 +- .../overloadedrecflds/should_fail/overloadedrecfldsfail04.hs | 2 +- .../overloadedrecflds/should_fail/overloadedrecfldsfail05.hs | 2 +- .../overloadedrecflds/should_fail/overloadedrecfldsfail06.hs | 4 ++-- .../overloadedrecflds/should_fail/overloadedrecfldsfail07.hs | 2 +- .../overloadedrecflds/should_run/OverloadedRecFldsRun02_A.hs | 2 +- .../tests/overloadedrecflds/should_run/overloadedrecfldsrun01.hs | 4 ++-- .../tests/overloadedrecflds/should_run/overloadedrecfldsrun02.hs | 2 +- .../tests/overloadedrecflds/should_run/overloadedrecfldsrun03.hs | 4 ++-- .../tests/overloadedrecflds/should_run/overloadedrecfldsrun04.hs | 4 ++-- 26 files changed, 46 insertions(+), 43 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b16c3aef1be5e1e383c596ea95d6233244ffccad From git at git.haskell.org Mon Jun 29 08:30:31 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 29 Jun 2015 08:30:31 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: Get rid of dead code (f8581f1) Message-ID: <20150629083031.7E1173A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/f8581f11af3b7707f9a81758d33fda56b167e833/ghc >--------------------------------------------------------------- commit f8581f11af3b7707f9a81758d33fda56b167e833 Author: Adam Gundry Date: Sun Jun 21 16:13:29 2015 +0100 Get rid of dead code >--------------------------------------------------------------- f8581f11af3b7707f9a81758d33fda56b167e833 compiler/typecheck/TcEnv.hs | 15 ++------------- 1 file changed, 2 insertions(+), 13 deletions(-) diff --git a/compiler/typecheck/TcEnv.hs b/compiler/typecheck/TcEnv.hs index cd4efca..901488d 100644 --- a/compiler/typecheck/TcEnv.hs +++ b/compiler/typecheck/TcEnv.hs @@ -54,8 +54,8 @@ module TcEnv( -- New Ids newLocalName, newDFunName, newDFunName', - newFamInstTyConName, newFamInstTyConName', - newFamInstAxiomName, newFamInstAxiomName', + newFamInstTyConName, + newFamInstAxiomName, mkStableIdFromString, mkStableIdFromName, mkWrapperName ) where @@ -733,21 +733,10 @@ newGlobalBinder. newFamInstTyConName :: Located Name -> [Type] -> TcM Name newFamInstTyConName (L loc name) tys = mk_fam_inst_name id loc name [tys] -newFamInstTyConName' :: Located Name -> [LHsType RdrName] -> TcM Name -newFamInstTyConName' (L loc name) tys - = mk_fam_inst_name' id loc info_string - where - info_string = occNameString (getOccName name) - ++ concatMap (getDFunHsTypeKey . unLoc) tys - newFamInstAxiomName :: SrcSpan -> Name -> [CoAxBranch] -> TcM Name newFamInstAxiomName loc name branches = mk_fam_inst_name mkInstTyCoOcc loc name (map coAxBranchLHS branches) -newFamInstAxiomName' :: SrcSpan -> String -> TcM Name -newFamInstAxiomName' loc info_string - = mk_fam_inst_name' mkInstTyCoOcc loc info_string - mk_fam_inst_name :: (OccName -> OccName) -> SrcSpan -> Name -> [[Type]] -> TcM Name mk_fam_inst_name adaptOcc loc tc_name tyss = mk_fam_inst_name' adaptOcc loc info_string From git at git.haskell.org Mon Jun 29 08:30:34 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 29 Jun 2015 08:30:34 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot: Remove unused test file (97fd90b) Message-ID: <20150629083034.4B2E03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/orf-reboot Link : http://ghc.haskell.org/trac/ghc/changeset/97fd90bea5107ddbdc72b8ed03a71decd14b8fd4/ghc >--------------------------------------------------------------- commit 97fd90bea5107ddbdc72b8ed03a71decd14b8fd4 Author: Adam Gundry Date: Sun Jun 21 16:54:21 2015 +0100 Remove unused test file >--------------------------------------------------------------- 97fd90bea5107ddbdc72b8ed03a71decd14b8fd4 .../should_fail/OverloadedRecFldsFail08_A.hs | 14 -------------- 1 file changed, 14 deletions(-) diff --git a/testsuite/tests/overloadedrecflds/should_fail/OverloadedRecFldsFail08_A.hs b/testsuite/tests/overloadedrecflds/should_fail/OverloadedRecFldsFail08_A.hs deleted file mode 100644 index aa830cc..0000000 --- a/testsuite/tests/overloadedrecflds/should_fail/OverloadedRecFldsFail08_A.hs +++ /dev/null @@ -1,14 +0,0 @@ -{-# LANGUAGE OverloadedRecordFields, ExistentialQuantification, RankNTypes, TypeFamilies #-} - -module OverloadedRecFldsFail08_A where - --- x is existential (naughty) -data T = forall e . MkT { x :: e } - --- y and z are higher-rank -data U = MkU { y :: forall a . a -> a } - | MkU2 { z :: (forall b . b) -> () } - -data family F a -data instance F Int = forall e . MkFInt { foo :: e } -data instance F Bool = MkFBool { foo :: forall a . a -> a } From git at git.haskell.org Mon Jun 29 08:30:38 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 29 Jun 2015 08:30:38 +0000 (UTC) Subject: [commit: ghc] wip/orf-reboot's head updated: Remove unused test file (97fd90b) Message-ID: <20150629083038.F09363A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/orf-reboot' now includes: 90dd11b Remove some unimplemented GranSim primops af45feb Update list of primops that don't get wrappers (#10191) 7f15a07 Implement part 1 of OverloadedRecordFields abde5da Rename driver phases C(obj)cpp to C(obj)cplusplus e2f1ffc Rename C(obj)cplusplus to C(obj)cxx a4656eb Doc typofix. e24f638 Renames some files to help with validation cleanup (#10212) de1160b Refactor the story around switches (#10137) c37ee4a Remove an unused include that doesn't exist on OS X (#10211) b1d6a60 Delete unused field `PipeEnv.pe_isHaskellishFile` 5971ad5 Syntax check package-qualified imports (#9225) 1f69f37 Add `integer-gmp` specific hint to build.mk.sample 995e8c1 Drop old integer-gmp-0.5 from GHC source tree a3d0a7a Testsuite: suppress errors when running GS on bad.ps 9e073ce Explicitly check for -C on registerised build (#7563) 6981862 Don't throw exception when start_phase==stop_phase (#10219) da17f99 Don't treat .hcr and .raw_s as haskellish suffixes 8757e2d Testsuite: redirect stderr to /dev/null when running GS on bad.ps 694c4d5 uBackpack: simplified Backpack description. d4cf705 Don't `make accept` output of expect_broken tests 7cec6c7 Change which files --make thinks are 'Haskellish' (#10220) 3749c05 Reformat build flavours in build.mk.sample (#10223) 43351ff Filter out `-Rghc-timing` for V=0 builds (#10223) f15dbc2 Indentation only. 0721e55 Fake (->) fixity declaration (#10145) 9b66a7f Do not set -fasm explicitly in build.mk.sample (#10223) 4c1e1c8 Disable same warnings for normal builds as for validate (#10223) afcfb62 Change 'Tab character' warnings so there is one per file (#9723) 47f821a libffi: backport noexecstack fix for x86/win32.S 48977c8 Fix validate linenumber off-by-one 13a0d5a clarify --no-as-needed is only needed on ELF 78c79e3 docs: remove unused -ddump flags from users guide 59f7a7b Restore unwind information generation 012ea0b parser: allow type-level cons in prefix position 3541f73 Data.Complex: Derive Generic 2255c76 Remove an incorrect statement about -fwarn-tabs fd1099c Don't `make accept` output of `expect_broken_for` tests ab0743f Comments only, mostly typos a0c1c96 testsuite: fix failing amd64/Windows perf tests 54b7dc5 rts/linker: make an error msg a debug msg b0ba054 testsuite: skip T10017 on Windows 89eef44 Whitespace only a1404e8 Update hsc2hs submodule a838d1f CmmSwitch: Do not trip over a case with no (valid) branches 8f07092 Test case for #10246 fef4948 User's guide: .a files can be 2-2.5x larger with -split-objs c81e070 Stop profiling output from running together (#8811) 22eecaf fix '&stg_interp_constr_entry' FFI type to be FunPtr 7209290 fix typo a7ab161 Replace hooks by callbacks in RtsConfig (#8785) 890461e Add +RTS -O to control the minimum old gen size 93f3a64 Add -n to the RTS help output f745b6e Typechecker: refactoring only 0622970 testdriver: delete unused ways b972de0 Suggest how to fix .ghci when it is group writeable (#8248) 9f0f99f Fix a long-standing bug in the demand analyser 547c597 Reduce module qualifiers in pretty-printing c897613 Error msg wibbles from reduced module prefixes 74d2c33 GHC.Prim.Constraint is not built-in syntax cfb6042 Do not quantify over the function itself in a RULE 6ca7b84 Put quotes round a Name in an error message 8b7ceec More aggressive Given/Wanted overlap check 553c518 Look inside synonyms for foralls when unifying 4f8e348 Replace endian test by 64-bit word access in T7600 ab76b09 rts/Linker.c: distinct between DATA and CODE labels when importing cf1d975 Don't repeat package key with -dppr-debug when package info is missing. f1a4e42 The production for `pquals` is incorrect; the specifics are in D803. cf19640 The production for squals is incorrect; see D806 for specifics. eacda92 Test Trac #10148 e6e0415 More error message wibbles a058ad6 Final error message wibble a7524ea Support for multiple signature files in scope. 9e7802f Commit missing T10148 files and ignore the built executable. 1d5c887 Axe one-shot sig-of 3c6448c Ignore temporary ./configure files. 53cc9af Test Trac #8030 6b96eeb Fixes a compiler error with -DDEBUG (#10265) f536d89 Import rand using capi 2d68aa6 Comments about AnyK d9b0be3 Comments in rejigConRes 702fc77 Comments only fa46c59 Make the evidence in a CtGiven into an EvId 9d16808 Typos in error messages and in comments 485dba8 configure : LLVM and LD detections improvements (#10234). edc059a Fix autoconf's check for create_timer() a5745d2 Derive Generic instance for System.Exit.ExitCode c327393 Derive Generic instance for Data.Version.Version 6109b31 use projectVersion from DynFlags rather than cProjectVersion for versionedAppDir 8aefc9b parser: opt_kind_sig has incorrect SrcSpan 9eab6fe parser: API Annotations : guardquals1 does not annotate commas properly 919b511 parser : the API annotation on opt_sig is being discarded d261d4c Zap usage info in CSE (Trac #10218) 25f2d68 Comments only a2ce3af Comments and white space only 7febc2b Add "error:" prefix to error-messages 79bfe27 Remove LlvmCodeGen panic variants. 8dc2944 API Annotations : ExprWithTySig processing discards annotated spans 5fded20 ApiAnnotations : lexer discards comment close in nested comment 6dd2765 Implement -f[no-]print-unicode-syntax flag for unicode syntax output (#8959) 7b042d5 Do not allow Typeable on constraints (Trac #9858) 49d9b00 Fix fundep coverage-condition check for poly-kinds a9ca67f Improve Call Arity performance 9654a7c Call Arity: Trade precision for performance in large mutually recursive groups 1fb4dd3 Add exception for `KnownNat` and `KnownSymbol` in super classes. d8d541d Fixes (hopefully!) T9858 e68e8ca Fix test output. ea579d9 Fix test output 3b90d8c Rename tests so that they have a unique name. 51af102 Better hints when RTS options not available (Trac #9579) 2483644 Documentation for rnImports/rnImportDecl. 2b3766b Comments only. ad6d6a7 Stub out pkgState with non-error, helps with debugging. 619a324 Make T9579 parallel-safe and add build outputs to .gitignore 88b8406 Test case for indirect dependencies in ghci linker (#10322) 4bc925a Update Cabal submodule to 1.22.3.0 release d5773a4 Teach DmdAnal that coercions are value arguments! 3bec1ac Teach DmdAnal about free coercion variables d12c7cb Spelling in comment f2d1b7f Support unboxing for GADT product types 5c7e4db Wibble to DmdAnal b9f20bd GADTs now are CPR-able 1e8c9b8 Enable SMP and GHCi support for Aarch64 0bbc2ac Use the gold linker for aarch64/linux (#9673) 3b932cc Add a blank line 9b9fc4c Fix the boot dfun impedence-matching binding c0b5adb Do not decompose => (Trac #9858) 1bb1ff2 Mark T8743 as passing 1bd1cef Don't use self {-# SOURCE #-} import in test-cases. a2f9fef Fix #10182 by disallowing/avoiding self {-# SOURCE #-} imports 646866f Fix superclass generation in an instance 9d3bd3d Comments only c715166 Improve error reporting for impredicative types 746f086 Better documetation of higher rank types 932f086 Test Trac #9858 comment:101 43d7137 Rename new T9858c to T9858d to avoid test name clash a55bfab Rename new T9858d to T9858e to avoid test name clash 524ddbd Make sure GHC.List.last is memory-efficient 6ab5da9 Rename role annotations w.r.t only local decls. a8d39a7 Fix #10285 by refusing to use NthCo on a newtype. 414e20b Fix the formal operational semantics (#10121) d4cf559 Test #10321 in ghci/scripts/T10321 dc587fe Test case for #10141 72a9272 Change default roles in hs-boot files. (#9204) bbabb71 Updates to Backpack documentation based on recent visit to MSRC. c4e8097 Bump base version to 4.8.2.0 75adc35 Add missing since-annotations for c024af131b9e2538 9a0c179 base: Export GHC.Event(.Internal).Lifetime 5f127fc Flesh out some more Backpack examples in the merging section. d0898ca Backpack docs: explain alternate merging scheme. 541aa7f Full type checking Backpack details. 21a37ca Backpack docs: merge backpack-shaping into algorithm, sigs no longer provide b61562f Seed SpecConstr from local calls 168c883 A little outright bug in canEqTyVar2 d9bb0ee Don't print evidence in TcFlatten a1275a7 Improve improvement in the constraint solver d4a926b Test Trac #10226 54cefbd Typeset Backpack syntax in a figure b83160d Tidy up treatment of FlexibleContexts a3f7517 Typo fixes (mostly in comments) fe5ccbb Typeset Backpack semantic entities in figure, figure-ify all asides. bbfa0ca Comments only f6ab0f2 Refactor TyCon to eliminate TupleTyCon 0d715db Update haddock submodule to track TyCon change b626cb0 Make Derived NomEq rewrite only Derived NomEq de5d022 Kill off the default types in ghc-prim 2f6a0ac Move IP, Symbol, Nat to ghc-prim 4efa421 Permit empty closed type families 63a10bb arm: Force non-executable stack (#10369) f7dfcef Fix safeHaskell test for llvm backend bf4f3e6 Give a hint when a TH splice has a bad package key, partially fixes #10279 cdba973 Documentation for Language.Haskell.TH.Quote. 1a4374c arm: Force non-executable stack (part 2) 341a766 Doc: checkCrossStageLifting, RnSplice/TcExpr is untyped/typed brackets (#10384) f7daf5a Normalise type families in the type of an expression 458a97b Fix typo: identifer -> identifier 03c4893 Retain ic_monad and ic_int_print from external packages after load 477f514 rts: add "-no-rtsopts-suggestions" option fa0474d base: Fix confusing docs typo fb54b2c API Annotations : add Locations in hsSyn were layout occurs caeae1a Correct parsing of lifted empty list constructor 15aafc7 ApiAnnotations : quoted type variables missing leading quote 81030ed ApiAnnotations : Nested forall loses forall annotation f34c072 Revert "ApiAnnotations : Nested forall loses forall annotation" 97d320f Revert "API Annotations : add Locations in hsSyn were layout occurs" d1295da Comments only 931d014 A bit of refactoring RnSplice c3e6b3a Regression test for Trac #10390 5bde9f7 ApiAnnotations : RdrHsSyn.isFunLhs discards parentheses cc9b788 Backpack docs: meditate on AvailTC with four examples. 225df19 ApiAnnotations : AnnComma missing in TupleSection 7136126 ApiAnnotations: misplaced AnnComma for squals production 2601a43 Backpack docs: AvailInfo plan, and why selectors are hard. 28257ca Support stage 1 Template Haskell (non-quasi) quotes, fixes #10382. 21c72e7 Split off quotes/ from th/ for tests that can be done on stage1 compiler. eb0ed40 RnSplice's staging test should be applied for quotes in stage1. 9a43b2c Always do polymorphic typed quote check, c.f. #10384 3c70ae0 Quick fix: drop base bound on template-haskell. 5c459ee Revert stage 1 template-haskell. This is a combination of 5 commits. 811b72a Api Annotations: RdrHsSyn.mkAtDefault causes annotations to be disconnected. e4032b1 ApiAnnotations : mkGadtDecl discards annotations for HsFunTy 27aa733 IdInfo comment update 2666ba3 haddock: update submodule to fix #10206 cf7573b More accurate allocation stats for :set +s 9736c04 compiler: make sure we reject -O + HscInterpreted 24707d7 ApiAnnotations : BooleanFormula construction discards original f35d621 Fix build breakage from 9736c042 fe38195 ApiAnnotations : pquals production adds AnnVbar in the wrong place ecc3d6b ApiAnnotations : PatBind gives wrong SrcSpan for the pattern. f16ddce Support stage 1 Template Haskell (non-quasi) quotes, fixes #10382. b0784cc Backpack docs: more carefully describe unification versus unioning. b4f6c16 Ignore out and toc files. 53409a7 Backpack docs: proper discourse on ModIface and ModDetails. eecef17 Fix safe haskell bug: instances in safe-inferred 4fffbc3 New handling of overlapping inst in Safe Haskell ef7ed16 Make template-haskell build with GHC 7.6, fixes bootstrap build. c119a80 Use fmap instead of <$> (Fixes #10407) ca7c855 We need an empty boolFormula.stderr f5188f3 Fix weird behavior of -ignore-dot-ghci and -ghci-scipt 6ee4b6f Turn off warnings when compiling boolFormula 1b47692 Backpack docs: Consistently italicize metavariables. 4432863 Update some tests for recent Safe Haskell change. a171cc1 Update Safe Haskell documentation. 4b8b4ce Fix fragile T9579 tests 8764a7e Revert D727 8da785d Delete commented-out line 130e93a Refactor tuple constraints 5910a1b Change in capitalisation of error msg a154944 Two wibbles to fix the build a8493e0 Fix imports in HscMain (stage2) 6e1174d Separate transCloVarSet from fixVarSet 51cbad1 Update haddock submodule ca173aa Add a case to checkValidTyCon eb6ca85 Make the "matchable-given" check happen first c0aae6f Test Trac #10248 a9ccd37 Test Trac #10403 04a484e Test Trac #10359 3cf8ecd Revert multiple commits 3ef7fce Do not check dir perms when .ghci doesn't exist 5972037 Backpack docs: Rewrite type checking section to have a more concrete plan. ab45de1 Failing test for #10420 using plugins. c256357 Speed up elimCommonBlocks by grouping blocks also by outgoing labels 8e4dc8f Greatly speed up nativeCodeGen/seqBlocks 73f836f CmmCommonBlockElim: Improve hash function 3f42de5 Test Trac #10359 f1f265d Test Trac #10403 fa0bdd3 Test Trac #10248 76024fd Delete commented-out line ffc2150 Refactor tuple constraints 228ddb9 Make the "matchable-given" check happen first eaaa38b includes/stg/SMP.h: implement simple load_/store_load_barrier on armv6 and older 85bf9e4 Add regression test for #10110. 5cbac88 user guide: correct documentation for -Wall (fixes #10386) 578d2ba Remove unneeded compatibility with LLVM < 3.6 b03f074 ghci: Allow :back and :forward to take counts b0b11ad In ghci linker, link against all previous temp sos (#10322) b199536 compiler: make sure we reject -O + HscInterpreted 470a949 Revert "In ghci linker, link against all previous temp sos (#10322)" 753b156 Add a TODO FIXME w.r.t. D894 fc8c5e7 Test Trac #8799, #8555 edb8dc5 Revert "compiler: make sure we reject -O + HscInterpreted" (again) 25d1a71 Fix error messages from open(Binary)TempFileWithDefaultPermissions c934914 Backpack docs: Clarifications from today's Skype call. 9f968e9 Fix binary instance for IfaceLitTy c553e98 ApiAnnotations : AST version of nested forall loses forall annotation 0df14b5 ApiAnnotations : parens around a context with wildcard loses annotations c488da8 ApiAnnotatons : AnnDcolon in wrong place for PatBind 369dd0c White space layout only eae703a Reduce magic for seqId c89bd68 Fix quadratic behaviour in tidyOccName 45d9a15 Fix a huge space leak in the mighty Simplifier 7d519da testsuite: commit missing T4945 stdout 4d6c0ee compiler: kill a stray pprTrace in OccName 6694ccf testsuite: handle missing stats files gracefully (#10305) c00f051 Update .mailmap c04571d rts: Fix typo in comment 326989e Add missing name for FFI import (fixes #9950) 70f1ca4 Fix ghci-way tests of -XStaticPointers. 71d1f01 Omit the static form error for variables not in scope. 388448b Build system: don't install haddock .t files (#10410) c591147 ApiAnnotations tweaks ef90466 Testdriver: don't use os.popen in config/ghc ce166a3 Testdriver: do not interfer with MinGW path magic (#10449) 640fe14 Remove unnecessary loadInterface for TH quoted name. e28462d base: fix #10298 & #7695 b0d8ba3 Add liftData function. a138fa1 Testsuite: accept new output for T2507 and T8959a 5ead7d1 Build system: make more targets PHONY 4c7d177 Build system: remove toplevel target `fast` a065a3a Build system: use `mkdir -p` instead of `-mkdir` 51aacde Build system: allow missing config.mk for target clean_% 4de8028 Build system: check $CLEANING instead of $MAKECMDGOALS 47e00ec Build system: don't set CLEANING=NO b0885e4 Build system: whitespace and comments only cd0e2f5 Build system: prevent "--version: Command not found" 0bfd05e Build system: prevent "./Setup: Command not found" a49070e Build system: time's config files have moved 48ed2f1 Build system: always allow me to clean haddock 577d315 Build system: always use `make -r` 0d20d76 Build system: make clean in utils/ghc-pkg should not delete inplace/lib/bin 0a159e3 Build system: don't use supposedly local variable inside macro 018fec0 Build system: also clean the inplace wrapper 508a3a3 Build system: don't build runghc if GhcWithInterpreter=NO (#10261) 7db2dec linker_unload working on Windows, fixes #8292. 5a65da4 Don't run T9330fail on Windows, no clobber occurs. #9930 94fff17 Travis: use validate --quiet to prevent hitting log file limits 4756438 Catch canonicalizePath exceptions, fix #10101 a52f144 In ghci linker, link against all previous temp sos (#10322) f5b43ce compiler/specialise: shut match_co up a bit f6ca695 rts: Fix aarch64 implementation of xchg e00910b ApiAnnotations : rationalise tests 7dd0ea7 Update binary submodule to 0.7.5.0 release e6191d1 ApiAnnotations : strings in warnings do not return SourceText e8a7254 Add constraint creation functions to TcPluginM API 1c38325 Fix dropped event registrations 928f536 Use seq rather than (==) to force the size 5eee6a1 Move seqExpr, seqIdInfo etc to CoreUtils 20d8621 Add some missing seqs to Coercion.seqCo d245787 Use named fields in SimplCont.Select constructor 403cfc9 Comments only 931268a Replace tabs with spaces. 98b0b2e Add information about allowed foreign prim args, see #10460. e5be846 Typofix: missing period. (#10460) a27fb46 Add (failing) test case for #7672. f82e866 Newline after type of allocate(). dfdc50d Don't call DEAD_WEAK finalizer again on shutdown (#7170) 34dcf8a Re-center perf numbers for T5631 2f0011a White space only 11d8f84 Treat pattern-synonym binders more consistently 9b73cb1 Refactor the GlobalRdrEnv, fixing #7672 90fde52 Mark sigof02 tests as expect_broken 1189196 Re-do superclass solving (again); fixes #10423 b095c97 Improve constraint tuples (Trac #10451) dbcdfe2 Set 32-bit perf figure d6c01fa Remove redundant import b1b2b44 Test Trac #10423 8a38348 Test Trac #10451 8e5f8cf Test Trac #10466 b2b69b2 Test Trac #10438 091944e compiler: make sure we reject -O + HscInterpreted e796026 build: make haddock a bit less chatty 3758050 Improve FFI error reporting 5688053 Detabify a programlisting in the User's Guide (#10425) 942a074 testsuite: mark test T9938 (#9938) as passing again 7a82b77 newTempName: Do not include pid in basename 2c4c627 Typofixes 6adfb88 Suggest -H to improve GC productivity, fixes #10474. 7b6800c Remove outdated uBackpack docs. 7ea156a Refactor RdrName.Provenance, to fix #7672 cd9c5c6 Allow Any return in foreign prim, fixes #10460. 08558a3 Move liftData and use it as a default definition for Lift. 942cfa4 typo: 'Ture' / 'True' 21d7c85 Travis: Send notifications to author and commiter c69b69d ghc-pkg support query by package-key, fixes #9507 d8f66f1 Re-center perf numbers for haddock.compiler 75c6e06 Build: make configure and ghc-pkg a bit less chatty 14652b5 ghc-cabal: don't warn about missing cabal fields 092082e Build: ./boot && ./configure && make sdist (#8723) cac68d0 Build: remove unnecessary CLEANING/=YES check 5dd0286 Build: remove more unnecessary CLEANING/=YES checks d0063e8 Make validate more quiet e340f6e Testsuite: add/fix cleanup for certain tests 07feab1 Testsuite: ignore `stdcall attribute ignored` (#1288) 0686d76 Testsuite: don't show compile/link info for some tests 7beb477 Travis: allow user forks 761fb7c Fix #10488 by unwrapping type synonyms. 53c1374 Minor code cleanup 61b96a8 Fix #10489 dcaaa98 docs: Fix #10416 ae83a81 Testsuite: only show output diff when test is expected to pass 328c212 Fix the sdist build 89223ce Fix the build when SplitObjs=YES 19ec6a8 Fix for CAF retention when dynamically loading & unloading code 7944a68 Revert "docs: Fix #10416" 058af6c Refactor wild card renaming a48167e build: Clean testsuite before sdist 3b55659 Always force the exception in enqueued commands bb99671 Revert "The test runner now also works under the msys-native Python." 43ebe24 Testsuite: delete expect_fail setups for hugs 3445947 Testsuite: delete expect_fail setups for ghc < 7.1 4a0b7a1 Build: run autoreconf jobs in parallel 5828457 make sdist: distclean testsuite for real (#10406) ca39b96 docs: Fix #10416 ddbb97d Another major improvement of "improvement" c0dc79f IndTypesPerfMerge no longer seems to requre -M20M a66ef35 Fix DWARF generation for MinGW (#10468) c1dc421 Update submodule process to master da84fd5 Testsuite Windows: fix T8172 (#8172) a765f72 Testsuite: mark tests as expect_broken on win64 506522c Testsuite: mark T4945 as expect_broken (#4945) 6cefeb3 Testsuite: mention the existence of ticket #10510 5e66a69 Testsuite: change some expect_fail tests to expect_broken a4318c6 Travis: use apt-get -q 0db0ac4 Removes all occurrences of __MINGW32__ (#10485) 23582b0 Add failing test for #9562. 28e04de Remove redundant tcg_visible_orphan_mods, it is recorded in imp_orphs. bac927b Revert "Support for multiple signature files in scope." c60704f Revert "Change loadSrcInterface to return a list of ModIface" ce53138 Delete _MSC_VER when not necessary, fix #10511 016bbfd docs: Fix unicode alternatives table (fixes #10509). 0ef7174 Squash typos in comments c14bd01 Testsuite: fix the little known CHECK_FILES_WRITTEN=1 d20031d Add parseExpr and compileParsedExpr and use them in GHC API and GHCi 892c3e9 Do not copy stack after stack overflow, refix #8435 dd5cac7 Fix typo in `traceShowM` haddock comment (#10392) 0a086c8 Docs: it's `gv --orientation=seascape` nowadays (#10497) b07dccc Docs: `-XTypeOperators` (#10175) e02a4f2 Add versioning section to Backpack docs. 5ddd904 Testsuite: diff non-whitespace normalised output (#10152) 6e542a6 Testsuite: add function compile_timeout_multiplier (#10345) a508455 UNREG: fix pprHexVal to emit zeros (#10518) 1cf7fc0 add type annotations to SrcLoc functions dd3080f Increase constraint tuple limit to 62 (Trac #10451) a607011 Test Trac #10348 77e5ec8 Demonstrate that inferring Typeable for type literals works efa136f Remove derived CFunEqCans after solving givens a3f6239 GHCi: fix scoping for record selectors a6cbf41 Spelling in comments 855f56b Improved peak_megabytes_allocated 2613271 Testsuite: fix framework failure f61ec3c Merge remote-tracking branch 'origin/master' into wip/orf-reboot 89c7168 Fix #10534 df63736 ghc.mk: Update instances of -auto-all 1ff7f09 Lexer: Suggest adding 'let' on unexpected '=' token 0d6c97b Lexer: Suggest adding 'let' on unexpected '=' token a90712b users_guide: Various spelling fixes d46fdf2 users_guide: Various spelling fixes 681973c Encode alignment in MO_Memcpy and friends a0d158f Encode alignment in MO_Memcpy and friends c772f57 Fix #10494 0de0b14 Fix #10495. ace8d4f Fix #10493. 6644039 Test case for #10428. ff82387 Decompose wanted repr. eqs. when no matchable givens. 93f97be (mostly) Comments only f108003 Testsuite wibble around decomposing newtypes. 7eceffb Refactor handling of decomposition. 9b105c6 Reimplement Unify.typesCantMatch in terms of apartness. 298c424 Treat funTyCon like any other TyCon in can_eq_nc. a6b8b9c Fix typo in comment daf1eee Clarify some comments around injectivity. 65d4b89 Add `Monoid` instance for `IO` f063656 Fix ghc-pkg reports cache out date (#10205) 0760b84 Update foreign export docs, fixes #10467 b98ca17 Make enum01/enum02/enum03 tests clang-compatible 023a0ba Care with impossible-cons in combineIdenticalAlts 5879d5a Report arity errors correctly despite kinds f4370c6 Comments only 4a7a6c3 Rename getCtLoc, setCtLoc 02bac02 Remove some horrible munging of origins for Coercible 760b079 A bit more tracing 0899911 Comments plus tiny refactoring ee64369 Refactor filterAlts into two parts 5d98b68 Trac #4945 is working again 72b21c3 Parser: commas_tup_tail duplicate SrcSpan on "Missing" value ba7c8e5 Test Trac #10503 2c99538 Fix reporting of unused overloaded record fields c45f8ce Elaborate test for Trac #10403 40698fe Spelling in comments e283cec testsuite: mark T4945 as expect_broken 440d1bc docs: Unbreak the PS/PDF builds for the User's Guide (#10509) 7d5a845 should_run/allocLimit4: disable ghci way e491803 Amend tcrun024, tcrun025 after Trac #7854 fix 7c2293a Amend tcrun037 after Trac #7854 fix 2c6a041 Fix a couple of tests for GHCi/-O* (Trac #10052) 5cc08eb Recognise 'hardhloat' as a valid vendor in a host tuple f2ffdc6 Updated output for test ghci024 7b8621e Merge remote-tracking branch 'origin/master' into wip/orf-reboot 87b361c Remove unnecessary Binary instance, since we don't serialize FieldLbl any more f8581f1 Get rid of dead code b16c3ae Distinguish AllowDuplicateRecordFields from OverloadedRecordFields 97fd90b Remove unused test file From git at git.haskell.org Mon Jun 29 09:28:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 29 Jun 2015 09:28:44 +0000 (UTC) Subject: [commit: ghc] master: Mask to avoid uncaught ^C exceptions (bb0e462) Message-ID: <20150629092844.096833A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bb0e462b6cff02737d67f496d8172207042c22b5/ghc >--------------------------------------------------------------- commit bb0e462b6cff02737d67f496d8172207042c22b5 Author: Simon Marlow Date: Thu Jun 25 14:21:44 2015 +0100 Mask to avoid uncaught ^C exceptions Summary: It was possible to kill GHCi with a carefully-timed ^C Test Plan: The bug in #10017 exposed this Reviewers: bgamari, austin Reviewed By: austin Subscribers: thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1015 GHC Trac Issues: #10017 >--------------------------------------------------------------- bb0e462b6cff02737d67f496d8172207042c22b5 ghc/InteractiveUI.hs | 21 ++++++++++++++------- 1 file changed, 14 insertions(+), 7 deletions(-) diff --git a/ghc/InteractiveUI.hs b/ghc/InteractiveUI.hs index a0223c1..d392327 100644 --- a/ghc/InteractiveUI.hs +++ b/ghc/InteractiveUI.hs @@ -553,7 +553,10 @@ runGHCi paths maybe_exprs = do -- this used to be topHandlerFastExit, see #2228 runInputTWithPrefs defaultPrefs defaultSettings $ do -- make `ghc -e` exit nonzero on invalid input, see Trac #7962 - runCommands' hdle (Just $ hdle (toException $ ExitFailure 1) >> return ()) (return Nothing) + _ <- runCommands' hdle + (Just $ hdle (toException $ ExitFailure 1) >> return ()) + (return Nothing) + return () -- and finally, exit liftIO $ when (verbosity dflags > 0) $ putStrLn "Leaving GHCi." @@ -712,12 +715,16 @@ installInteractivePrint (Just ipFun) exprmode = do -- | The main read-eval-print loop runCommands :: InputT GHCi (Maybe String) -> InputT GHCi () -runCommands = runCommands' handler Nothing +runCommands gCmd = runCommands' handler Nothing gCmd >> return () runCommands' :: (SomeException -> GHCi Bool) -- ^ Exception handler -> Maybe (GHCi ()) -- ^ Source error handler - -> InputT GHCi (Maybe String) -> InputT GHCi () -runCommands' eh sourceErrorHandler gCmd = do + -> InputT GHCi (Maybe String) + -> InputT GHCi (Maybe Bool) + -- We want to return () here, but have to return (Maybe Bool) + -- because gmask is not polymorphic enough: we want to use + -- unmask at two different types. +runCommands' eh sourceErrorHandler gCmd = gmask $ \unmask -> do b <- ghandle (\e -> case fromException e of Just UserInterrupt -> return $ Just False _ -> case fromException e of @@ -726,12 +733,12 @@ runCommands' eh sourceErrorHandler gCmd = do return Nothing _other -> liftIO (Exception.throwIO e)) - (runOneCommand eh gCmd) + (unmask $ runOneCommand eh gCmd) case b of - Nothing -> return () + Nothing -> return Nothing Just success -> do when (not success) $ maybe (return ()) lift sourceErrorHandler - runCommands' eh sourceErrorHandler gCmd + unmask $ runCommands' eh sourceErrorHandler gCmd -- | Evaluate a single line of user input (either : or Haskell code). -- A result of Nothing means there was no more input to process. From git at git.haskell.org Mon Jun 29 10:26:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 29 Jun 2015 10:26:32 +0000 (UTC) Subject: [commit: ghc] wip/impredicativity: Fix incorrect instantiation of quantifiers in RULES (c54e4d6) Message-ID: <20150629102632.ED2D23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/impredicativity Link : http://ghc.haskell.org/trac/ghc/changeset/c54e4d67729fdcdae595378a8cc06207c1d0c007/ghc >--------------------------------------------------------------- commit c54e4d67729fdcdae595378a8cc06207c1d0c007 Author: Alejandro Serrano Date: Mon Jun 29 12:26:37 2015 +0200 Fix incorrect instantiation of quantifiers in RULES >--------------------------------------------------------------- c54e4d67729fdcdae595378a8cc06207c1d0c007 compiler/typecheck/TcExpr.hs | 4 ++-- compiler/typecheck/TcHsSyn.hs | 12 +++++++----- compiler/typecheck/TcRules.hs | 18 +++++++++--------- 3 files changed, 18 insertions(+), 16 deletions(-) diff --git a/compiler/typecheck/TcExpr.hs b/compiler/typecheck/TcExpr.hs index ea84eec..860d301 100644 --- a/compiler/typecheck/TcExpr.hs +++ b/compiler/typecheck/TcExpr.hs @@ -1050,7 +1050,7 @@ tc_app fun args fun_ty res_ty special -- > f x = S (error x) -- Without it, the `a` coming from `f` cannot be unified with -- the second type variable of `error` - ; case getTyVar_maybe res_ty of + ; case getTyVar_maybe actual_res_ty of { Nothing -> do { ev_res <- addErrCtxtM (funResCtxt True (unLoc fun) actual_res_ty res_ty) $ emitWanted AppOrigin (mkInstanceOfPred actual_res_ty res_ty) @@ -1065,7 +1065,7 @@ tc_app fun args fun_ty res_ty special ; return $ NormalTcAppResult (mkLHsWrapCo co_fun fun1) -- Instantiated function args1 -- Arguments - (mkHsWrapCo co_res) } } } -- Coercion to expected result type + (mkHsWrapCo co_res) } } } -- Coercion to expected result type mk_app_msg :: LHsExpr Name -> SDoc mk_app_msg fun = sep [ ptext (sLit "The function") <+> quotes (ppr fun) diff --git a/compiler/typecheck/TcHsSyn.hs b/compiler/typecheck/TcHsSyn.hs index f9eacf6..8853607 100644 --- a/compiler/typecheck/TcHsSyn.hs +++ b/compiler/typecheck/TcHsSyn.hs @@ -1322,7 +1322,8 @@ zonkEvBind env (EvBind { eb_lhs = var, eb_rhs = term, eb_is_given = is_given }) -- This has a very big effect on some programs (eg Trac #5030) ; term' <- case getEqPredTys_maybe (idType var') of Just (r, ty1, ty2) | ty1 `eqType` ty2 - -> return (EvCoercion (mkTcReflCo r ty1)) + -> do { ty1' <- zonkTcTypeToType env ty1 + ; return (EvCoercion (mkTcReflCo r ty1')) } _other -> zonkEvTerm env term ; return (EvBind { eb_lhs = var', eb_rhs = term', eb_is_given = is_given }) } @@ -1339,10 +1340,11 @@ zonkEvInstanceOf env (EvInstanceOfInst tys co q) ; q' <- mapM (zonkEvTerm env) q ; return (EvInstanceOfInst tys' co' q') } zonkEvInstanceOf env (EvInstanceOfLet tys qvars bnds i) - = do { let qvars' = map (zonkIdOcc env) qvars - ; (env', bnds') <- zonkTcEvBinds env bnds - ; let i' = zonkIdOcc env' i - ; return (EvInstanceOfLet tys qvars' bnds' i') } + = do { (env', tys') <- zonkTyBndrsX env tys + ; let qvars' = map (zonkIdOcc env') qvars + ; (env'', bnds') <- zonkTcEvBinds env' bnds + ; let i' = zonkIdOcc env'' i + ; return (EvInstanceOfLet tys' qvars' bnds' i') } {- ************************************************************************ diff --git a/compiler/typecheck/TcRules.hs b/compiler/typecheck/TcRules.hs index 9972af0..4335717 100644 --- a/compiler/typecheck/TcRules.hs +++ b/compiler/typecheck/TcRules.hs @@ -299,20 +299,19 @@ simplifyRule :: RuleName simplifyRule name lhs_wanted rhs_wanted = do { -- We allow ourselves to unify environment -- variables: runTcS runs with topTcLevel - (insoluble, _) <- runTcS $ + ((insoluble, lhs_extra), _) <- runTcS $ do { -- First solve the LHS and *then* solve the RHS -- See Note [Solve order for RULES] lhs_resid <- solveWanteds lhs_wanted + ; let lhs_resid_simple = wc_simple lhs_resid ; lhs_inst <- fmap andManyCts $ - mapM instantiateWC (bagToList (wc_simple lhs_resid)) + mapM instantiateWC (bagToList lhs_resid_simple) ; lhs_inst_resid <- solveWanteds lhs_resid { wc_simple = lhs_inst } ; rhs_resid <- solveWanteds rhs_wanted - ; return (insolubleWC lhs_inst_resid || insolubleWC rhs_resid) } + ; return (insolubleWC lhs_inst_resid || insolubleWC rhs_resid, lhs_inst) } - ; zonked_lhs_simples <- zonkSimples (wc_simple lhs_wanted) - ; (zonked_lhs_inst, _) <- runTcS $ fmap andManyCts $ - mapM instantiateWC (bagToList zonked_lhs_simples) - ; let (q_cts, non_q_cts) = partitionBag quantify_me zonked_lhs_inst + ; zonked_lhs <- zonkSimples (wc_simple lhs_wanted `unionBags` lhs_extra) + ; let (q_cts, non_q_cts) = partitionBag quantify_me zonked_lhs quantify_me -- Note [RULE quantification over equalities] | insoluble = quantify_insol | otherwise = quantify_normal @@ -322,6 +321,8 @@ simplifyRule name lhs_wanted rhs_wanted quantify_normal ct | EqPred NomEq t1 t2 <- classifyPredType (ctPred ct) = not (t1 `tcEqType` t2) + | InstanceOfPred _ _ <- classifyPredType (ctPred ct) + = False | otherwise = True @@ -329,8 +330,7 @@ simplifyRule name lhs_wanted rhs_wanted vcat [ ptext (sLit "LHS of rule") <+> doubleQuotes (ftext name) , text "lhs_wantd" <+> ppr lhs_wanted , text "rhs_wantd" <+> ppr rhs_wanted - , text "zonked_lhs_simples" <+> ppr zonked_lhs_simples - , text "zonked_lhs_inst" <+> ppr zonked_lhs_inst + , text "zonked_lhs" <+> ppr zonked_lhs , text "q_cts" <+> ppr q_cts , text "non_q_cts" <+> ppr non_q_cts ] From git at git.haskell.org Mon Jun 29 12:59:51 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 29 Jun 2015 12:59:51 +0000 (UTC) Subject: [commit: ghc] wip/impredicativity: Fix bug on the generation of HsWrappers (59a2764) Message-ID: <20150629125951.C4CA83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/impredicativity Link : http://ghc.haskell.org/trac/ghc/changeset/59a276484a58dc64e4e8b6857978422df01e4487/ghc >--------------------------------------------------------------- commit 59a276484a58dc64e4e8b6857978422df01e4487 Author: Alejandro Serrano Date: Mon Jun 29 15:00:21 2015 +0200 Fix bug on the generation of HsWrappers >--------------------------------------------------------------- 59a276484a58dc64e4e8b6857978422df01e4487 compiler/typecheck/TcExpr.hs | 15 ++++++++------- 1 file changed, 8 insertions(+), 7 deletions(-) diff --git a/compiler/typecheck/TcExpr.hs b/compiler/typecheck/TcExpr.hs index 860d301..33f59e6 100644 --- a/compiler/typecheck/TcExpr.hs +++ b/compiler/typecheck/TcExpr.hs @@ -1226,19 +1226,20 @@ tc_check_id orig id_name res_ty -> do { (expr, actual_ty) <- case cl of RealDataCon con -> inst_data_con con PatSynCon ps -> tcPatSynBuilderOcc orig ps - ; co <- unifyType res_ty actual_ty - ; return (mkHsWrap (mkWpCast co) expr) } + ; co <- unifyType actual_ty res_ty + ; return (mkHsWrapCo co expr) } _ -> failWithTc $ ppr thing <+> ptext (sLit "used where a value identifier was expected") } where inst_normal_id orig id res_ty flavor = do { let actual_ty = idType id - ; case flavor of - TcIdMonomorphic - -> do { co <- unifyType res_ty actual_ty - ; return (mkHsWrap (mkWpCast co) (HsVar id)) } - TcIdUnrestricted + ; case (res_ty `eqType` actual_ty, flavor) of + (True, _) -> return (HsVar id) + (False, TcIdMonomorphic) + -> do { co <- unifyType actual_ty res_ty + ; return (mkHsWrapCo co (HsVar id)) } + (False, TcIdUnrestricted) -> do { ev <- emitWanted orig (mkInstanceOfPred actual_ty res_ty) ; return (mkHsWrap (mkWpInstanceOf actual_ty ev) (HsVar id)) } } From git at git.haskell.org Mon Jun 29 14:11:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 29 Jun 2015 14:11:44 +0000 (UTC) Subject: [commit: ghc] master: Update performance numbers due to #10482 (9b5df2a) Message-ID: <20150629141144.61EFA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9b5df2a401ba8f033cbbc80331f16ac8cf827c92/ghc >--------------------------------------------------------------- commit 9b5df2a401ba8f033cbbc80331f16ac8cf827c92 Author: Joachim Breitner Date: Mon Jun 29 15:59:17 2015 +0200 Update performance numbers due to #10482 The fix in 0b7e538a has regressed these benchmarks. I have recentered them rather than marking them as broken(10482), because nobody systematically watches the broken test cases, and we want to catch future regressions (or improvements!). #10482 is currently still open, presumably because this needs investigating. >--------------------------------------------------------------- 9b5df2a401ba8f033cbbc80331f16ac8cf827c92 testsuite/tests/perf/haddock/all.T | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/perf/haddock/all.T b/testsuite/tests/perf/haddock/all.T index aaa7c55..94f7cbd 100644 --- a/testsuite/tests/perf/haddock/all.T +++ b/testsuite/tests/perf/haddock/all.T @@ -45,7 +45,7 @@ test('haddock.base', test('haddock.Cabal', [unless(in_tree_compiler(), skip), req_haddock ,stats_num_field('bytes allocated', - [(wordsize(64), 6710234312, 5) + [(wordsize(64), 7413958344, 5) # 2012-08-14: 3255435248 (amd64/Linux) # 2012-08-29: 3324606664 (amd64/Linux, new codegen) # 2012-10-08: 3373401360 (amd64/Linux) @@ -65,6 +65,7 @@ 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 ,(platform('i386-unknown-mingw32'), 3293415576, 5) # 2012-10-30: 1733638168 (x86/Windows) @@ -86,7 +87,7 @@ test('haddock.Cabal', test('haddock.compiler', [unless(in_tree_compiler(), skip), req_haddock ,stats_num_field('bytes allocated', - [(wordsize(64), 36740649320, 10) + [(wordsize(64), 40624322224, 10) # 2012P-08-14: 26070600504 (amd64/Linux) # 2012-08-29: 26353100288 (amd64/Linux, new CG) # 2012-09-18: 26882813032 (amd64/Linux) @@ -96,6 +97,7 @@ test('haddock.compiler', # 2014-09-10: 30353349160 (amd64/Linux) post-AMP cleanup # 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 ,(platform('i386-unknown-mingw32'), 902576468, 10) # 2012-10-30: 13773051312 (x86/Windows) From git at git.haskell.org Mon Jun 29 19:12:32 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 29 Jun 2015 19:12:32 +0000 (UTC) Subject: [commit: ghc] master: Correct BangPat SrcSpan calculation (c6bb2fc) Message-ID: <20150629191232.BFABD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c6bb2fc50716a2fc540d55ecddbc5c14e94979f7/ghc >--------------------------------------------------------------- commit c6bb2fc50716a2fc540d55ecddbc5c14e94979f7 Author: Matthew Pickering Date: Mon Jun 29 21:11:17 2015 +0200 Correct BangPat SrcSpan calculation Summary: Previously when the split was performed in splitBang, `BangPat` was given the same SrcSpan as the whole of the LHS of the declaration. This patch correctly calculates the value. Reviewers: alanz, austin Reviewed By: alanz, austin Subscribers: thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1020 GHC Trac Issues: #10588 >--------------------------------------------------------------- c6bb2fc50716a2fc540d55ecddbc5c14e94979f7 compiler/parser/RdrHsSyn.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/compiler/parser/RdrHsSyn.hs b/compiler/parser/RdrHsSyn.hs index d7af65d..aa0b8cf 100644 --- a/compiler/parser/RdrHsSyn.hs +++ b/compiler/parser/RdrHsSyn.hs @@ -997,9 +997,10 @@ checkDoAndIfThenElse guardExpr semiThen thenExpr semiElse elseExpr -- not be any OpApps inside the e's splitBang :: LHsExpr RdrName -> Maybe (LHsExpr RdrName, [LHsExpr RdrName]) -- Splits (f ! g a b) into (f, [(! g), a, b]) -splitBang (L loc (OpApp l_arg bang@(L _ (HsVar op)) _ r_arg)) - | op == bang_RDR = Just (l_arg, L loc (SectionR bang arg1) : argns) +splitBang (L _ (OpApp l_arg bang@(L _ (HsVar op)) _ r_arg)) + | op == bang_RDR = Just (l_arg, L l' (SectionR bang arg1) : argns) where + l' = combineLocs bang arg1 (arg1,argns) = split_bang r_arg [] split_bang (L _ (HsApp f e)) es = split_bang f (e:es) split_bang e es = (e,es) From git at git.haskell.org Tue Jun 30 10:12:41 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 30 Jun 2015 10:12:41 +0000 (UTC) Subject: [commit: ghc] master: Build system: remove unused variable CHECK_PACKAGES (c495c67) Message-ID: <20150630101241.810CB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c495c670cc726ad345072e94e4541a9c5d8fb98a/ghc >--------------------------------------------------------------- commit c495c670cc726ad345072e94e4541a9c5d8fb98a Author: Thomas Miedema Date: Tue Jun 30 03:12:32 2015 +0200 Build system: remove unused variable CHECK_PACKAGES >--------------------------------------------------------------- c495c670cc726ad345072e94e4541a9c5d8fb98a mk/config.mk.in | 3 --- mk/validate-settings.mk | 2 -- 2 files changed, 5 deletions(-) diff --git a/mk/config.mk.in b/mk/config.mk.in index ab177af..00c66ca 100644 --- a/mk/config.mk.in +++ b/mk/config.mk.in @@ -302,9 +302,6 @@ SplitObjs=$(SupportsSplitObjs) # Whether to install the extra packages InstallExtraPackages = NO -# Run "ghc-pkg check" on each package -CHECK_PACKAGES = NO - # ---------------------------------------------------------------------------- # There are a number of things which technically depend on GHC (e.g. if diff --git a/mk/validate-settings.mk b/mk/validate-settings.mk index cfc7234..ef3a58e 100644 --- a/mk/validate-settings.mk +++ b/mk/validate-settings.mk @@ -31,8 +31,6 @@ SplitObjs = NO NoFibWays = STRIP_CMD = : -CHECK_PACKAGES = YES - # We want to install DPH when validating, so that we can test it InstallExtraPackages = YES From git at git.haskell.org Tue Jun 30 10:12:44 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 30 Jun 2015 10:12:44 +0000 (UTC) Subject: [commit: ghc] master: Testsuite: accept T2592.stderr (minor changes) (897a46c) Message-ID: <20150630101244.482EC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/897a46c16756060d2b924ec0953de140060592c7/ghc >--------------------------------------------------------------- commit 897a46c16756060d2b924ec0953de140060592c7 Author: Thomas Miedema Date: Tue Jun 30 10:55:17 2015 +0200 Testsuite: accept T2592.stderr (minor changes) >--------------------------------------------------------------- 897a46c16756060d2b924ec0953de140060592c7 testsuite/tests/profiling/should_run/T2592.stderr | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/profiling/should_run/T2592.stderr b/testsuite/tests/profiling/should_run/T2592.stderr index 724ef0e..a5d0317 100644 --- a/testsuite/tests/profiling/should_run/T2592.stderr +++ b/testsuite/tests/profiling/should_run/T2592.stderr @@ -1,3 +1,3 @@ T2592: Heap exhausted; -Current maximum heap size is 1048576 bytes (1 MB); -use `+RTS -M' to increase it. +T2592: Current maximum heap size is 1048576 bytes (1 MB). +T2592: Use `+RTS -M' to increase it. From git at git.haskell.org Tue Jun 30 10:12:46 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 30 Jun 2015 10:12:46 +0000 (UTC) Subject: [commit: ghc] master: Testsuite: put extra_run_opts last on command line (6b9fc65) Message-ID: <20150630101246.F10C63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6b9fc657ec561e7b96c93d9fe79da5a5e1b013ed/ghc >--------------------------------------------------------------- commit 6b9fc657ec561e7b96c93d9fe79da5a5e1b013ed Author: Thomas Miedema Date: Tue Jun 30 10:57:19 2015 +0200 Testsuite: put extra_run_opts last on command line Some tests use the format: extra_run_opts('+RTS foo') (without closing -RTS). Make it clear in testlib.py that this should work. >--------------------------------------------------------------- 6b9fc657ec561e7b96c93d9fe79da5a5e1b013ed testsuite/driver/testlib.py | 10 +++++++--- 1 file changed, 7 insertions(+), 3 deletions(-) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index 033440b..0fcb738 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -1293,7 +1293,7 @@ def simple_build( name, way, extra_hc_opts, should_fail, top_mod, link, addsuf, # from /dev/null. Route output to testname.run.stdout and # testname.run.stderr. Returns the exit code of the run. -def simple_run( name, way, prog, args ): +def simple_run(name, way, prog, extra_run_opts): opts = getTestOpts() # figure out what to use for stdin @@ -1319,7 +1319,9 @@ def simple_run( name, way, prog, args ): stats_file = name + '.stats' if len(opts.stats_range_fields) > 0: - args += ' +RTS -V0 -t' + stats_file + ' --machine-readable -RTS' + stats_args = ' +RTS -V0 -t' + stats_file + ' --machine-readable -RTS' + else: + stats_args = '' if opts.no_stdin: stdin_comes_from = '' @@ -1333,8 +1335,10 @@ def simple_run( name, way, prog, args ): redirection = ' > {0} 2> {1}'.format(run_stdout, run_stderr) redirection_append = ' >> {0} 2>> {1}'.format(run_stdout, run_stderr) - cmd = prog + ' ' + args + ' ' \ + # Put extra_run_opts last: extra_run_opts('+RTS foo') should work. + cmd = prog + stats_args + ' ' \ + my_rts_flags + ' ' \ + + extra_run_opts + ' ' \ + stdin_comes_from \ + redirection From git at git.haskell.org Tue Jun 30 10:12:49 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 30 Jun 2015 10:12:49 +0000 (UTC) Subject: [commit: ghc] master: Build system: prevent "warning: overriding commands for target..." (daa5097) Message-ID: <20150630101249.A85C83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/daa5097facb228307d52e5d3e789e5c81494a475/ghc >--------------------------------------------------------------- commit daa5097facb228307d52e5d3e789e5c81494a475 Author: Thomas Miedema Date: Tue Jun 30 12:00:43 2015 +0200 Build system: prevent "warning: overriding commands for target..." This happened because the dyn way was listed twice in GhcLibWays for BuildFlavour=perf. >--------------------------------------------------------------- daa5097facb228307d52e5d3e789e5c81494a475 mk/build.mk.sample | 1 + 1 file changed, 1 insertion(+) diff --git a/mk/build.mk.sample b/mk/build.mk.sample index 1e95bdd..7969b40 100644 --- a/mk/build.mk.sample +++ b/mk/build.mk.sample @@ -94,6 +94,7 @@ GhcLibHcOpts = -O2 #BUILD_DOCBOOK_PS #BUILD_DOCBOOK_PDF +GhcLibWays = v GhcLibWays += p ifeq "$(PlatformSupportsSharedLibs)" "YES" GhcLibWays += dyn From git at git.haskell.org Tue Jun 30 13:00:56 2015 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 30 Jun 2015 13:00:56 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: Correct BangPat SrcSpan calculation (5560861) Message-ID: <20150630130056.064523A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/5560861e4562a2e270e6610e6ef3cf120253bb16/ghc >--------------------------------------------------------------- commit 5560861e4562a2e270e6610e6ef3cf120253bb16 Author: Matthew Pickering Date: Mon Jun 29 21:11:17 2015 +0200 Correct BangPat SrcSpan calculation Summary: Previously when the split was performed in splitBang, `BangPat` was given the same SrcSpan as the whole of the LHS of the declaration. This patch correctly calculates the value. Reviewers: alanz, austin Reviewed By: alanz, austin Subscribers: thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1020 GHC Trac Issues: #10588 (cherry picked from commit c6bb2fc50716a2fc540d55ecddbc5c14e94979f7) >--------------------------------------------------------------- 5560861e4562a2e270e6610e6ef3cf120253bb16 compiler/parser/RdrHsSyn.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/compiler/parser/RdrHsSyn.hs b/compiler/parser/RdrHsSyn.hs index cc019d1..3d3e9c9 100644 --- a/compiler/parser/RdrHsSyn.hs +++ b/compiler/parser/RdrHsSyn.hs @@ -1169,9 +1169,10 @@ checkDoAndIfThenElse guardExpr semiThen thenExpr semiElse elseExpr -- not be any OpApps inside the e's splitBang :: LHsExpr RdrName -> Maybe (LHsExpr RdrName, [LHsExpr RdrName]) -- Splits (f ! g a b) into (f, [(! g), a, b]) -splitBang (L loc (OpApp l_arg bang@(L _ (HsVar op)) _ r_arg)) - | op == bang_RDR = Just (l_arg, L loc (SectionR bang arg1) : argns) +splitBang (L _ (OpApp l_arg bang@(L _ (HsVar op)) _ r_arg)) + | op == bang_RDR = Just (l_arg, L l' (SectionR bang arg1) : argns) where + l' = combineLocs bang arg1 (arg1,argns) = split_bang r_arg [] split_bang (L _ (HsApp f e)) es = split_bang f (e:es) split_bang e es = (e,es)