From git at git.haskell.org Sat Mar 1 07:15:34 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 1 Mar 2014 07:15:34 +0000 (UTC) Subject: [commit: ghc] master: add missing files (#8124) (3fba875) Message-ID: <20140301071534.9AA492406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3fba87599378afbcf425a0fc2a5a61d21e3719d4/ghc >--------------------------------------------------------------- commit 3fba87599378afbcf425a0fc2a5a61d21e3719d4 Author: Simon Marlow Date: Sat Mar 1 07:14:47 2014 +0000 add missing files (#8124) >--------------------------------------------------------------- 3fba87599378afbcf425a0fc2a5a61d21e3719d4 testsuite/tests/rts/T8124.hs | 6 ++++++ testsuite/tests/rts/T8124_c.c | 42 +++++++++++++++++++++++++++++++++++++++++ 2 files changed, 48 insertions(+) diff --git a/testsuite/tests/rts/T8124.hs b/testsuite/tests/rts/T8124.hs new file mode 100644 index 0000000..c914b03 --- /dev/null +++ b/testsuite/tests/rts/T8124.hs @@ -0,0 +1,6 @@ +module T8124 where + +f :: Int -> Int +f x = x + 1 + +foreign export ccall "f" f :: Int -> Int diff --git a/testsuite/tests/rts/T8124_c.c b/testsuite/tests/rts/T8124_c.c new file mode 100644 index 0000000..e7e8739 --- /dev/null +++ b/testsuite/tests/rts/T8124_c.c @@ -0,0 +1,42 @@ +#include +#include "T8124_stub.h" +#include "HsFFI.h" +#include + +void *thread(void *param) +{ + f(3); + hs_thread_done(); + pthread_exit(NULL); +} + +int main (int argc, char *argv[]) +{ + hs_init(&argc,&argv); + + // check that we can call hs_thread_done() without having made any + // Haskell calls: + hs_thread_done(); + + // check that we can call hs_thread_done() and then make another Haskell + // call: + int i; + for (i=0; i < 1000; i++) { + f(3); + hs_thread_done(); + } + + // check that we can call hs_thread_done() twice: + hs_thread_done(); + hs_thread_done(); + + // check that hs_thread_done() from child threads works: + pthread_t pid; + for (i=0; i < 1000; i++) { + pthread_create(&pid, NULL, thread, NULL); + pthread_join(pid, NULL); + } + + hs_exit(); + exit(0); +} From git at git.haskell.org Sat Mar 1 07:16:58 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 1 Mar 2014 07:16:58 +0000 (UTC) Subject: [commit: ghc] master: fix copy/pasto (176205c) Message-ID: <20140301071658.D18122406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/176205cf0b89f76d904d381bdcd61e8685116bb7/ghc >--------------------------------------------------------------- commit 176205cf0b89f76d904d381bdcd61e8685116bb7 Author: Simon Marlow Date: Sat Mar 1 07:16:44 2014 +0000 fix copy/pasto >--------------------------------------------------------------- 176205cf0b89f76d904d381bdcd61e8685116bb7 testsuite/tests/rts/Makefile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/rts/Makefile b/testsuite/tests/rts/Makefile index 7f9e073..180fe9b 100644 --- a/testsuite/tests/rts/Makefile +++ b/testsuite/tests/rts/Makefile @@ -85,7 +85,7 @@ T6006_setup : '$(TEST_HC)' $(TEST_HC_OPTS) -c T6006.hs T8124_setup : - '$(TEST_HC)' $(TEST_HC_OPTS) -c T6006.hs + '$(TEST_HC)' $(TEST_HC_OPTS) -c T8124.hs ifeq "$(TARGETPLATFORM)" "i386-unknown-mingw32" T7037_CONST = const From git at git.haskell.org Sat Mar 1 08:09:37 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 1 Mar 2014 08:09:37 +0000 (UTC) Subject: [commit: packages/Cabal] ghc-head: Disable TemplateHaskell/{dynamic, profiling} tests on Travis. (0d5ffeb) Message-ID: <20140301080937.A8D0A2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/Cabal On branch : ghc-head Link : http://git.haskell.org/packages/Cabal.git/commitdiff/0d5ffeb91075739246627da17bda945aedc6a427 >--------------------------------------------------------------- commit 0d5ffeb91075739246627da17bda945aedc6a427 Author: Mikhail Glushenkov Date: Fri Dec 20 17:25:00 2013 +0100 Disable TemplateHaskell/{dynamic,profiling} tests on Travis. >--------------------------------------------------------------- 0d5ffeb91075739246627da17bda945aedc6a427 Cabal/tests/PackageTests.hs | 64 ++++++++++++++++++++++++++++--------------- 1 file changed, 42 insertions(+), 22 deletions(-) diff --git a/Cabal/tests/PackageTests.hs b/Cabal/tests/PackageTests.hs index d515c4e..54b833b 100644 --- a/Cabal/tests/PackageTests.hs +++ b/Cabal/tests/PackageTests.hs @@ -6,21 +6,6 @@ module Main where -import Data.Version (Version(Version)) -import Distribution.Simple.LocalBuildInfo (LocalBuildInfo(..)) -import Distribution.Simple.Program.Types (programPath) -import Distribution.Simple.Program.Builtin (ghcProgram, ghcPkgProgram) -import Distribution.Simple.Program.Db (requireProgram) -import Distribution.Simple.Utils (cabalVersion, die, withFileContents) -import Distribution.Text (display) -import Distribution.Verbosity (normal) -import System.Directory (doesFileExist, getCurrentDirectory, - setCurrentDirectory) -import System.FilePath (()) -import Test.Framework (Test, TestName, defaultMain, testGroup) -import Test.Framework.Providers.HUnit (hUnitTestToTests) -import qualified Test.HUnit as HUnit - import PackageTests.BenchmarkExeV10.Check import PackageTests.BenchmarkOptions.Check import PackageTests.BenchmarkStanza.Check @@ -48,11 +33,31 @@ import PackageTests.TestStanza.Check import PackageTests.TestSuiteExeV10.Check import PackageTests.OrderFlags.Check +import Distribution.Compat.Exception (catchIO) +import Distribution.Simple.LocalBuildInfo (LocalBuildInfo(..)) +import Distribution.Simple.Program.Types (programPath) +import Distribution.Simple.Program.Builtin (ghcProgram, ghcPkgProgram) +import Distribution.Simple.Program.Db (requireProgram) +import Distribution.Simple.Utils (cabalVersion, die, withFileContents) +import Distribution.Text (display) +import Distribution.Verbosity (normal) +import Distribution.Version (Version(Version)) + +import Data.Maybe (isJust) +import System.Directory (doesFileExist, getCurrentDirectory, + setCurrentDirectory) +import System.Environment (getEnv) +import System.FilePath (()) +import Test.Framework (Test, TestName, defaultMain, testGroup) +import Test.Framework.Providers.HUnit (hUnitTestToTests) +import qualified Test.HUnit as HUnit + + hunit :: TestName -> HUnit.Test -> Test hunit name test = testGroup name $ hUnitTestToTests test -tests :: Version -> PackageSpec -> FilePath -> FilePath -> [Test] -tests version inplaceSpec ghcPath ghcPkgPath = +tests :: Version -> PackageSpec -> FilePath -> FilePath -> Bool -> [Test] +tests version inplaceSpec ghcPath ghcPkgPath runningOnTravis = [ hunit "BuildDeps/SameDepsAllRound" (PackageTests.BuildDeps.SameDepsAllRound.Check.suite ghcPath) -- The two following tests were disabled by Johan Tibell as @@ -79,10 +84,6 @@ tests version inplaceSpec ghcPath ghcPkgPath = , hunit "BenchmarkOptions" (PackageTests.BenchmarkOptions.Check.suite ghcPath) , hunit "TemplateHaskell/vanilla" (PackageTests.TemplateHaskell.Check.vanilla ghcPath) - , hunit "TemplateHaskell/profiling" - (PackageTests.TemplateHaskell.Check.profiling ghcPath) - , hunit "TemplateHaskell/dynamic" - (PackageTests.TemplateHaskell.Check.dynamic ghcPath) , hunit "PathsModule/Executable" (PackageTests.PathsModule.Executable.Check.suite ghcPath) , hunit "PathsModule/Library" (PackageTests.PathsModule.Library.Check.suite ghcPath) @@ -93,6 +94,15 @@ tests version inplaceSpec ghcPath ghcPkgPath = , hunit "OrderFlags" (PackageTests.OrderFlags.Check.suite ghcPath) ] ++ + -- These tests are expected to fail on Travis because hvr's PPA GHCs don't + -- include profiling and dynamic libs. + (if not runningOnTravis + then [ hunit "TemplateHaskell/profiling" + (PackageTests.TemplateHaskell.Check.profiling ghcPath) + , hunit "TemplateHaskell/dynamic" + (PackageTests.TemplateHaskell.Check.dynamic ghcPath) + ] + else []) ++ -- These tests are only required to pass on cabal version >= 1.7 (if version >= Version [1, 7] [] then [ hunit "BuildDeps/TargetSpecificDeps1" @@ -134,9 +144,19 @@ main = do putStrLn $ "Using ghc: " ++ ghcPath putStrLn $ "Using ghc-pkg: " ++ ghcPkgPath setCurrentDirectory "tests" + -- Are we running on Travis-CI? + runningOnTravis <- checkRunningOnTravis -- Create a shared Setup executable to speed up Simple tests compileSetup "." ghcPath - defaultMain (tests cabalVersion inplaceSpec ghcPath ghcPkgPath) + defaultMain (tests cabalVersion inplaceSpec + ghcPath ghcPkgPath runningOnTravis) + +-- | Is the test suite running on the Travis-CI build bot? +checkRunningOnTravis :: IO Bool +checkRunningOnTravis = fmap isJust (lookupEnv "CABAL_TEST_RUNNING_ON_TRAVIS") + where + lookupEnv :: String -> IO (Maybe String) + lookupEnv name = (Just `fmap` getEnv name) `catchIO` const (return Nothing) -- Like Distribution.Simple.Configure.getPersistBuildConfig but -- doesn't check that the Cabal version matches, which it doesn't when From git at git.haskell.org Sat Mar 1 08:09:39 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 1 Mar 2014 08:09:39 +0000 (UTC) Subject: [commit: packages/Cabal] ghc-head: Update 'bootstrap.sh'. (d310d87) Message-ID: <20140301080939.A616B2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/Cabal On branch : ghc-head Link : http://git.haskell.org/packages/Cabal.git/commitdiff/d310d87c2c445f52987169a2ce4da03c14070918 >--------------------------------------------------------------- commit d310d87c2c445f52987169a2ce4da03c14070918 Author: Mikhail Glushenkov Date: Tue Feb 4 03:32:45 2014 +0100 Update 'bootstrap.sh'. >--------------------------------------------------------------- d310d87c2c445f52987169a2ce4da03c14070918 cabal-install/bootstrap.sh | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/cabal-install/bootstrap.sh b/cabal-install/bootstrap.sh index f7a9394..03e482d 100755 --- a/cabal-install/bootstrap.sh +++ b/cabal-install/bootstrap.sh @@ -49,14 +49,14 @@ PREFIX=${PREFIX:-${DEFAULT_PREFIX}} # Versions of the packages to install. # The version regex says what existing installed versions are ok. -PARSEC_VER="3.1.3"; PARSEC_VER_REGEXP="[23]\." # == 2.* || == 3.* -DEEPSEQ_VER="1.3.0.1"; DEEPSEQ_VER_REGEXP="1\.[1-9]\." # >= 1.1 && < 2 -TEXT_VER="0.11.3.1"; TEXT_VER_REGEXP="0\.([2-9]|(1[0-1]))\." # >= 0.2 && < 0.12 -NETWORK_VER="2.4.1.2"; NETWORK_VER_REGEXP="2\." # == 2.* -CABAL_VER="1.18.1"; CABAL_VER_REGEXP="1\.1[89]\." # >= 1.18 && < 1.20 +PARSEC_VER="3.1.5"; PARSEC_VER_REGEXP="[23]\." # == 2.* || == 3.* +DEEPSEQ_VER="1.3.0.2"; DEEPSEQ_VER_REGEXP="1\.[1-9]\." # >= 1.1 && < 2 +TEXT_VER="1.1.0.0"; TEXT_VER_REGEXP="((1\.[01]\.)|(0\.([2-9]|(1[0-1]))\.))" # >= 0.2 && < 1.2 +NETWORK_VER="2.4.2.2"; NETWORK_VER_REGEXP="2\." # == 2.* +CABAL_VER="1.18.1.2"; CABAL_VER_REGEXP="1\.1[89]\." # >= 1.18 && < 1.20 TRANS_VER="0.3.0.0"; TRANS_VER_REGEXP="0\.[23]\." # >= 0.2.* && < 0.4.* MTL_VER="2.1.2"; MTL_VER_REGEXP="[2]\." # == 2.* -HTTP_VER="4000.2.8"; HTTP_VER_REGEXP="4000\.[012]\." # == 4000.0.* || 4000.1.* || 4000.2.* +HTTP_VER="4000.2.10"; HTTP_VER_REGEXP="4000\.[012]\." # == 4000.0.* || 4000.1.* || 4000.2.* ZLIB_VER="0.5.4.1"; ZLIB_VER_REGEXP="0\.[45]\." # == 0.4.* || == 0.5.* TIME_VER="1.4.1" TIME_VER_REGEXP="1\.[1234]\.?" # >= 1.1 && < 1.5 RANDOM_VER="1.0.1.1" RANDOM_VER_REGEXP="1\.0\." # >= 1 && < 1.1 From git at git.haskell.org Sat Mar 1 08:13:59 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 1 Mar 2014 08:13:59 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Update to latest Cabal 1.18 branch tip (again) (732aa7e) Message-ID: <20140301081359.8BC232406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/732aa7e24e644928891431d321da52ca6df28a7f/ghc >--------------------------------------------------------------- commit 732aa7e24e644928891431d321da52ca6df28a7f Author: Herbert Valerio Riedel Date: Sat Mar 1 09:10:32 2014 +0100 Update to latest Cabal 1.18 branch tip (again) This was already performed in 37d6e2c54f117 but accidentally reverted as a side-effect of 9976c2ece3aa4. So this update pulls in the fix into ghc-7.8 for #8266 again. Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 732aa7e24e644928891431d321da52ca6df28a7f libraries/Cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Cabal b/libraries/Cabal index e97aa58..d310d87 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit e97aa58f68519db54de1c62339459ebb88aed069 +Subproject commit d310d87c2c445f52987169a2ce4da03c14070918 From git at git.haskell.org Sat Mar 1 09:05:51 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 1 Mar 2014 09:05:51 +0000 (UTC) Subject: [commit: packages/Win32] tag 'Win32-2.3.0.1-release' created Message-ID: <20140301090551.2439C2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/Win32 New tag : Win32-2.3.0.1-release Referencing: e983aceac83a46fa5623df3f5a25c56f9596b86b From git at git.haskell.org Sat Mar 1 09:15:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 1 Mar 2014 09:15:47 +0000 (UTC) Subject: [commit: packages/random] tag 'random-1.0.1.1-release' created Message-ID: <20140301091547.39E022406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/random New tag : random-1.0.1.1-release Referencing: 2d72beea563be14dfffa25da2058c99ac86a03c1 From git at git.haskell.org Sat Mar 1 09:23:48 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 1 Mar 2014 09:23:48 +0000 (UTC) Subject: [commit: packages/Cabal] tag 'Cabal-1.18.1.2-release' created Message-ID: <20140301092348.96CC42406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/Cabal New tag : Cabal-1.18.1.2-release Referencing: 12bf49765f6bff9baaa862320145ccad2f08e043 From git at git.haskell.org Sat Mar 1 09:25:12 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 1 Mar 2014 09:25:12 +0000 (UTC) Subject: [commit: packages/binary] tag 'binary-0.7.1.0-release' created Message-ID: <20140301092513.06A572406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary New tag : binary-0.7.1.0-release Referencing: 123cd0dda0a4c33bc6b32ccacd29dfd1921a6519 From git at git.haskell.org Sat Mar 1 10:06:23 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 1 Mar 2014 10:06:23 +0000 (UTC) Subject: [commit: packages/ghc-prim] master: Add Since-annotation to `Coercible` (a3b0a06) Message-ID: <20140301100623.E66C12406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc-prim On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a3b0a06a2bbe37122f1a3d5e20926bc30f5656d1/ghc-prim >--------------------------------------------------------------- commit a3b0a06a2bbe37122f1a3d5e20926bc30f5656d1 Author: Herbert Valerio Riedel Date: Sat Mar 1 11:05:45 2014 +0100 Add Since-annotation to `Coercible` Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- a3b0a06a2bbe37122f1a3d5e20926bc30f5656d1 GHC/Types.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/GHC/Types.hs b/GHC/Types.hs index 0d7583d..96673e1 100644 --- a/GHC/Types.hs +++ b/GHC/Types.hs @@ -136,6 +136,8 @@ data (~) a b = Eq# ((~#) a b) -- by writing -- -- @type role Set nominal@ +-- +-- /Since: 4.7.0.0/ data Coercible a b = MkCoercible ((~#) a b) -- | Alias for tagToEnum#. Returns True of its parameter is 1# and False From git at git.haskell.org Sat Mar 1 10:06:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 1 Mar 2014 10:06:47 +0000 (UTC) Subject: [commit: packages/ghc-prim] ghc-7.8's head updated: Add Since-annotation to `Coercible` (a3b0a06) Message-ID: <20140301100647.2ABE82406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc-prim Branch 'ghc-7.8' now includes: a3b0a06 Add Since-annotation to `Coercible` From git at git.haskell.org Sat Mar 1 10:42:44 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 1 Mar 2014 10:42:44 +0000 (UTC) Subject: [commit: packages/base] master: Tweak documentation and update changelog.md (44dec75) Message-ID: <20140301104244.C58F22406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/base On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/44dec750a618a89202f80dcd695e5eb9fb74a74f/base >--------------------------------------------------------------- commit 44dec750a618a89202f80dcd695e5eb9fb74a74f Author: Herbert Valerio Riedel Date: Sat Mar 1 11:29:48 2014 +0100 Tweak documentation and update changelog.md This adds release note entries to changelog and tweaks Haddock comments with respect to the recent commits 1a9abe7a1a3c7 (re #8797) and f932b79948f0 (re #8745) Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 44dec750a618a89202f80dcd695e5eb9fb74a74f Data/Coerce.hs | 4 ++++ GHC/Exts.hs | 4 ++++ changelog.md | 20 +++++++++++++++++--- 3 files changed, 25 insertions(+), 3 deletions(-) diff --git a/Data/Coerce.hs b/Data/Coerce.hs index 93d5e19..2065159 100644 --- a/Data/Coerce.hs +++ b/Data/Coerce.hs @@ -14,6 +14,10 @@ -- -- Safe coercions between data types. -- +-- More in-depth information can be found on the +-- +-- +-- /Since: 4.7.0.0/ ----------------------------------------------------------------------------- module Data.Coerce diff --git a/GHC/Exts.hs b/GHC/Exts.hs index 62f1951..efdf868 100755 --- a/GHC/Exts.hs +++ b/GHC/Exts.hs @@ -46,6 +46,10 @@ module GHC.Exts lazy, inline, -- * Safe coercions + -- + -- | These are available from the /Trustworthy/ module "Data.Coerce" as well + -- + -- /Since: 4.7.0.0/ Data.Coerce.coerce, Data.Coerce.Coercible, -- * Transform comprehensions diff --git a/changelog.md b/changelog.md index 7e33059..c88c79e 100644 --- a/changelog.md +++ b/changelog.md @@ -15,7 +15,7 @@ * There are now `Foldable` and `Traversable` instances for `Either a`, `Const r`, and `(,) a`. - * There is now a `Monoid` instance for `Const`. + * There is now a `Monoid`, `Generic`, and `Generic1` instance for `Const`. * There is now a `Data` instance for `Data.Version`. @@ -29,7 +29,8 @@ * There are now `Bits` and `FiniteBits` instances for `Bool`. - * There are now `Eq`, `Ord`, `Show` and `Read` instances for `ZipList`. + * There are now `Eq`, `Ord`, `Show`, `Read`, `Generic`. and `Generic1` + instances for `ZipList`. * There are now `Eq`, `Ord`, `Show` and `Read` instances for `Down`. @@ -37,6 +38,12 @@ for types in GHC.Generics (`U1`, `Par1`, `Rec1`, `K1`, `M1`, `(:+:)`, `(:*:)`, `(:.:)`). + * `Data.Monoid`: There are now `Generic` instances for `Dual`, `Endo`, + `All`, `Any`, `Sum`, `Product`, `First`, and `Last`; as well as + `Generic1` instances for `Dual`, `Sum`, `Product`, `First`, and `Last`. + + * The `Data.Monoid.{Product,Sum}` newtype wrappers now have `Num` instances. + * There are now `Functor` instances for `System.Console.GetOpt`'s `ArgOrder`, `OptDescr`, and `ArgDescr`. @@ -47,6 +54,10 @@ * New `Data.Proxy` module providing a concrete, poly-kinded proxy type. + * New `Data.Coerce` module which exports the new `Coercible` class + together with the `coerce` primitive which provide safe coercion + (wrt role checking) between types with same representation. + * `Control.Concurrent.MVar` has a new implementation of `readMVar`, which fixes a long-standing bug where `readMVar` is only atomic if there are no other threads running `putMVar`. `readMVar` now is @@ -95,6 +106,9 @@ `Monad` to an `Applicative`, has now a `Monad m => Monad (WrappedMonad m)` instance. + * There is now a `Generic` and a `Generic1` instance for `WrappedMonad` + and `WrappedArrow`. + * Handle `ExitFailure (-sig)` on Unix by killing process with signal `sig`. * New module `Data.Type.Bool` providing operations on type-level booleans. @@ -106,7 +120,7 @@ * Add `Typeable` instance for `(->)` and `RealWorld`. - * Declare CPP head `` officially obsolete as GHC 7.8+ + * Declare CPP header `` officially obsolete as GHC 7.8+ does not support hand-written `Typeable` instances anymore. * Remove (unmaintained) Hugs98 and NHC98 specific code. From git at git.haskell.org Sat Mar 1 10:42:46 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 1 Mar 2014 10:42:46 +0000 (UTC) Subject: [commit: packages/base] master: Tweak Haddock comments in `Data.Ord.Down` added in ebc85262c (1dadd50) Message-ID: <20140301104246.D5C132406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/base On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1dadd50d80240a03c403a07d4374b83cf9da4736/base >--------------------------------------------------------------- commit 1dadd50d80240a03c403a07d4374b83cf9da4736 Author: Herbert Valerio Riedel Date: Sat Mar 1 11:40:21 2014 +0100 Tweak Haddock comments in `Data.Ord.Down` added in ebc85262c Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 1dadd50d80240a03c403a07d4374b83cf9da4736 Data/Ord.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/Data/Ord.hs b/Data/Ord.hs index a574b83..624dae1 100644 --- a/Data/Ord.hs +++ b/Data/Ord.hs @@ -43,8 +43,9 @@ comparing p x y = compare (p x) (p y) -- This is particularly useful when sorting in generalised list comprehensions, -- as in: @then sortWith by 'Down' x@ -- +-- Provides 'Show' and 'Read' instances (/since: 4.7.0.0/). +-- -- /Since: 4.6.0.0/ --- Show and Read instances /Since: 4.7.0.0/ newtype Down a = Down a deriving (Eq, Show, Read) instance Ord a => Ord (Down a) where From git at git.haskell.org Sat Mar 1 10:43:28 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 1 Mar 2014 10:43:28 +0000 (UTC) Subject: [commit: packages/base] ghc-7.8: Tweak documentation and update changelog.md (a535527) Message-ID: <20140301104328.3F7152406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/base On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/a53552791a4ec99cd51060f119b64adc728ba365/base >--------------------------------------------------------------- commit a53552791a4ec99cd51060f119b64adc728ba365 Author: Herbert Valerio Riedel Date: Sat Mar 1 11:29:48 2014 +0100 Tweak documentation and update changelog.md This adds release note entries to changelog and tweaks Haddock comments with respect to the recent commits 1a9abe7a1a3c7 (re #8797) and f932b79948f0 (re #8745) Signed-off-by: Herbert Valerio Riedel (cherry picked from commit 44dec750a618a89202f80dcd695e5eb9fb74a74f) >--------------------------------------------------------------- a53552791a4ec99cd51060f119b64adc728ba365 Data/Coerce.hs | 4 ++++ GHC/Exts.hs | 4 ++++ changelog.md | 20 +++++++++++++++++--- 3 files changed, 25 insertions(+), 3 deletions(-) diff --git a/Data/Coerce.hs b/Data/Coerce.hs index 93d5e19..2065159 100644 --- a/Data/Coerce.hs +++ b/Data/Coerce.hs @@ -14,6 +14,10 @@ -- -- Safe coercions between data types. -- +-- More in-depth information can be found on the +-- +-- +-- /Since: 4.7.0.0/ ----------------------------------------------------------------------------- module Data.Coerce diff --git a/GHC/Exts.hs b/GHC/Exts.hs index 62f1951..efdf868 100755 --- a/GHC/Exts.hs +++ b/GHC/Exts.hs @@ -46,6 +46,10 @@ module GHC.Exts lazy, inline, -- * Safe coercions + -- + -- | These are available from the /Trustworthy/ module "Data.Coerce" as well + -- + -- /Since: 4.7.0.0/ Data.Coerce.coerce, Data.Coerce.Coercible, -- * Transform comprehensions diff --git a/changelog.md b/changelog.md index 7e33059..c88c79e 100644 --- a/changelog.md +++ b/changelog.md @@ -15,7 +15,7 @@ * There are now `Foldable` and `Traversable` instances for `Either a`, `Const r`, and `(,) a`. - * There is now a `Monoid` instance for `Const`. + * There is now a `Monoid`, `Generic`, and `Generic1` instance for `Const`. * There is now a `Data` instance for `Data.Version`. @@ -29,7 +29,8 @@ * There are now `Bits` and `FiniteBits` instances for `Bool`. - * There are now `Eq`, `Ord`, `Show` and `Read` instances for `ZipList`. + * There are now `Eq`, `Ord`, `Show`, `Read`, `Generic`. and `Generic1` + instances for `ZipList`. * There are now `Eq`, `Ord`, `Show` and `Read` instances for `Down`. @@ -37,6 +38,12 @@ for types in GHC.Generics (`U1`, `Par1`, `Rec1`, `K1`, `M1`, `(:+:)`, `(:*:)`, `(:.:)`). + * `Data.Monoid`: There are now `Generic` instances for `Dual`, `Endo`, + `All`, `Any`, `Sum`, `Product`, `First`, and `Last`; as well as + `Generic1` instances for `Dual`, `Sum`, `Product`, `First`, and `Last`. + + * The `Data.Monoid.{Product,Sum}` newtype wrappers now have `Num` instances. + * There are now `Functor` instances for `System.Console.GetOpt`'s `ArgOrder`, `OptDescr`, and `ArgDescr`. @@ -47,6 +54,10 @@ * New `Data.Proxy` module providing a concrete, poly-kinded proxy type. + * New `Data.Coerce` module which exports the new `Coercible` class + together with the `coerce` primitive which provide safe coercion + (wrt role checking) between types with same representation. + * `Control.Concurrent.MVar` has a new implementation of `readMVar`, which fixes a long-standing bug where `readMVar` is only atomic if there are no other threads running `putMVar`. `readMVar` now is @@ -95,6 +106,9 @@ `Monad` to an `Applicative`, has now a `Monad m => Monad (WrappedMonad m)` instance. + * There is now a `Generic` and a `Generic1` instance for `WrappedMonad` + and `WrappedArrow`. + * Handle `ExitFailure (-sig)` on Unix by killing process with signal `sig`. * New module `Data.Type.Bool` providing operations on type-level booleans. @@ -106,7 +120,7 @@ * Add `Typeable` instance for `(->)` and `RealWorld`. - * Declare CPP head `` officially obsolete as GHC 7.8+ + * Declare CPP header `` officially obsolete as GHC 7.8+ does not support hand-written `Typeable` instances anymore. * Remove (unmaintained) Hugs98 and NHC98 specific code. From git at git.haskell.org Sat Mar 1 10:43:30 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 1 Mar 2014 10:43:30 +0000 (UTC) Subject: [commit: packages/base] ghc-7.8: Tweak Haddock comments in `Data.Ord.Down` added in ebc85262c (240528c) Message-ID: <20140301104330.4166D2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/base On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/240528ca9df8eb48ae4b462f65434a8de1886b1e/base >--------------------------------------------------------------- commit 240528ca9df8eb48ae4b462f65434a8de1886b1e Author: Herbert Valerio Riedel Date: Sat Mar 1 11:40:21 2014 +0100 Tweak Haddock comments in `Data.Ord.Down` added in ebc85262c Signed-off-by: Herbert Valerio Riedel (cherry picked from commit 1dadd50d80240a03c403a07d4374b83cf9da4736) >--------------------------------------------------------------- 240528ca9df8eb48ae4b462f65434a8de1886b1e Data/Ord.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/Data/Ord.hs b/Data/Ord.hs index a574b83..624dae1 100644 --- a/Data/Ord.hs +++ b/Data/Ord.hs @@ -43,8 +43,9 @@ comparing p x y = compare (p x) (p y) -- This is particularly useful when sorting in generalised list comprehensions, -- as in: @then sortWith by 'Down' x@ -- +-- Provides 'Show' and 'Read' instances (/since: 4.7.0.0/). +-- -- /Since: 4.6.0.0/ --- Show and Read instances /Since: 4.7.0.0/ newtype Down a = Down a deriving (Eq, Show, Read) instance Ord a => Ord (Down a) where From git at git.haskell.org Sat Mar 1 13:52:53 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 1 Mar 2014 13:52:53 +0000 (UTC) Subject: [commit: packages/base] master: Workaround failed constant-folding for zeroBits (2dbfcd7) Message-ID: <20140301135253.CB0022406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/base On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2dbfcd70e53845d9119389cecc88411b47b70644/base >--------------------------------------------------------------- commit 2dbfcd70e53845d9119389cecc88411b47b70644 Author: Herbert Valerio Riedel Date: Sat Mar 1 14:45:48 2014 +0100 Workaround failed constant-folding for zeroBits For some reason GHC fails to constant fold `zeroBits :: Int` and `zeroBits :: Integer`; `ghc -show-iface` shows $fBitsInt_$czeroBits :: GHC.Types.Int {- Strictness: m, Unfolding: (GHC.Types.I# (GHC.Prim.andI# 1 (GHC.Prim.notI# 1))) -} Otoh, constant-folding works as expected, reducing `zeroBits` to 0 constant for the other integer-types (= {Word,Int}{8,16,32,64}` and `Word`). So this quickfix is actually just treating the symptom rather than the cause. Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 2dbfcd70e53845d9119389cecc88411b47b70644 Data/Bits.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/Data/Bits.hs b/Data/Bits.hs index e771624..28cd024 100644 --- a/Data/Bits.hs +++ b/Data/Bits.hs @@ -363,6 +363,8 @@ instance Bits Int where {-# INLINE bit #-} {-# INLINE testBit #-} + zeroBits = 0 + bit = bitDefault testBit = testBitDefault @@ -437,6 +439,7 @@ instance Bits Integer where | otherwise = shiftRInteger x (negateInt# i#) testBit x (I# i) = testBitInteger x i + zeroBits = 0 bit = bitDefault popCount = popCountDefault From git at git.haskell.org Sat Mar 1 13:53:21 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 1 Mar 2014 13:53:21 +0000 (UTC) Subject: [commit: packages/base] ghc-7.8: Workaround failed constant-folding for zeroBits (591142f) Message-ID: <20140301135323.7B8C42406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/base On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/591142f8aead4c28bdaa5656d79e6dc38273e685/base >--------------------------------------------------------------- commit 591142f8aead4c28bdaa5656d79e6dc38273e685 Author: Herbert Valerio Riedel Date: Sat Mar 1 14:45:48 2014 +0100 Workaround failed constant-folding for zeroBits For some reason GHC fails to constant fold `zeroBits :: Int` and `zeroBits :: Integer`; `ghc -show-iface` shows $fBitsInt_$czeroBits :: GHC.Types.Int {- Strictness: m, Unfolding: (GHC.Types.I# (GHC.Prim.andI# 1 (GHC.Prim.notI# 1))) -} Otoh, constant-folding works as expected, reducing `zeroBits` to 0 constant for the other integer-types (= {Word,Int}{8,16,32,64}` and `Word`). So this quickfix is actually just treating the symptom rather than the cause. Signed-off-by: Herbert Valerio Riedel (cherry picked from commit 2dbfcd70e53845d9119389cecc88411b47b70644) >--------------------------------------------------------------- 591142f8aead4c28bdaa5656d79e6dc38273e685 Data/Bits.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/Data/Bits.hs b/Data/Bits.hs index e771624..28cd024 100644 --- a/Data/Bits.hs +++ b/Data/Bits.hs @@ -363,6 +363,8 @@ instance Bits Int where {-# INLINE bit #-} {-# INLINE testBit #-} + zeroBits = 0 + bit = bitDefault testBit = testBitDefault @@ -437,6 +439,7 @@ instance Bits Integer where | otherwise = shiftRInteger x (negateInt# i#) testBit x (I# i) = testBitInteger x i + zeroBits = 0 bit = bitDefault popCount = popCountDefault From git at git.haskell.org Mon Mar 3 08:30:13 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Mar 2014 08:30:13 +0000 (UTC) Subject: [commit: packages/time] ghc-head: Changes for Safe Haskell (6dffeea) Message-ID: <20140303083013.B88382406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : ghc-head Link : http://git.haskell.org/packages/time.git/commitdiff/6dffeeafa97f3c93d902d9191a64ac703ccdb0ac >--------------------------------------------------------------- commit 6dffeeafa97f3c93d902d9191a64ac703ccdb0ac Author: omari Date: Thu Feb 13 23:24:36 2014 +0000 Changes for Safe Haskell Makes minimal necessary changes so that modules will infer as Safe for Safe Haskell. Some modules are using rewrite rules, which are not Safe; to these I added Trustworthy pragmas. The rewrite rules will continue to fire as normal, according to GHC's documentation. Other modules import Foreign. I changed these to import Foreign.Safe instead. I changed the time.cabal file so that the minimum version of Base is 4.4; that was the first version of Base that has the Foreign.Safe module. (base 4.4 came with GHC 7.2, which is over two years old.) >--------------------------------------------------------------- 6dffeeafa97f3c93d902d9191a64ac703ccdb0ac Data/Time/Clock/CTimeval.hs | 2 +- Data/Time/Clock/Scale.hs | 1 + Data/Time/Clock/UTC.hs | 1 + Data/Time/LocalTime/TimeZone.hs | 2 +- time.cabal | 2 +- 5 files changed, 5 insertions(+), 3 deletions(-) diff --git a/Data/Time/Clock/CTimeval.hs b/Data/Time/Clock/CTimeval.hs index b0d8920..c8a692a 100644 --- a/Data/Time/Clock/CTimeval.hs +++ b/Data/Time/Clock/CTimeval.hs @@ -4,7 +4,7 @@ module Data.Time.Clock.CTimeval where #ifndef mingw32_HOST_OS -- All Unix-specific, this -import Foreign +import Foreign.Safe import Foreign.C data CTimeval = MkCTimeval CLong CLong diff --git a/Data/Time/Clock/Scale.hs b/Data/Time/Clock/Scale.hs index 9e91795..8ba7759 100644 --- a/Data/Time/Clock/Scale.hs +++ b/Data/Time/Clock/Scale.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Trustworthy #-} {-# OPTIONS -fno-warn-unused-imports #-} #include "HsConfigure.h" -- #hide diff --git a/Data/Time/Clock/UTC.hs b/Data/Time/Clock/UTC.hs index 3ba3309..d41b8f8 100644 --- a/Data/Time/Clock/UTC.hs +++ b/Data/Time/Clock/UTC.hs @@ -1,4 +1,5 @@ {-# OPTIONS -fno-warn-unused-imports #-} +{-# LANGUAGE Trustworthy #-} #include "HsConfigure.h" -- #hide module Data.Time.Clock.UTC diff --git a/Data/Time/LocalTime/TimeZone.hs b/Data/Time/LocalTime/TimeZone.hs index fa70026..e9e4f5f 100644 --- a/Data/Time/LocalTime/TimeZone.hs +++ b/Data/Time/LocalTime/TimeZone.hs @@ -17,7 +17,7 @@ import Data.Time.Calendar.Private import Data.Time.Clock import Data.Time.Clock.POSIX -import Foreign +import Foreign.Safe import Foreign.C import Control.DeepSeq import Data.Typeable diff --git a/time.cabal b/time.cabal index e1f7d79..334fa08 100644 --- a/time.cabal +++ b/time.cabal @@ -36,7 +36,7 @@ source-repository head library build-depends: - base >= 4 && < 5, + base >= 4.4 && < 5, deepseq >= 1.1, old-locale ghc-options: -Wall From git at git.haskell.org Mon Mar 3 08:30:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Mar 2014 08:30:15 +0000 (UTC) Subject: [commit: packages/time] ghc-head: version 1.4.2; improve Makefile (db383ba) Message-ID: <20140303083015.83FED2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : ghc-head Link : http://git.haskell.org/packages/time.git/commitdiff/db383ba64d08634a4388dbdcfd30e3b470b46140 >--------------------------------------------------------------- commit db383ba64d08634a4388dbdcfd30e3b470b46140 Author: Ashley Yakeley Date: Mon Mar 3 05:18:43 2014 +0000 version 1.4.2; improve Makefile >--------------------------------------------------------------- db383ba64d08634a4388dbdcfd30e3b470b46140 Makefile | 11 +++++++---- time.cabal | 2 +- 2 files changed, 8 insertions(+), 5 deletions(-) diff --git a/Makefile b/Makefile index 4fe6afb..73f55fd 100644 --- a/Makefile +++ b/Makefile @@ -1,4 +1,4 @@ -default: install +default: clean test install sdist # Building @@ -17,8 +17,11 @@ test: build haddock: configure cabal haddock -install: build test haddock - cabal install --user --enable-library-profiling --enable-executable-profiling +copy: build test haddock + cabal copy + +install: + cabal install --user --ghc-options=-Werror --enable-library-profiling --enable-executable-profiling sdist: clean configure cabal sdist @@ -26,4 +29,4 @@ sdist: clean configure # switch off intermediate file deletion .SECONDARY: -.PHONY: default clean configure build haddock install test sdist +.PHONY: default clean configure build haddock copy install test sdist diff --git a/time.cabal b/time.cabal index 334fa08..fad816c 100644 --- a/time.cabal +++ b/time.cabal @@ -1,5 +1,5 @@ name: time -version: 1.4.1 +version: 1.4.2 stability: stable license: BSD3 license-file: LICENSE From git at git.haskell.org Mon Mar 3 08:30:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Mar 2014 08:30:17 +0000 (UTC) Subject: [commit: packages/time] ghc-head: Merge tag '1_4_2' of http://code.haskell.org/time/ into ghc-head (adafac2) Message-ID: <20140303083017.BAC7E2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time On branch : ghc-head Link : http://git.haskell.org/packages/time.git/commitdiff/adafac26307cffab0be20c126385ab161c259237 >--------------------------------------------------------------- commit adafac26307cffab0be20c126385ab161c259237 Merge: d4f019b db383ba Author: Herbert Valerio Riedel Date: Mon Mar 3 09:19:20 2014 +0100 Merge tag '1_4_2' of http://code.haskell.org/time/ into ghc-head >--------------------------------------------------------------- adafac26307cffab0be20c126385ab161c259237 Data/Time/Clock/CTimeval.hs | 2 +- Data/Time/Clock/Scale.hs | 1 + Data/Time/Clock/UTC.hs | 1 + Data/Time/LocalTime/TimeZone.hs | 2 +- Makefile | 11 +++++++---- time.cabal | 4 ++-- 6 files changed, 13 insertions(+), 8 deletions(-) From git at git.haskell.org Mon Mar 3 08:30:30 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Mar 2014 08:30:30 +0000 (UTC) Subject: [commit: packages/time] tag 'time-1.4.2-release' created Message-ID: <20140303083030.982442406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/time New tag : time-1.4.2-release Referencing: 99a10d073c30d77cca4c64184469d4e8d169b3e3 From git at git.haskell.org Mon Mar 3 08:33:14 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 3 Mar 2014 08:33:14 +0000 (UTC) Subject: [commit: ghc] master: Update time to 1.4.2 release (afb42a5) Message-ID: <20140303083314.4FA342406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/afb42a54bc0c5cd0dfb69750d3b5e76bcb66ff5a/ghc >--------------------------------------------------------------- commit afb42a54bc0c5cd0dfb69750d3b5e76bcb66ff5a Author: Herbert Valerio Riedel Date: Mon Mar 3 09:25:45 2014 +0100 Update time to 1.4.2 release Note: The only visible change in `time-1.4.2` is at the SafeHaskell level Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- afb42a54bc0c5cd0dfb69750d3b5e76bcb66ff5a libraries/time | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/time b/libraries/time index d4f019b..adafac2 160000 --- a/libraries/time +++ b/libraries/time @@ -1 +1 @@ -Subproject commit d4f019b2c6a332be5443b5bf88d0c7fef91523c6 +Subproject commit adafac26307cffab0be20c126385ab161c259237 From git at git.haskell.org Tue Mar 4 21:16:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Mar 2014 21:16:11 +0000 (UTC) Subject: [commit: packages/Cabal] ghc-head: Bump version number in Makefile to 1.18.1.3 (c226c0d) Message-ID: <20140304211612.E12DE2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/Cabal On branch : ghc-head Link : http://git.haskell.org/packages/Cabal.git/commitdiff/c226c0de042999bbe4c5c339c6c28a9be7f0c6d1 >--------------------------------------------------------------- commit c226c0de042999bbe4c5c339c6c28a9be7f0c6d1 Author: Johan Tibell Date: Tue Mar 4 08:44:37 2014 +0100 Bump version number in Makefile to 1.18.1.3 >--------------------------------------------------------------- c226c0de042999bbe4c5c339c6c28a9be7f0c6d1 Cabal/Makefile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Cabal/Makefile b/Cabal/Makefile index 3cf4387..d2daa1a 100644 --- a/Cabal/Makefile +++ b/Cabal/Makefile @@ -1,5 +1,5 @@ -VERSION=1.18.1.2 +VERSION=1.18.1.3 #KIND=devel KIND=rc From git at git.haskell.org Tue Mar 4 21:17:48 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Mar 2014 21:17:48 +0000 (UTC) Subject: [commit: packages/Cabal] tag 'Cabal-1.18.1.3-release' created Message-ID: <20140304211748.3C67E2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/Cabal New tag : Cabal-1.18.1.3-release Referencing: 6cd4b88965eb7fc178e2f18d0a892730c9aabc4f From git at git.haskell.org Tue Mar 4 21:20:12 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 4 Mar 2014 21:20:12 +0000 (UTC) Subject: [commit: ghc] master: Update `Cabal` to 1.18.1.3 release (01f9ac3) Message-ID: <20140304212013.090F12406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/01f9ac3e977fb128388467a31f62e84d769e17ec/ghc >--------------------------------------------------------------- commit 01f9ac3e977fb128388467a31f62e84d769e17ec Author: Herbert Valerio Riedel Date: Tue Mar 4 22:19:37 2014 +0100 Update `Cabal` to 1.18.1.3 release Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 01f9ac3e977fb128388467a31f62e84d769e17ec libraries/Cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Cabal b/libraries/Cabal index ee6d1cf..c226c0d 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit ee6d1cf5cefe18f6d74ed379af21d92f8b0ae92d +Subproject commit c226c0de042999bbe4c5c339c6c28a9be7f0c6d1 From git at git.haskell.org Wed Mar 5 15:04:54 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Mar 2014 15:04:54 +0000 (UTC) Subject: [commit: ghc] master: Major Call Arity rework (cb8a63c) Message-ID: <20140305150454.71C392406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cb8a63cb61af3cbc871b73071c6b894780f04cc5/ghc >--------------------------------------------------------------- commit cb8a63cb61af3cbc871b73071c6b894780f04cc5 Author: Joachim Breitner Date: Fri Feb 21 10:57:34 2014 +0100 Major Call Arity rework This patch improves the call arity analysis in various ways. Most importantly, it enriches the analysis result information so that when looking at a call, we do not have to make a random choice about what side we want to take the information from. Instead we can combine the results in a way that does not lose valuable information. To do so, besides the incoming arities, we store remember "what can be called with what", i.e. an undirected graph between the (interesting) free variables of an expression. Of course it makes combining the results a bit more tricky (especially mutual recursion), but still doable. The actually implemation of the graph structure is abstractly put away in a module of its own (UnVarGraph.hs) The implementation is geared towards efficiently representing the graphs that we need (which can contain large complete and large complete bipartite graphs, which would be huge in other representations). If someone feels like designing data structures: There is surely some speed-up to be obtained by improving that data structure. Additionally, the analysis now takes into account that if a RHS stays a thunk, then its calls happen only once, even if the variables the RHS is bound to is evaluated multiple times, or is part of a recursive group. >--------------------------------------------------------------- cb8a63cb61af3cbc871b73071c6b894780f04cc5 compiler/ghc.cabal.in | 1 + compiler/simplCore/CallArity.hs | 697 +++++++++++--------- compiler/utils/UnVarGraph.hs | 136 ++++ compiler/utils/UniqFM.lhs | 4 + testsuite/tests/callarity/unittest/CallArity1.hs | 34 +- .../tests/callarity/unittest/CallArity1.stderr | 27 +- testsuite/tests/perf/compiler/all.T | 3 +- 7 files changed, 593 insertions(+), 309 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc cb8a63cb61af3cbc871b73071c6b894780f04cc5 From git at git.haskell.org Wed Mar 5 20:14:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 5 Mar 2014 20:14:15 +0000 (UTC) Subject: [commit: ghc] master: Typos in comments (2d82846) Message-ID: <20140305201415.5BFF32406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2d828460a6e378f85f16677da0ea5c20c4a88e96/ghc >--------------------------------------------------------------- commit 2d828460a6e378f85f16677da0ea5c20c4a88e96 Author: Gabor Greif Date: Wed Mar 5 21:13:31 2014 +0100 Typos in comments >--------------------------------------------------------------- 2d828460a6e378f85f16677da0ea5c20c4a88e96 compiler/coreSyn/CoreArity.lhs | 2 +- ghc/Main.hs | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/coreSyn/CoreArity.lhs b/compiler/coreSyn/CoreArity.lhs index 2c7cd83..080a6fd 100644 --- a/compiler/coreSyn/CoreArity.lhs +++ b/compiler/coreSyn/CoreArity.lhs @@ -325,7 +325,7 @@ this transformation. So we try to limit it as much as possible: (3) Do NOT move a lambda outside a case unless (a) The scrutinee is ok-for-speculation, or - (b) more liberally: the scrunitee is cheap and -fpedantic-bottoms is not + (b) more liberally: the scrutinee is cheap and -fpedantic-bottoms is not enforced Of course both (1) and (2) are readily defeated by disguising the bottoms. diff --git a/ghc/Main.hs b/ghc/Main.hs index 481e7df..46b0970 100644 --- a/ghc/Main.hs +++ b/ghc/Main.hs @@ -835,7 +835,7 @@ the GC stats. As a result, this breaks things like `:set +s` in GHCi (#8754). As a hacky workaround, we instead call 'defaultHooks' directly to initalize the flags in the RTS. -A biproduct of this, I believe, is that hooks are likely broken on OS +A byproduct of this, I believe, is that hooks are likely broken on OS X when dynamically linking. But this probably doesn't affect most people since we're linking GHC dynamically, but most things themselves link statically. From git at git.haskell.org Thu Mar 6 12:17:21 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Mar 2014 12:17:21 +0000 (UTC) Subject: [commit: ghc] master: Add some debug tracing (eeb1400) Message-ID: <20140306121721.D83642406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/eeb1400a0ca9ba7d1831f8ec0b221f632dec9f68/ghc >--------------------------------------------------------------- commit eeb1400a0ca9ba7d1831f8ec0b221f632dec9f68 Author: Simon Peyton Jones Date: Thu Mar 6 10:50:32 2014 +0000 Add some debug tracing >--------------------------------------------------------------- eeb1400a0ca9ba7d1831f8ec0b221f632dec9f68 compiler/stranal/DmdAnal.lhs | 33 ++++++++++++++++++--------------- 1 file changed, 18 insertions(+), 15 deletions(-) diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index e9a7ab4..88eea0c 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -123,21 +123,24 @@ dmdAnalStar env dmd e = (postProcessDmdTypeM defer_and_use dmd_ty, e') -- Main Demand Analsysis machinery -dmdAnal :: AnalEnv +dmdAnal, dmdAnal' :: AnalEnv -> CleanDemand -- The main one takes a *CleanDemand* -> CoreExpr -> (DmdType, CoreExpr) -- The CleanDemand is always strict and not absent -- See Note [Ensure demand is strict] -dmdAnal _ _ (Lit lit) = (nopDmdType, Lit lit) -dmdAnal _ _ (Type ty) = (nopDmdType, Type ty) -- Doesn't happen, in fact -dmdAnal _ _ (Coercion co) = (nopDmdType, Coercion co) +dmdAnal env d e = -- pprTrace "dmdAnal" (ppr d <+> ppr e) $ + dmdAnal' env d e -dmdAnal env dmd (Var var) +dmdAnal' _ _ (Lit lit) = (nopDmdType, Lit lit) +dmdAnal' _ _ (Type ty) = (nopDmdType, Type ty) -- Doesn't happen, in fact +dmdAnal' _ _ (Coercion co) = (nopDmdType, Coercion co) + +dmdAnal' env dmd (Var var) = (dmdTransform env var dmd, Var var) -dmdAnal env dmd (Cast e co) +dmdAnal' env dmd (Cast e co) = (dmd_ty, Cast e' co) where (dmd_ty, e') = dmdAnal env dmd e @@ -155,24 +158,24 @@ dmdAnal env dmd (Cast e co) -- a fixpoint. So revert to a vanilla Eval demand -} -dmdAnal env dmd (Tick t e) +dmdAnal' env dmd (Tick t e) = (dmd_ty, Tick t e') where (dmd_ty, e') = dmdAnal env dmd e -dmdAnal env dmd (App fun (Type ty)) +dmdAnal' env dmd (App fun (Type ty)) = (fun_ty, App fun' (Type ty)) where (fun_ty, fun') = dmdAnal env dmd fun -dmdAnal sigs dmd (App fun (Coercion co)) +dmdAnal' sigs dmd (App fun (Coercion co)) = (fun_ty, App fun' (Coercion co)) where (fun_ty, fun') = dmdAnal sigs dmd fun -- Lots of the other code is there to make this -- beautiful, compositional, application rule :-) -dmdAnal env dmd (App fun arg) -- Non-type arguments +dmdAnal' env dmd (App fun arg) -- Non-type arguments = let -- [Type arg handled above] call_dmd = mkCallDmd dmd (fun_ty, fun') = dmdAnal env call_dmd fun @@ -190,7 +193,7 @@ dmdAnal env dmd (App fun arg) -- Non-type arguments (res_ty `bothDmdType` arg_ty, App fun' arg') -- this is an anonymous lambda, since @dmdAnalRhs@ uses @collectBinders@ -dmdAnal env dmd (Lam var body) +dmdAnal' env dmd (Lam var body) | isTyVar var = let (body_ty, body') = dmdAnal env dmd body @@ -209,7 +212,7 @@ dmdAnal env dmd (Lam var body) in (postProcessUnsat defer_and_use lam_ty, Lam var' body') -dmdAnal env dmd (Case scrut case_bndr ty [alt@(DataAlt dc, _, _)]) +dmdAnal' env dmd (Case scrut case_bndr ty [alt@(DataAlt dc, _, _)]) -- Only one alternative with a product constructor | let tycon = dataConTyCon dc , isProductTyCon tycon @@ -267,7 +270,7 @@ dmdAnal env dmd (Case scrut case_bndr ty [alt@(DataAlt dc, _, _)]) -- , text "res_ty" <+> ppr res_ty ]) $ (res_ty, Case scrut' case_bndr' ty [alt']) -dmdAnal env dmd (Case scrut case_bndr ty alts) +dmdAnal' env dmd (Case scrut case_bndr ty alts) = let -- Case expression with multiple alternatives (alt_tys, alts') = mapAndUnzip (dmdAnalAlt env dmd) alts (scrut_ty, scrut') = dmdAnal env cleanEvalDmd scrut @@ -281,7 +284,7 @@ dmdAnal env dmd (Case scrut case_bndr ty alts) -- , text "res_ty" <+> ppr res_ty ]) $ (res_ty, Case scrut' case_bndr' ty alts') -dmdAnal env dmd (Let (NonRec id rhs) body) +dmdAnal' env dmd (Let (NonRec id rhs) body) = (body_ty2, Let (NonRec id2 annotated_rhs) body') where (sig, lazy_fv, id1, rhs') = dmdAnalRhs NotTopLevel Nothing env id rhs @@ -306,7 +309,7 @@ dmdAnal env dmd (Let (NonRec id rhs) body) -- the vanilla call demand seem to be due to (b). So we don't -- bother to re-analyse the RHS. -dmdAnal env dmd (Let (Rec pairs) body) +dmdAnal' env dmd (Let (Rec pairs) body) = let (env', lazy_fv, pairs') = dmdFix NotTopLevel env pairs (body_ty, body') = dmdAnal env' dmd body From git at git.haskell.org Thu Mar 6 12:17:25 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Mar 2014 12:17:25 +0000 (UTC) Subject: [commit: ghc] master: Make the demand on a binder compatible with type (fixes Trac #8569) (4b355cd) Message-ID: <20140306121725.319252406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4b355cd21a190e3d2c2d3a830ba2337d1c442dfe/ghc >--------------------------------------------------------------- commit 4b355cd21a190e3d2c2d3a830ba2337d1c442dfe Author: Simon Peyton Jones Date: Thu Mar 6 11:31:47 2014 +0000 Make the demand on a binder compatible with type (fixes Trac #8569) Because of GADTs and casts we were getting binders whose demand annotation was more deeply nested than made sense for its type. See Note [Trimming a demand to a type], in Demand.lhs, which I reproduce here: Note [Trimming a demand to a type] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Consider this: f :: a -> Bool f x = case ... of A g1 -> case (x |> g1) of (p,q) -> ... B -> error "urk" where A,B are the constructors of a GADT. We'll get a U(U,U) demand on x from the A branch, but that's a stupid demand for x itself, which has type 'a'. Indeed we get ASSERTs going off (notably in splitUseProdDmd, Trac #8569). Bottom line: we really don't want to have a binder whose demand is more deeply-nested than its type. There are various ways to tackle this. When processing (x |> g1), we could "trim" the incoming demand U(U,U) to match x's type. But I'm currently doing so just at the moment when we pin a demand on a binder, in DmdAnal.findBndrDmd. >--------------------------------------------------------------- 4b355cd21a190e3d2c2d3a830ba2337d1c442dfe compiler/basicTypes/Demand.lhs | 62 +++++++++++++++++++++++++++++++++++++- compiler/stranal/DmdAnal.lhs | 64 +++++++++++++++++++++------------------- compiler/stranal/WwLib.lhs | 31 ++++++++++++++++++- 3 files changed, 124 insertions(+), 33 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 4b355cd21a190e3d2c2d3a830ba2337d1c442dfe From git at git.haskell.org Thu Mar 6 12:17:27 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Mar 2014 12:17:27 +0000 (UTC) Subject: [commit: ghc] master: Attach the right location to pattern synonym error message (fixes Trac #8841) (96daafc) Message-ID: <20140306121727.D3F0F2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/96daafc3305a691590b88c1175a8f45e5d327471/ghc >--------------------------------------------------------------- commit 96daafc3305a691590b88c1175a8f45e5d327471 Author: Simon Peyton Jones Date: Thu Mar 6 11:32:55 2014 +0000 Attach the right location to pattern synonym error message (fixes Trac #8841) >--------------------------------------------------------------- 96daafc3305a691590b88c1175a8f45e5d327471 compiler/typecheck/TcPatSyn.lhs | 9 ++++----- 1 file changed, 4 insertions(+), 5 deletions(-) diff --git a/compiler/typecheck/TcPatSyn.lhs b/compiler/typecheck/TcPatSyn.lhs index a126f0f..703e59d 100644 --- a/compiler/typecheck/TcPatSyn.lhs +++ b/compiler/typecheck/TcPatSyn.lhs @@ -186,7 +186,7 @@ tcPatSynWrapper lname lpat dir args univ_tvs ex_tvs theta pat_ty (Unidirectional, _) -> return Nothing (ImplicitBidirectional, Nothing) -> - cannotInvertPatSynErr (unLoc lpat) + cannotInvertPatSynErr lpat (ImplicitBidirectional, Just lexpr) -> fmap Just $ tc_pat_syn_wrapper_from_expr lname lexpr args univ_tvs ex_tvs theta pat_ty } @@ -281,10 +281,9 @@ asPatInPatSynErr pat hang (ptext (sLit "Pattern synonym definition cannot contain as-patterns (@):")) 2 (ppr pat) --- TODO: Highlight sub-pattern that causes the problem -cannotInvertPatSynErr :: OutputableBndr name => Pat name -> TcM a -cannotInvertPatSynErr pat - = failWithTc $ +cannotInvertPatSynErr :: OutputableBndr name => LPat name -> TcM a +cannotInvertPatSynErr (L loc pat) + = setSrcSpan loc $ failWithTc $ hang (ptext (sLit "Right-hand side of bidirectional pattern synonym cannot be used as an expression")) 2 (ppr pat) From git at git.haskell.org Thu Mar 6 12:17:30 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Mar 2014 12:17:30 +0000 (UTC) Subject: [commit: ghc] master: Test for Trac #8841 now works (bf9bf60) Message-ID: <20140306121731.AD7E42406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bf9bf602399eca30ca522ae5bae52d4f3ec1ab88/ghc >--------------------------------------------------------------- commit bf9bf602399eca30ca522ae5bae52d4f3ec1ab88 Author: Simon Peyton Jones Date: Thu Mar 6 12:13:05 2014 +0000 Test for Trac #8841 now works >--------------------------------------------------------------- bf9bf602399eca30ca522ae5bae52d4f3ec1ab88 testsuite/tests/patsyn/should_fail/unidir.stderr | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/patsyn/should_fail/unidir.stderr b/testsuite/tests/patsyn/should_fail/unidir.stderr index ea019bc..b116115 100644 --- a/testsuite/tests/patsyn/should_fail/unidir.stderr +++ b/testsuite/tests/patsyn/should_fail/unidir.stderr @@ -1,4 +1,4 @@ -unidir.hs:1:1: +unidir.hs:4:18: Right-hand side of bidirectional pattern synonym cannot be used as an expression x : _ From git at git.haskell.org Thu Mar 6 12:17:32 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 6 Mar 2014 12:17:32 +0000 (UTC) Subject: [commit: ghc] master: Trac #8569 fixed (7fa6c67) Message-ID: <20140306121732.80AF22406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7fa6c67bcc9970ce2fa4b3f3a7f17042b9b4fd0e/ghc >--------------------------------------------------------------- commit 7fa6c67bcc9970ce2fa4b3f3a7f17042b9b4fd0e Author: Simon Peyton Jones Date: Thu Mar 6 12:13:17 2014 +0000 Trac #8569 fixed >--------------------------------------------------------------- 7fa6c67bcc9970ce2fa4b3f3a7f17042b9b4fd0e testsuite/tests/stranal/sigs/all.T | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/stranal/sigs/all.T b/testsuite/tests/stranal/sigs/all.T index 9d36479..9accd01 100644 --- a/testsuite/tests/stranal/sigs/all.T +++ b/testsuite/tests/stranal/sigs/all.T @@ -8,7 +8,7 @@ setTestOpts(extra_hc_opts('-ddump-strsigs')) setTestOpts(only_ways(['optasm'])) test('StrAnalExample', normal, compile, ['']) -test('T8569', expect_broken(8569), compile, ['']) +test('T8569', normal, compile, ['']) test('HyperStrUse', normal, compile, ['']) test('T8598', normal, compile, ['']) test('FacState', expect_broken(1600), compile, ['']) From git at git.haskell.org Fri Mar 7 06:00:37 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Mar 2014 06:00:37 +0000 (UTC) Subject: [commit: ghc] master: Test #8851. (1ac9114) Message-ID: <20140307060038.3CDE62406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1ac91146dc3431742eafd33ed4afc552ca17fb64/ghc >--------------------------------------------------------------- commit 1ac91146dc3431742eafd33ed4afc552ca17fb64 Author: Richard Eisenberg Date: Thu Mar 6 23:44:57 2014 -0500 Test #8851. >--------------------------------------------------------------- 1ac91146dc3431742eafd33ed4afc552ca17fb64 testsuite/tests/deriving/should_compile/T8851.hs | 24 ++++++++++++++++++++++ testsuite/tests/deriving/should_compile/all.T | 1 + 2 files changed, 25 insertions(+) diff --git a/testsuite/tests/deriving/should_compile/T8851.hs b/testsuite/tests/deriving/should_compile/T8851.hs new file mode 100644 index 0000000..84f0ad4 --- /dev/null +++ b/testsuite/tests/deriving/should_compile/T8851.hs @@ -0,0 +1,24 @@ +{-# LANGUAGE GeneralizedNewtypeDeriving #-} + +module T8851 where + +import Control.Applicative + +class Parsing m where + notFollowedBy :: (Monad m, Show a) => m a -> m () + +data Parser a +instance Parsing Parser where + notFollowedBy = undefined + +instance Functor Parser where + fmap = undefined +instance Applicative Parser where + pure = undefined + (<*>) = undefined +instance Monad Parser where + return = undefined + (>>=) = undefined + +newtype MyParser a = MkMP (Parser a) + deriving Parsing \ No newline at end of file diff --git a/testsuite/tests/deriving/should_compile/all.T b/testsuite/tests/deriving/should_compile/all.T index a7cc3df..8620c36 100644 --- a/testsuite/tests/deriving/should_compile/all.T +++ b/testsuite/tests/deriving/should_compile/all.T @@ -44,3 +44,4 @@ test('AutoDeriveTypeable', normal, compile, ['']) test('T8138', reqlib('primitive'), compile, ['-O2']) test('T8631', normal, compile, ['']) test('T8758', extra_clean(['T8758a.o', 'T8758a.hi']), multimod_compile, ['T8758a', '-v0']) +test('T8851', expect_broken(8851), compile, ['']) \ No newline at end of file From git at git.haskell.org Fri Mar 7 15:05:48 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Mar 2014 15:05:48 +0000 (UTC) Subject: [commit: ghc] master: Run testcase for 8124 only with threaded ways (0014fb3) Message-ID: <20140307150548.E2A542406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0014fb3dbf4a2096489a4800adf2d79a83a12274/ghc >--------------------------------------------------------------- commit 0014fb3dbf4a2096489a4800adf2d79a83a12274 Author: Joachim Breitner Date: Fri Mar 7 16:05:39 2014 +0100 Run testcase for 8124 only with threaded ways >--------------------------------------------------------------- 0014fb3dbf4a2096489a4800adf2d79a83a12274 testsuite/tests/rts/all.T | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/rts/all.T b/testsuite/tests/rts/all.T index d36cc21..f7c4986 100644 --- a/testsuite/tests/rts/all.T +++ b/testsuite/tests/rts/all.T @@ -200,7 +200,7 @@ test('T8209', [ only_ways(threaded_ways), ignore_output ], test('T8242', [ only_ways(threaded_ways), ignore_output ], compile_and_run, ['']) -test('T8124', [ omit_ways(prof_ways + ['ghci']), +test('T8124', [ only_ways(threaded_ways), omit_ways(['ghci']), extra_clean(['T8124_c.o']), pre_cmd('$MAKE -s --no-print-directory T8124_setup') ], # The T8124_setup hack is to ensure that we generate From git at git.haskell.org Fri Mar 7 15:54:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Mar 2014 15:54:24 +0000 (UTC) Subject: [commit: ghc] master: Make sync-all handle all github protocols correctly (3efcb0a) Message-ID: <20140307155425.00CCB2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3efcb0a7d147e05f86501783144bcd0ad3757e93/ghc >--------------------------------------------------------------- commit 3efcb0a7d147e05f86501783144bcd0ad3757e93 Author: Joachim Breitner Date: Fri Mar 7 16:50:43 2014 +0100 Make sync-all handle all github protocols correctly This fixes #8824. >--------------------------------------------------------------- 3efcb0a7d147e05f86501783144bcd0ad3757e93 sync-all | 8 +++++--- 1 file changed, 5 insertions(+), 3 deletions(-) diff --git a/sync-all b/sync-all index 469dabe..a585e9a 100755 --- a/sync-all +++ b/sync-all @@ -19,6 +19,8 @@ my $bare_flag = ""; # NOT the opposite of checked_out_flag (describes local repo my %tags; +my $GITHUB = qr!(?:git@|git://|https://)github.com!; + sub inDir { my $dir = shift; my $code = shift; @@ -262,7 +264,7 @@ sub gitall { my ($repo_base, $checked_out_tree, $repo_local) = getrepo(); - my $is_github_repo = $repo_base =~ m/(git@|git:\/\/|https:\/\/)github.com/; + my $is_github_repo = $repo_base =~ $GITHUB; @args = (); @@ -584,8 +586,8 @@ sub gitInitSubmodules { my $submodulespaths = &readgit(".", "config", "--get-regexp", "^submodule[.].*[.]url"); # if we came from github, change the urls appropriately - while ($submodulespaths =~ m!^(submodule.libraries/[a-zA-Z0-9]+.url) git://github.com/ghc/packages/([a-zA-Z0-9]+).git$!gm) { - &git(".", "config", $1, "git://github.com/ghc/packages-$2"); + while ($submodulespaths =~ m!^(submodule.libraries/[a-zA-Z0-9]+.url) ($GITHUB)/ghc/packages/([a-zA-Z0-9]+).git$!gm) { + &git(".", "config", $1, "$2/ghc/packages-$3"); } # if we came from a local repository, grab our submodules from their From git at git.haskell.org Fri Mar 7 16:52:49 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Mar 2014 16:52:49 +0000 (UTC) Subject: [commit: ghc] master: Make -XDeriveFunctor more generous about non-last arguments (Trac #8678) (cdac487) Message-ID: <20140307165249.B619D2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cdac487bcd9928d77738f6e79ead7b9bb4bc00fd/ghc >--------------------------------------------------------------- commit cdac487bcd9928d77738f6e79ead7b9bb4bc00fd Author: Simon Peyton Jones Date: Fri Mar 7 16:45:55 2014 +0000 Make -XDeriveFunctor more generous about non-last arguments (Trac #8678) When deriving Functor, Foldable, Traversable, we need only look at the way that the last type argument is treated. It's fine for there to be existentials etc, provided they don't affect the last type argument. See Note [Check that the type variable is truly universal] in TcDeriv. >--------------------------------------------------------------- cdac487bcd9928d77738f6e79ead7b9bb4bc00fd compiler/typecheck/TcDeriv.lhs | 88 +++++++++++++++----- compiler/typecheck/TcGenDeriv.lhs | 8 +- docs/users_guide/glasgow_exts.xml | 7 ++ testsuite/tests/deriving/should_compile/T8678.hs | 12 +++ testsuite/tests/deriving/should_compile/all.T | 1 + testsuite/tests/deriving/should_fail/T3101.stderr | 2 +- testsuite/tests/generics/GenCannotDoRep0_0.stderr | 3 +- testsuite/tests/generics/GenCannotDoRep1_0.stderr | 3 +- .../tests/typecheck/should_fail/tcfail086.stderr | 2 +- 9 files changed, 96 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 cdac487bcd9928d77738f6e79ead7b9bb4bc00fd From git at git.haskell.org Fri Mar 7 16:52:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Mar 2014 16:52:52 +0000 (UTC) Subject: [commit: ghc] master: Fix the treatment of lexically scoped kind variables (Trac #8856) (cf1a0f9) Message-ID: <20140307165252.76FC42406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cf1a0f971966af633fbd932ad012ce716680465b/ghc >--------------------------------------------------------------- commit cf1a0f971966af633fbd932ad012ce716680465b Author: Simon Peyton Jones Date: Fri Mar 7 16:50:17 2014 +0000 Fix the treatment of lexically scoped kind variables (Trac #8856) The issue here is described in Note [Binding scoped type variables] in TcPat. When implementing this fix I was able to make things quite a bit simpler: * The type variables in a type signature now never unify with each other, and so can be straightfoward skolems. * We only need the SigTv stuff for signatures in patterns, and for kind variables. >--------------------------------------------------------------- cf1a0f971966af633fbd932ad012ce716680465b compiler/typecheck/FamInst.lhs | 2 +- compiler/typecheck/TcBinds.lhs | 45 +++------------ compiler/typecheck/TcExpr.lhs | 9 ++- compiler/typecheck/TcMType.lhs | 49 ++++++---------- compiler/typecheck/TcPat.lhs | 60 ++++++++++++++++---- compiler/typecheck/TcPatSyn.lhs | 2 +- compiler/typecheck/TcType.lhs | 36 +++++------- compiler/vectorise/Vectorise/Generic/PData.hs | 2 +- testsuite/tests/typecheck/should_compile/MutRec.hs | 11 ++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 10 files changed, 107 insertions(+), 110 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc cf1a0f971966af633fbd932ad012ce716680465b From git at git.haskell.org Fri Mar 7 17:15:36 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 7 Mar 2014 17:15:36 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #8856 (062391b) Message-ID: <20140307171536.DA9F12406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/062391be4f06aa408187582c4a40f1cea80429c3/ghc >--------------------------------------------------------------- commit 062391be4f06aa408187582c4a40f1cea80429c3 Author: Simon Peyton Jones Date: Fri Mar 7 17:15:15 2014 +0000 Test Trac #8856 >--------------------------------------------------------------- 062391be4f06aa408187582c4a40f1cea80429c3 testsuite/tests/typecheck/should_compile/T8856.hs | 6 ++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 2 files changed, 7 insertions(+) diff --git a/testsuite/tests/typecheck/should_compile/T8856.hs b/testsuite/tests/typecheck/should_compile/T8856.hs new file mode 100644 index 0000000..6605e47 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T8856.hs @@ -0,0 +1,6 @@ +{-# LANGUAGE ScopedTypeVariables, RankNTypes, PolyKinds #-} +module T8856 where + +import Data.Proxy + +foo = (undefined :: Proxy a) :: forall a. Proxy a diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index 35b5dd2..373e739 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -417,3 +417,4 @@ test('T8565', normal, compile, ['']) test('T8644', normal, compile, ['']) test('T8762', normal, compile, ['']) test('MutRec', normal, compile, ['']) +test('T8856', normal, compile, ['']) From git at git.haskell.org Sat Mar 8 00:11:51 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Mar 2014 00:11:51 +0000 (UTC) Subject: [commit: ghc] master: Also allow http://github.com (#8824) (d246c62) Message-ID: <20140308001151.4B1412406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d246c62afd7312185aee9433b065ea99e4fa4054/ghc >--------------------------------------------------------------- commit d246c62afd7312185aee9433b065ea99e4fa4054 Author: Joachim Breitner Date: Sat Mar 8 01:11:42 2014 +0100 Also allow http://github.com (#8824) >--------------------------------------------------------------- d246c62afd7312185aee9433b065ea99e4fa4054 sync-all | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/sync-all b/sync-all index a585e9a..4b4b7a3 100755 --- a/sync-all +++ b/sync-all @@ -19,7 +19,7 @@ my $bare_flag = ""; # NOT the opposite of checked_out_flag (describes local repo my %tags; -my $GITHUB = qr!(?:git@|git://|https://)github.com!; +my $GITHUB = qr!(?:git@|git://|https://|http://)github.com!; sub inDir { my $dir = shift; From git at git.haskell.org Sat Mar 8 21:14:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 8 Mar 2014 21:14:47 +0000 (UTC) Subject: [commit: haddock] master: Render fixity information (17970e6) Message-ID: <20140308211447.DF32A2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : master Link : http://git.haskell.org/haddock.git/commitdiff/17970e6b6aa22962c498ce02ead8dbadad31a733 >--------------------------------------------------------------- commit 17970e6b6aa22962c498ce02ead8dbadad31a733 Author: Niklas Haas Date: Sat Mar 8 09:42:00 2014 +0100 Render fixity information Affects functions, type synonyms, type families, class names, data type names, constructors, data families, associated TFs/DFs, type synonyms, pattern synonyms and everything else I could think of. >--------------------------------------------------------------- 17970e6b6aa22962c498ce02ead8dbadad31a733 html-test/ref/Bug8.html | 6 +- html-test/ref/Operators.html | 379 +++++++++++++++++++++++++++++++++++ html-test/src/Operators.hs | 56 ++++++ src/Haddock/Backends/Hoogle.hs | 2 +- src/Haddock/Backends/LaTeX.hs | 11 +- src/Haddock/Backends/Xhtml.hs | 10 +- src/Haddock/Backends/Xhtml/Decl.hs | 175 +++++++++------- src/Haddock/Backends/Xhtml/Utils.hs | 17 +- src/Haddock/Interface/Create.hs | 53 +++-- src/Haddock/Interface/Rename.hs | 10 +- src/Haddock/Types.hs | 6 + 11 files changed, 621 insertions(+), 104 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 17970e6b6aa22962c498ce02ead8dbadad31a733 From git at git.haskell.org Sun Mar 9 06:54:25 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 9 Mar 2014 06:54:25 +0000 (UTC) Subject: [commit: haddock] master: Reorder topDeclElem to move the source/wiki links to the top (843c42c) Message-ID: <20140309065425.22E2F2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : master Link : http://git.haskell.org/haddock.git/commitdiff/843c42c4179526a2ad3526e4c7d38cbf4d50001d >--------------------------------------------------------------- commit 843c42c4179526a2ad3526e4c7d38cbf4d50001d Author: Niklas Haas Date: Sun Mar 9 07:43:39 2014 +0100 Reorder topDeclElem to move the source/wiki links to the top They appear in the same position due to the float: right attribute but now they're always at the top of the box instead of at the bottom. >--------------------------------------------------------------- 843c42c4179526a2ad3526e4c7d38cbf4d50001d src/Haddock/Backends/Xhtml/Layout.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Haddock/Backends/Xhtml/Layout.hs b/src/Haddock/Backends/Xhtml/Layout.hs index dbc043b..9a0e461 100644 --- a/src/Haddock/Backends/Xhtml/Layout.hs +++ b/src/Haddock/Backends/Xhtml/Layout.hs @@ -192,7 +192,7 @@ declElem = paragraph ! [theclass "src"] -- it adds a source and wiki link at the right hand side of the box topDeclElem :: LinksInfo -> SrcSpan -> [DocName] -> Html -> Html topDeclElem ((_,_,sourceMap), (_,_,maybe_wiki_url)) loc names html = - declElem << (html <+> srcLink <+> wikiLink) + declElem << (srcLink <+> wikiLink <+> html) where srcLink = case Map.lookup origPkg sourceMap of Nothing -> noHtml From git at git.haskell.org Sun Mar 9 07:12:18 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 9 Mar 2014 07:12:18 +0000 (UTC) Subject: [commit: haddock] master: Differentiate between TH splices (line-links) and regular names (003f117) Message-ID: <20140309071218.6C0732406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : master Link : http://git.haskell.org/haddock.git/commitdiff/003f11795e4413abae5275e8a855765c571ccab9 >--------------------------------------------------------------- commit 003f11795e4413abae5275e8a855765c571ccab9 Author: Niklas Haas Date: Sun Mar 9 06:07:09 2014 +0100 Differentiate between TH splices (line-links) and regular names This adds a new type of source code link, to a specific line rather than a specific declaration/name - this is used to link to the location of a TH splice that defines a certain name. Rather hefty changes throughout and still one unresolved issue (the line URLs aren't parsed from the third form of --read-interface which means they're currently restricted to same-interface links). Not sure if this issue is really worth all the hassle, especially since we could just use line links in general. This commit also contains some cleanup/clarification of the types in Haddock.Backends.Xhtml.Decl and shortens some overlong lines in the process. Notably, the Bool parameter was replaced by a Unicode type synonym to help clarify its presence in type signatures. >--------------------------------------------------------------- 003f11795e4413abae5275e8a855765c571ccab9 src/Haddock.hs | 6 +- src/Haddock/Backends/Hoogle.hs | 2 +- src/Haddock/Backends/LaTeX.hs | 6 +- src/Haddock/Backends/Xhtml.hs | 14 +-- src/Haddock/Backends/Xhtml/Decl.hs | 195 ++++++++++++++++++---------------- src/Haddock/Backends/Xhtml/Layout.hs | 12 ++- src/Haddock/Backends/Xhtml/Types.hs | 12 ++- src/Haddock/Interface/Create.hs | 49 +++++---- src/Haddock/Interface/Rename.hs | 4 +- src/Haddock/Options.hs | 18 ++-- src/Haddock/Types.hs | 4 + 11 files changed, 182 insertions(+), 140 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 003f11795e4413abae5275e8a855765c571ccab9 From git at git.haskell.org Sun Mar 9 07:12:20 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 9 Mar 2014 07:12:20 +0000 (UTC) Subject: [commit: haddock] master: Use optLast instead of listToMaybe for sourceUrls/wikiUrls (9aa5a2a) Message-ID: <20140309071220.50B852406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : master Link : http://git.haskell.org/haddock.git/commitdiff/9aa5a2a420788e39806c5fe85845002181f3b945 >--------------------------------------------------------------- commit 9aa5a2a420788e39806c5fe85845002181f3b945 Author: Niklas Haas Date: Sat Mar 8 23:58:38 2014 +0100 Use optLast instead of listToMaybe for sourceUrls/wikiUrls This lets you override them using eg. cabal haddock --haddock-options, which can come in handy if you want to use a different layout or URL for your source code links than cabal-install generates. >--------------------------------------------------------------- 9aa5a2a420788e39806c5fe85845002181f3b945 src/Haddock/Options.hs | 13 ++++++------- 1 file changed, 6 insertions(+), 7 deletions(-) diff --git a/src/Haddock/Options.hs b/src/Haddock/Options.hs index 12c80b6..2e10827 100644 --- a/src/Haddock/Options.hs +++ b/src/Haddock/Options.hs @@ -32,7 +32,6 @@ module Haddock.Options ( ) where -import Data.Maybe import Distribution.Verbosity import Haddock.Utils import Haddock.Types @@ -219,16 +218,16 @@ optCssFile flags = optLast [ str | Flag_CSS str <- flags ] sourceUrls :: [Flag] -> (Maybe String, Maybe String, Maybe String) sourceUrls flags = - (listToMaybe [str | Flag_SourceBaseURL str <- flags] - ,listToMaybe [str | Flag_SourceModuleURL str <- flags] - ,listToMaybe [str | Flag_SourceEntityURL str <- flags]) + (optLast [str | Flag_SourceBaseURL str <- flags] + ,optLast [str | Flag_SourceModuleURL str <- flags] + ,optLast [str | Flag_SourceEntityURL str <- flags]) wikiUrls :: [Flag] -> (Maybe String, Maybe String, Maybe String) wikiUrls flags = - (listToMaybe [str | Flag_WikiBaseURL str <- flags] - ,listToMaybe [str | Flag_WikiModuleURL str <- flags] - ,listToMaybe [str | Flag_WikiEntityURL str <- flags]) + (optLast [str | Flag_WikiBaseURL str <- flags] + ,optLast [str | Flag_WikiModuleURL str <- flags] + ,optLast [str | Flag_WikiEntityURL str <- flags]) optDumpInterfaceFile :: [Flag] -> Maybe FilePath From git at git.haskell.org Mon Mar 10 04:20:13 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 10 Mar 2014 04:20:13 +0000 (UTC) Subject: [commit: haddock] master: Group similar fixities together (68a7893) Message-ID: <20140310042013.0CD2F2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : master Link : http://git.haskell.org/haddock.git/commitdiff/68a78932b5b004945f6681bd51e8080e868fc0ee >--------------------------------------------------------------- commit 68a78932b5b004945f6681bd51e8080e868fc0ee Author: Niklas Haas Date: Sun Mar 9 16:32:36 2014 +0100 Group similar fixities together Identical fixities declared for the same line should now render using syntax like: infix 4 <, >=, >, <= >--------------------------------------------------------------- 68a78932b5b004945f6681bd51e8080e868fc0ee html-test/ref/Operators.html | 33 ++++++++++++++++++++++++++++++++- html-test/src/Operators.hs | 10 +++++++++- src/Haddock/Backends/Xhtml/Decl.hs | 13 ++++++++++--- 3 files changed, 51 insertions(+), 5 deletions(-) diff --git a/html-test/ref/Operators.html b/html-test/ref/Operators.html index 89ebbbb..fdc46aa 100644 --- a/html-test/ref/Operators.html +++ b/html-test/ref/Operators.html @@ -144,7 +144,19 @@ window.onload = function () {pageLoad();setSynopsis("mini_Operators.html");}; >
  • (>><), (<<>) :: a -> b -> ()
  • (**>), (<**), (>**), (**<) :: a -> a -> ()
  • Methods

    infixr 4 >><
    infixl 5 <<>
    infixr 4 >><
    (>><), (<<>) :: a -> b -> ()

    infixr 8 **>, >**
    infixl 8 <**, **<
    (**>), (<**), (>**), (**<) :: a -> a -> ()

    Multiple fixities

    <> b where type a <>< b :: * data a ><< b - (>><) :: a -> b -> () + (>><), (<<>) :: a -> b -> () + + -- | Multiple fixities + (**>), (**<), (>**), (<**) :: a -> a -> () + infixr 1 ><> infixl 2 <>< infixl 3 ><< infixr 4 >>< +infixl 5 <<> + +infixr 8 **>, >** +infixl 8 **<, <** -- | Type synonym with fixity type (a >-< b) = a <-> b diff --git a/src/Haddock/Backends/Xhtml/Decl.hs b/src/Haddock/Backends/Xhtml/Decl.hs index 5cc86d4..42f0628 100644 --- a/src/Haddock/Backends/Xhtml/Decl.hs +++ b/src/Haddock/Backends/Xhtml/Decl.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE TransformListComp #-} ----------------------------------------------------------------------------- -- | -- Module : Haddock.Backends.Html.Decl @@ -34,6 +35,7 @@ import Data.Monoid ( mempty ) import Text.XHtml hiding ( name, title, p, quote ) import GHC +import GHC.Exts import Name @@ -158,15 +160,20 @@ ppTypeOrFunSig summary links loc docnames typ (doc, argDocs) (pref1, pref2, sep) = [(leader <+> ppType unicode qual t, argDoc n, [])] ppFixities :: [(DocName, Fixity)] -> Qualification -> Html -ppFixities fs qual = vcat $ map ppFix fs +ppFixities fs qual = vcat $ map ppFix uniq_fs where - ppFix (n, Fixity p d) = toHtml (ppDir d) <+> toHtml (show p) - <+> ppDocName qual Infix False n + ppFix (ns, p, d) = toHtml d <+> toHtml (show p) <+> ppNames ns ppDir InfixR = "infixr" ppDir InfixL = "infixl" ppDir InfixN = "infix" + ppNames = concatHtml . intersperse (stringToHtml ", ") . map (ppDocName qual Infix False) + + uniq_fs = [ (n, the p, the d') | (n, Fixity p d) <- fs + , let d' = ppDir d + , then group by Down (p,d') using groupWith ] + ppTyVars :: LHsTyVarBndrs DocName -> [Html] ppTyVars tvs = map ppTyName (tyvarNames tvs) From git at git.haskell.org Mon Mar 10 04:27:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 10 Mar 2014 04:27:50 +0000 (UTC) Subject: [commit: haddock] master: Update changelog (c40ee25) Message-ID: <20140310042750.6489C2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : master Link : http://git.haskell.org/haddock.git/commitdiff/c40ee25c4a9cc4952b237d1b5a659eaeb0023c05 >--------------------------------------------------------------- commit c40ee25c4a9cc4952b237d1b5a659eaeb0023c05 Author: Mateusz Kowalczyk Date: Mon Mar 10 04:24:18 2014 +0000 Update changelog >--------------------------------------------------------------- c40ee25c4a9cc4952b237d1b5a659eaeb0023c05 CHANGES | 9 +++++++++ 1 file changed, 9 insertions(+) diff --git a/CHANGES b/CHANGES index f548d03..ff86401 100644 --- a/CHANGES +++ b/CHANGES @@ -31,6 +31,15 @@ Changes in version 2.14.0 * Fix display of poly-kinded type operators + * PatternSynonyms support + + * Fix display of implicit parameters (#260) + + * Fix rendering of Contents when links are present (#276) + + * Fix documentation duplication on record fields (#195) + + Changes in version 2.13.2 * Handle HsExplicitListTy in renamer (#213) From git at git.haskell.org Mon Mar 10 11:11:38 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 10 Mar 2014 11:11:38 +0000 (UTC) Subject: [commit: ghc] master: Improve documentation of standalone deriving (c.f. Trac #8851) (9d14262) Message-ID: <20140310111138.7AED72406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9d14262299fe721e49eb0efadebca9d095c834b3/ghc >--------------------------------------------------------------- commit 9d14262299fe721e49eb0efadebca9d095c834b3 Author: Simon Peyton Jones Date: Mon Mar 10 11:08:37 2014 +0000 Improve documentation of standalone deriving (c.f. Trac #8851) >--------------------------------------------------------------- 9d14262299fe721e49eb0efadebca9d095c834b3 docs/users_guide/glasgow_exts.xml | 28 +++++++++++++++++++++------- 1 file changed, 21 insertions(+), 7 deletions(-) diff --git a/docs/users_guide/glasgow_exts.xml b/docs/users_guide/glasgow_exts.xml index dc1fbb5..4217b7d 100644 --- a/docs/users_guide/glasgow_exts.xml +++ b/docs/users_guide/glasgow_exts.xml @@ -3752,8 +3752,16 @@ GHC now allows stand-alone deriving declarations, enabled by The syntax is identical to that of an ordinary instance declaration apart from (a) the keyword deriving, and (b) the absence of the where part. -Note the following points: + + +However, standalone deriving differs from a deriving clause in a number +of important ways: +The standalone deriving declaration does not need to be in the +same module as the data type declaration. (But be aware of the dangers of +orphan instances (). + + You must supply an explicit context (in the example the context is (Eq a)), exactly as you would in an ordinary instance declaration. @@ -3762,12 +3770,6 @@ attached to a data type declaration, the context is inferred.) -A deriving instance declaration -must obey the same rules concerning form and termination as ordinary instance declarations, -controlled by the same flags; see . - - - Unlike a deriving declaration attached to a data declaration, the instance can be more specific than the data type (assuming you also use @@ -3789,6 +3791,8 @@ declaration attached to a data declaration, GHC does not restrict the form of the data type. Instead, GHC simply generates the appropriate boilerplate code for the specified class, and typechecks it. If there is a type error, it is your problem. (GHC will show you the offending code if it has a type error.) + + The merit of this is that you can derive instances for GADTs and other exotic data types, providing only that the boilerplate code does indeed typecheck. For example: @@ -3811,6 +3815,16 @@ the side-conditions are necessarily more conservative, but any error message may be more comprehensible. + + + +In other ways, however, a standalone deriving obeys the same rules as ordinary deriving: + + +A deriving instance declaration +must obey the same rules concerning form and termination as ordinary instance declarations, +controlled by the same flags; see . + The stand-alone syntax is generalised for newtypes in exactly the same From git at git.haskell.org Mon Mar 10 11:11:41 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 10 Mar 2014 11:11:41 +0000 (UTC) Subject: [commit: ghc] master: Unify, rather than match, in GND processing (fixes Trac #8865) (f521a26) Message-ID: <20140310111141.386972406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f521a26cb741409011137115d17232df901c3c94/ghc >--------------------------------------------------------------- commit f521a26cb741409011137115d17232df901c3c94 Author: Simon Peyton Jones Date: Mon Mar 10 11:10:21 2014 +0000 Unify, rather than match, in GND processing (fixes Trac #8865) Yet another small way in which polymorphic kinds needs a bit of care See Note [Unify kinds in deriving] in TcDeriv >--------------------------------------------------------------- f521a26cb741409011137115d17232df901c3c94 compiler/ghci/RtClosureInspect.hs | 3 +- compiler/typecheck/TcDeriv.lhs | 49 ++++++++++++++-------- compiler/types/Unify.lhs | 21 ++++++---- testsuite/tests/deriving/should_compile/T8865.hs | 11 +++++ testsuite/tests/deriving/should_compile/all.T | 1 + 5 files changed, 59 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 f521a26cb741409011137115d17232df901c3c94 From git at git.haskell.org Mon Mar 10 17:57:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 10 Mar 2014 17:57:50 +0000 (UTC) Subject: [commit: ghc] master: Add "bench" build flavour to build system (ddf79eb) Message-ID: <20140310175751.C66D82406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ddf79ebf69fe4a6e69d69d451a6040a53b1ea12c/ghc >--------------------------------------------------------------- commit ddf79ebf69fe4a6e69d69d451a6040a53b1ea12c Author: Johan Tibell Date: Mon Mar 10 18:54:47 2014 +0100 Add "bench" build flavour to build system This build generates the same code as the "perf" build and is thus good for compiling benchmarks and inspecting the generated code. However, it compiles the stage2 compiler faster at the expense of compiler user programs more slowly. >--------------------------------------------------------------- ddf79ebf69fe4a6e69d69d451a6040a53b1ea12c mk/build.mk.sample | 64 ++++++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 64 insertions(+) diff --git a/mk/build.mk.sample b/mk/build.mk.sample index cb049ba..a16eb0f 100644 --- a/mk/build.mk.sample +++ b/mk/build.mk.sample @@ -40,6 +40,17 @@ # A development build, working on the stage 2 compiler: #BuildFlavour = devel2 +# A build with max optimisation that still builds the stage2 compiler +# quickly. Compiled code will be the same as with "perf". Programs +# will compile more slowly. +#BuildFlavour = bench + +# As above but build GHC using the LLVM backend +#BuildFlavour = bench-llvm + +# Bench build configured for a cross-compiler +#BuildFlavour = bench-cross + # -------- Miscellaneous variables -------------------------------------------- # Set to V = 0 to get prettier build output. @@ -235,6 +246,59 @@ LAX_DEPENDENCIES = YES endif +# -------- A bench build with optimised libs ----------------------------------- + +ifeq "$(BuildFlavour)" "bench" + +SRC_HC_OPTS = -O -H64m +GhcStage1HcOpts = -O -fasm +GhcStage2HcOpts = -O0 -fasm +GhcLibHcOpts = -O2 -fasm +SplitObjs = NO +HADDOCK_DOCS = NO +BUILD_DOCBOOK_HTML = NO +BUILD_DOCBOOK_PS = NO +BUILD_DOCBOOK_PDF = NO + +endif + +# ---------------- Perf build using LLVM -------------------------------------- + +ifeq "$(BuildFlavour)" "bench-llvm" + +SRC_HC_OPTS = -O -H64m +GhcStage1HcOpts = -O -fllvm +GhcStage2HcOpts = -O0 -fllvm +GhcLibHcOpts = -O2 -fllvm +SplitObjs = NO +HADDOCK_DOCS = NO +BUILD_DOCBOOK_HTML = NO +BUILD_DOCBOOK_PS = NO +BUILD_DOCBOOK_PDF = NO + +endif + +# ------- A Perf build configured for cross-compilation ---------------------- + +ifeq "$(BuildFlavour)" "bench-cross" + +SRC_HC_OPTS = -O -H64m +GhcStage1HcOpts = -O -fasm +GhcStage2HcOpts = -O0 -fasm +GhcLibHcOpts = -O2 -fasm +SplitObjs = NO +INTEGER_LIBRARY = integer-simple +Stage1Only = YES +HADDOCK_DOCS = NO +BUILD_DOCBOOK_HTML = NO +BUILD_DOCBOOK_PS = NO +BUILD_DOCBOOK_PDF = NO + +DYNAMIC_BY_DEFAULT = NO +DYNAMIC_GHC_PROGRAMS = NO + +endif + # ----------------------------------------------------------------------------- # Other settings that might be useful From git at git.haskell.org Mon Mar 10 17:59:30 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 10 Mar 2014 17:59:30 +0000 (UTC) Subject: [commit: ghc] master: Fix copy-paste error in build system comment (9c9bb00) Message-ID: <20140310175930.DF9FA2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9c9bb00343c2ab4c985bf248b576106ea8fa5a3d/ghc >--------------------------------------------------------------- commit 9c9bb00343c2ab4c985bf248b576106ea8fa5a3d Author: Johan Tibell Date: Mon Mar 10 18:59:21 2014 +0100 Fix copy-paste error in build system comment >--------------------------------------------------------------- 9c9bb00343c2ab4c985bf248b576106ea8fa5a3d mk/build.mk.sample | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/mk/build.mk.sample b/mk/build.mk.sample index a16eb0f..3d47bbe 100644 --- a/mk/build.mk.sample +++ b/mk/build.mk.sample @@ -262,7 +262,7 @@ BUILD_DOCBOOK_PDF = NO endif -# ---------------- Perf build using LLVM -------------------------------------- +# ---------------- Bench build using LLVM -------------------------------------- ifeq "$(BuildFlavour)" "bench-llvm" @@ -278,7 +278,7 @@ BUILD_DOCBOOK_PDF = NO endif -# ------- A Perf build configured for cross-compilation ---------------------- +# ------- A Bench build configured for cross-compilation ---------------------- ifeq "$(BuildFlavour)" "bench-cross" From git at git.haskell.org Tue Mar 11 09:49:06 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Mar 2014 09:49:06 +0000 (UTC) Subject: [commit: haddock] master: Update changelog (3f6c34a) Message-ID: <20140311094906.13C762406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : master Link : http://git.haskell.org/haddock.git/commitdiff/3f6c34a3cb23d046486c2a58cdf197b9959a4983 >--------------------------------------------------------------- commit 3f6c34a3cb23d046486c2a58cdf197b9959a4983 Author: Niklas Haas Date: Mon Mar 10 21:32:58 2014 +0100 Update changelog >--------------------------------------------------------------- 3f6c34a3cb23d046486c2a58cdf197b9959a4983 CHANGES | 9 ++++++++- 1 file changed, 8 insertions(+), 1 deletion(-) diff --git a/CHANGES b/CHANGES index ff86401..e34701c 100644 --- a/CHANGES +++ b/CHANGES @@ -29,7 +29,7 @@ Changes in version 2.14.0 * Print type/data family instances - * Fix display of poly-kinded type operators + * Fix display of poly-kinded type operators (#189) * PatternSynonyms support @@ -39,6 +39,13 @@ Changes in version 2.14.0 * Fix documentation duplication on record fields (#195) + * Add `--source-entity-line` for exact line links (eg. things defined + inside TH splices) (#79) + + * Display fixity information for names with nonstandard fixities + + * Bird tracks specified like "> code" no longer suffer from an extra leading + space in the code output Changes in version 2.13.2 From git at git.haskell.org Tue Mar 11 09:49:08 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Mar 2014 09:49:08 +0000 (UTC) Subject: [commit: haddock] master: Update appearance of fixity annotations (72f655f) Message-ID: <20140311094908.335352406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : master Link : http://git.haskell.org/haddock.git/commitdiff/72f655f5a4429403674521d251e6cccf62d76747 >--------------------------------------------------------------- commit 72f655f5a4429403674521d251e6cccf62d76747 Author: Niklas Haas Date: Tue Mar 11 07:21:03 2014 +0100 Update appearance of fixity annotations This moves them in-line with their corresponding lines, similar to a presentation envision by @hvr and described in #ghc. Redundant operator names are also omitted when no ambiguity is present. >--------------------------------------------------------------- 72f655f5a4429403674521d251e6cccf62d76747 html-test/ref/Bug8.html | 20 +++-- html-test/ref/Operators.html | 133 ++++++++++++++++++++---------- resources/html/Ocean.std-theme/ocean.css | 13 +++ src/Haddock/Backends/Xhtml/Decl.hs | 42 ++++++---- 4 files changed, 141 insertions(+), 67 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 72f655f5a4429403674521d251e6cccf62d76747 From git at git.haskell.org Tue Mar 11 09:49:10 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Mar 2014 09:49:10 +0000 (UTC) Subject: [commit: haddock] master: Include fixity information in the Interface file (28e685d) Message-ID: <20140311094910.3F81D2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : master Link : http://git.haskell.org/haddock.git/commitdiff/28e685d2589e4cd6847c21fe45a3b702c15090ea >--------------------------------------------------------------- commit 28e685d2589e4cd6847c21fe45a3b702c15090ea Author: Niklas Haas Date: Mon Mar 10 21:03:22 2014 +0100 Include fixity information in the Interface file This resolves fixity information not appearing across package borders. The binary file version has been increased accordingly. >--------------------------------------------------------------- 28e685d2589e4cd6847c21fe45a3b702c15090ea src/Haddock/Interface/AttachInstances.hs | 55 ++++++++++++++++-------------- src/Haddock/Interface/Create.hs | 1 + src/Haddock/InterfaceFile.hs | 11 +++--- src/Haddock/Types.hs | 3 ++ 4 files changed, 40 insertions(+), 30 deletions(-) diff --git a/src/Haddock/Interface/AttachInstances.hs b/src/Haddock/Interface/AttachInstances.hs index 8c9d45c..88512c1 100644 --- a/src/Haddock/Interface/AttachInstances.hs +++ b/src/Haddock/Interface/AttachInstances.hs @@ -16,10 +16,12 @@ module Haddock.Interface.AttachInstances (attachInstances) where import Haddock.Types import Haddock.Convert +import Haddock.GhcUtils import Control.Arrow import Data.List import Data.Ord (comparing) +import Data.Function (on) import qualified Data.Map as Map import qualified Data.Set as Set @@ -45,6 +47,7 @@ type ExportedNames = Set.Set Name type Modules = Set.Set Module type ExportInfo = (ExportedNames, Modules) +-- Also attaches fixities attachInstances :: ExportInfo -> [Interface] -> InstIfaceMap -> Ghc [Interface] attachInstances expInfo ifaces instIfaceMap = mapM attach ifaces where @@ -59,19 +62,19 @@ attachInstances expInfo ifaces instIfaceMap = mapM attach ifaces attachToExportItem :: ExportInfo -> Interface -> IfaceMap -> InstIfaceMap -> ExportItem Name -> Ghc (ExportItem Name) attachToExportItem expInfo iface ifaceMap instIfaceMap export = - case export of - ExportDecl { expItemDecl = L _ (TyClD d) } -> do + case attachFixities export of + e at ExportDecl { expItemDecl = L _ (TyClD d) } -> do mb_info <- getAllInfo (tcdName d) let export' = - export { + e { expItemInstances = case mb_info of Just (_, _, cls_instances, fam_instances) -> let fam_insts = [ (synifyFamInst i, n) | i <- sortBy (comparing instFam) fam_instances - , let n = lookupInstDoc (getName i) iface ifaceMap instIfaceMap + , let n = instLookup instDocMap (getName i) iface ifaceMap instIfaceMap ] - cls_insts = [ (synifyInstHead i, lookupInstDoc n iface ifaceMap instIfaceMap) + cls_insts = [ (synifyInstHead i, instLookup instDocMap n iface ifaceMap instIfaceMap) | let is = [ (instanceHead' i, getName i) | i <- cls_instances ] , (i@(_,_,cls,tys), n) <- sortBy (comparing $ first instHead) is , not $ isInstanceHidden expInfo cls tys @@ -80,28 +83,28 @@ attachToExportItem expInfo iface ifaceMap instIfaceMap export = Nothing -> [] } return export' - _ -> return export - - -lookupInstDoc :: Name -> Interface -> IfaceMap -> InstIfaceMap -> Maybe (Doc Name) --- TODO: capture this pattern in a function (when we have streamlined the --- handling of instances) -lookupInstDoc name iface ifaceMap instIfaceMap = - case Map.lookup name (ifaceDocMap iface) of - Just doc -> Just doc - Nothing -> - case Map.lookup modName ifaceMap of - Just iface2 -> - case Map.lookup name (ifaceDocMap iface2) of - Just doc -> Just doc - Nothing -> Nothing - Nothing -> - case Map.lookup modName instIfaceMap of - Just instIface -> Map.lookup name (instDocMap instIface) - Nothing -> Nothing + e -> return e where - modName = nameModule name - + attachFixities e at ExportDecl{ expItemDecl = L _ d } = e { expItemFixities = + nubBy ((==) `on` fst) $ expItemFixities e ++ + [ (n',f) | n <- getMainDeclBinder d + , Just subs <- [instLookup instSubMap n iface ifaceMap instIfaceMap] + , n' <- n : subs + , Just f <- [instLookup instFixMap n' iface ifaceMap instIfaceMap] + ] } + + attachFixities e = e + + +instLookup :: (InstalledInterface -> Map.Map Name a) -> Name + -> Interface -> IfaceMap -> InstIfaceMap -> Maybe a +instLookup f name iface ifaceMap instIfaceMap = + case Map.lookup name (f $ toInstalledIface iface) of + res@(Just _) -> res + Nothing -> do + let ifaceMaps = Map.union (fmap toInstalledIface ifaceMap) instIfaceMap + iface' <- Map.lookup (nameModule name) ifaceMaps + Map.lookup name (f iface') -- | Like GHC's 'instanceHead' but drops "silent" arguments. instanceHead' :: ClsInst -> ([TyVar], ThetaType, Class, [Type]) diff --git a/src/Haddock/Interface/Create.hs b/src/Haddock/Interface/Create.hs index e23e992..aef2cd8 100644 --- a/src/Haddock/Interface/Create.hs +++ b/src/Haddock/Interface/Create.hs @@ -141,6 +141,7 @@ createInterface tm flags modMap instIfaceMap = do , ifaceVisibleExports = visibleNames , ifaceDeclMap = declMap , ifaceSubMap = subMap + , ifaceFixMap = fixMap , ifaceModuleAliases = aliases , ifaceInstances = instances , ifaceFamInstances = fam_instances diff --git a/src/Haddock/InterfaceFile.hs b/src/Haddock/InterfaceFile.hs index b4d5406..924829d 100644 --- a/src/Haddock/InterfaceFile.hs +++ b/src/Haddock/InterfaceFile.hs @@ -77,7 +77,7 @@ binaryInterfaceMagic = 0xD0Cface -- binaryInterfaceVersion :: Word16 #if __GLASGOW_HASKELL__ == 709 -binaryInterfaceVersion = 24 +binaryInterfaceVersion = 25 binaryInterfaceVersionCompatibility :: [Word16] binaryInterfaceVersionCompatibility = [binaryInterfaceVersion] @@ -365,15 +365,17 @@ instance Binary InterfaceFile where instance Binary InstalledInterface where - put_ bh (InstalledInterface modu info docMap argMap exps visExps opts subMap) = do + put_ bh (InstalledInterface modu info docMap argMap + exps visExps opts subMap fixMap) = do put_ bh modu put_ bh info put_ bh docMap - put_ bh argMap + put_ bh argMap put_ bh exps put_ bh visExps put_ bh opts put_ bh subMap + put_ bh fixMap get bh = do modu <- get bh @@ -384,9 +386,10 @@ instance Binary InstalledInterface where visExps <- get bh opts <- get bh subMap <- get bh + fixMap <- get bh return (InstalledInterface modu info docMap argMap - exps visExps opts subMap) + exps visExps opts subMap fixMap) instance Binary DocOption where diff --git a/src/Haddock/Types.hs b/src/Haddock/Types.hs index 179413e..9538f3b 100644 --- a/src/Haddock/Types.hs +++ b/src/Haddock/Types.hs @@ -100,6 +100,7 @@ data Interface = Interface , ifaceRnArgMap :: !(ArgMap DocName) , ifaceSubMap :: !(Map Name [Name]) + , ifaceFixMap :: !(Map Name Fixity) , ifaceExportItems :: ![ExportItem Name] , ifaceRnExportItems :: ![ExportItem DocName] @@ -158,6 +159,7 @@ data InstalledInterface = InstalledInterface , instOptions :: [DocOption] , instSubMap :: Map Name [Name] + , instFixMap :: Map Name Fixity } @@ -172,6 +174,7 @@ toInstalledIface interface = InstalledInterface , instVisibleExports = ifaceVisibleExports interface , instOptions = ifaceOptions interface , instSubMap = ifaceSubMap interface + , instFixMap = ifaceFixMap interface } From git at git.haskell.org Tue Mar 11 09:49:12 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Mar 2014 09:49:12 +0000 (UTC) Subject: [commit: haddock] master: Add documentation for --source-entity-line (b999504) Message-ID: <20140311094912.4BA052406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : master Link : http://git.haskell.org/haddock.git/commitdiff/b9995041b5c838d41ba14ff684d9f5bfacd9ffc4 >--------------------------------------------------------------- commit b9995041b5c838d41ba14ff684d9f5bfacd9ffc4 Author: Niklas Haas Date: Tue Mar 11 09:11:21 2014 +0100 Add documentation for --source-entity-line >--------------------------------------------------------------- b9995041b5c838d41ba14ff684d9f5bfacd9ffc4 doc/haddock.xml | 7 +++++++ 1 file changed, 7 insertions(+) diff --git a/doc/haddock.xml b/doc/haddock.xml index 5bc27ac..da0c545 100644 --- a/doc/haddock.xml +++ b/doc/haddock.xml @@ -539,6 +539,10 @@ $ pdflatex package.tex =URL + + + =URL + Include links to the source files in the generated documentation. Use the option to add a @@ -547,6 +551,9 @@ $ pdflatex package.tex the header bar of each module page. Use the option to add a source code link next to the documentation for every value and type in each module. + is a flag that gets used for + entities that need to link to an exact source location rather than a + name, eg. since they were defined inside a Template Haskell splice. In each case URL is the base URL From git at git.haskell.org Tue Mar 11 09:49:14 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Mar 2014 09:49:14 +0000 (UTC) Subject: [commit: haddock] master: Filter family instances of hidden types (b8efaf4) Message-ID: <20140311094914.637022406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : master Link : http://git.haskell.org/haddock.git/commitdiff/b8efaf4ead90c5c95367cc479da522b820b5004e >--------------------------------------------------------------- commit b8efaf4ead90c5c95367cc479da522b820b5004e Author: Niklas Haas Date: Tue Mar 11 08:42:34 2014 +0100 Filter family instances of hidden types Currently, this check does not extend to hidden right hand sides, although it probably should hide them in that case. >--------------------------------------------------------------- b8efaf4ead90c5c95367cc479da522b820b5004e CHANGES | 2 +- html-test/src/TypeFamilies2.hs | 8 ++++++++ src/Haddock/Interface/AttachInstances.hs | 15 +++++++++++---- 3 files changed, 20 insertions(+), 5 deletions(-) diff --git a/CHANGES b/CHANGES index e34701c..e067785 100644 --- a/CHANGES +++ b/CHANGES @@ -27,7 +27,7 @@ Changes in version 2.14.0 * Properly render License field (#271) - * Print type/data family instances + * Print type/data family instances (for exported types only) * Fix display of poly-kinded type operators (#189) diff --git a/html-test/src/TypeFamilies2.hs b/html-test/src/TypeFamilies2.hs index 093f77c..34790a5 100644 --- a/html-test/src/TypeFamilies2.hs +++ b/html-test/src/TypeFamilies2.hs @@ -3,6 +3,9 @@ -- in type instances. The expected behaviour is -- that we get the instance, Y is not linked and -- Haddock shows a linking warning. +-- +-- The other families and instances that are not exported should not +-- show up at all module TypeFamilies2 (X, Foo, Bar) where data X @@ -10,6 +13,11 @@ data Y type family Foo a type instance Foo X = Y +type instance Foo Y = X -- Should be hidden data family Bar a data instance Bar X = BarX Y + +type family Invisible a +type instance Invisible X = Y +type instance Invisible Y = X diff --git a/src/Haddock/Interface/AttachInstances.hs b/src/Haddock/Interface/AttachInstances.hs index 88512c1..60ae466 100644 --- a/src/Haddock/Interface/AttachInstances.hs +++ b/src/Haddock/Interface/AttachInstances.hs @@ -73,6 +73,10 @@ attachToExportItem expInfo iface ifaceMap instIfaceMap export = let fam_insts = [ (synifyFamInst i, n) | i <- sortBy (comparing instFam) fam_instances , let n = instLookup instDocMap (getName i) iface ifaceMap instIfaceMap + , not $ isNameHidden expInfo (fi_fam i) + , not $ any (isTypeHidden expInfo) (fi_tys i) + -- Should we check for hidden RHS as well? + -- Ideally, in that case the RHS should simply not show up ] cls_insts = [ (synifyInstHead i, instLookup instDocMap n iface ifaceMap instIfaceMap) | let is = [ (instanceHead' i, getName i) | i <- cls_instances ] @@ -199,11 +203,11 @@ isInstanceHidden expInfo cls tys = instClassHidden = isNameHidden expInfo $ getName cls instTypeHidden :: Bool - instTypeHidden = any typeHidden tys - - nameHidden :: Name -> Bool - nameHidden = isNameHidden expInfo + instTypeHidden = any (isTypeHidden expInfo) tys +isTypeHidden :: ExportInfo -> Type -> Bool +isTypeHidden expInfo = typeHidden + where typeHidden :: Type -> Bool typeHidden t = case t of @@ -213,3 +217,6 @@ isInstanceHidden expInfo cls tys = FunTy t1 t2 -> typeHidden t1 || typeHidden t2 ForAllTy _ ty -> typeHidden ty LitTy _ -> False + + nameHidden :: Name -> Bool + nameHidden = isNameHidden expInfo From git at git.haskell.org Tue Mar 11 09:49:16 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Mar 2014 09:49:16 +0000 (UTC) Subject: [commit: haddock] master: Revert "Reorder topDeclElem to move the source/wiki links to the top" (5f02bd6) Message-ID: <20140311094916.498682406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : master Link : http://git.haskell.org/haddock.git/commitdiff/5f02bd67b9a17feb2dc64dc5f5c011996850fb8a >--------------------------------------------------------------- commit 5f02bd67b9a17feb2dc64dc5f5c011996850fb8a Author: Niklas Haas Date: Tue Mar 11 10:36:55 2014 +0100 Revert "Reorder topDeclElem to move the source/wiki links to the top" This reverts commit 843c42c4179526a2ad3526e4c7d38cbf4d50001d. This change is no longer needed with the new rendering style, and it messes with copy/pasting lines. >--------------------------------------------------------------- 5f02bd67b9a17feb2dc64dc5f5c011996850fb8a src/Haddock/Backends/Xhtml/Layout.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Haddock/Backends/Xhtml/Layout.hs b/src/Haddock/Backends/Xhtml/Layout.hs index dfcda47..6784fb3 100644 --- a/src/Haddock/Backends/Xhtml/Layout.hs +++ b/src/Haddock/Backends/Xhtml/Layout.hs @@ -192,7 +192,7 @@ declElem = paragraph ! [theclass "src"] -- it adds a source and wiki link at the right hand side of the box topDeclElem :: LinksInfo -> SrcSpan -> Bool -> [DocName] -> Html -> Html topDeclElem ((_,_,sourceMap,lineMap), (_,_,maybe_wiki_url)) loc splice names html = - declElem << (srcLink <+> wikiLink <+> html) + declElem << (html <+> srcLink <+> wikiLink) where srcLink = let nameUrl = Map.lookup origPkg sourceMap lineUrl = Map.lookup origPkg lineMap mUrl | splice = lineUrl From git at git.haskell.org Tue Mar 11 09:49:18 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Mar 2014 09:49:18 +0000 (UTC) Subject: [commit: haddock] master: Bump version to 2.15.0 (dd05c5c) Message-ID: <20140311094920.5F5912406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : master Link : http://git.haskell.org/haddock.git/commitdiff/dd05c5cb8a21113d7e8ee63ffc9bf5e13ced4cac >--------------------------------------------------------------- commit dd05c5cb8a21113d7e8ee63ffc9bf5e13ced4cac Author: Mateusz Kowalczyk Date: Tue Mar 11 08:47:23 2014 +0000 Bump version to 2.15.0 >--------------------------------------------------------------- dd05c5cb8a21113d7e8ee63ffc9bf5e13ced4cac doc/haddock.xml | 2 +- haddock.cabal | 2 +- haddock.spec | 2 +- html-test/ref/A.html | 2 +- html-test/ref/AdvanceTypes.html | 2 +- html-test/ref/B.html | 2 +- html-test/ref/Bold.html | 2 +- html-test/ref/Bug1.html | 2 +- html-test/ref/Bug195.html | 2 +- html-test/ref/Bug2.html | 2 +- html-test/ref/Bug3.html | 2 +- html-test/ref/Bug4.html | 2 +- html-test/ref/Bug6.html | 2 +- html-test/ref/Bug7.html | 2 +- html-test/ref/Bug8.html | 2 +- html-test/ref/BugDeprecated.html | 2 +- html-test/ref/BugExportHeadings.html | 2 +- html-test/ref/Bugs.html | 2 +- html-test/ref/CrossPackageDocs.html | 2 +- html-test/ref/DeprecatedClass.html | 2 +- html-test/ref/DeprecatedData.html | 2 +- html-test/ref/DeprecatedFunction.html | 2 +- html-test/ref/DeprecatedFunction2.html | 2 +- html-test/ref/DeprecatedFunction3.html | 2 +- html-test/ref/DeprecatedModule.html | 2 +- html-test/ref/DeprecatedModule2.html | 2 +- html-test/ref/DeprecatedNewtype.html | 2 +- html-test/ref/DeprecatedReExport.html | 2 +- html-test/ref/DeprecatedRecord.html | 2 +- html-test/ref/DeprecatedTypeFamily.html | 2 +- html-test/ref/DeprecatedTypeSynonym.html | 2 +- html-test/ref/Examples.html | 2 +- html-test/ref/Extensions.html | 2 +- html-test/ref/FunArgs.html | 2 +- html-test/ref/GADTRecords.html | 2 +- html-test/ref/Hash.html | 2 +- html-test/ref/HiddenInstances.html | 2 +- html-test/ref/HiddenInstancesB.html | 2 +- html-test/ref/Hyperlinks.html | 2 +- html-test/ref/IgnoreExports.html | 2 +- html-test/ref/ImplicitParams.html | 2 +- html-test/ref/ModuleWithWarning.html | 2 +- html-test/ref/NamedDoc.html | 2 +- html-test/ref/Nesting.html | 2 +- html-test/ref/NoLayout.html | 2 +- html-test/ref/NonGreedy.html | 2 +- html-test/ref/Operators.html | 2 +- html-test/ref/PatternSyns.html | 2 +- html-test/ref/Properties.html | 2 +- html-test/ref/PruneWithWarning.html | 2 +- html-test/ref/QuasiExpr.html | 2 +- html-test/ref/QuasiQuote.html | 2 +- html-test/ref/SpuriousSuperclassConstraints.html | 2 +- html-test/ref/TH.html | 2 +- html-test/ref/TH2.html | 2 +- html-test/ref/Test.html | 2 +- html-test/ref/Ticket112.html | 2 +- html-test/ref/Ticket253_1.html | 2 +- html-test/ref/Ticket253_2.html | 2 +- html-test/ref/Ticket61.html | 2 +- html-test/ref/Ticket75.html | 2 +- html-test/ref/TitledPicture.html | 2 +- html-test/ref/TypeFamilies.html | 2 +- html-test/ref/TypeFamilies2.html | 2 +- html-test/ref/TypeOperators.html | 2 +- html-test/ref/Unicode.html | 2 +- html-test/ref/Visible.html | 2 +- 67 files changed, 67 insertions(+), 67 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc dd05c5cb8a21113d7e8ee63ffc9bf5e13ced4cac From git at git.haskell.org Tue Mar 11 09:49:20 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Mar 2014 09:49:20 +0000 (UTC) Subject: [commit: haddock] master: Fix up some whitespace (8f71c6f) Message-ID: <20140311094920.C319A24069@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : master Link : http://git.haskell.org/haddock.git/commitdiff/8f71c6f26eb5b36e5a1ca253b8c8ffdca75849d8 >--------------------------------------------------------------- commit 8f71c6f26eb5b36e5a1ca253b8c8ffdca75849d8 Author: Mateusz Kowalczyk Date: Tue Mar 11 08:50:42 2014 +0000 Fix up some whitespace >--------------------------------------------------------------- 8f71c6f26eb5b36e5a1ca253b8c8ffdca75849d8 doc/haddock.xml | 1566 ++++++++++++++++++++++++------------------------- html-test/src/Hash.hs | 2 +- 2 files changed, 784 insertions(+), 784 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 8f71c6f26eb5b36e5a1ca253b8c8ffdca75849d8 From git at git.haskell.org Tue Mar 11 09:57:04 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Mar 2014 09:57:04 +0000 (UTC) Subject: [commit: haddock] tag 'haddock-2.14.0' created Message-ID: <20140311095705.08DDE2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock New tag : haddock-2.14.0 Referencing: 45b4391d1a17c5cdde344cc4b44b0a66ba1a7e54 From git at git.haskell.org Tue Mar 11 10:17:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Mar 2014 10:17:01 +0000 (UTC) Subject: [commit: haddock] tag 'haddock-2.14.0' deleted Message-ID: <20140311101701.AF5AA2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock Deleted tag: haddock-2.14.0 From git at git.haskell.org Tue Mar 11 10:24:41 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Mar 2014 10:24:41 +0000 (UTC) Subject: [commit: haddock] branch 'v2.14' created Message-ID: <20140311102442.741B42406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock New branch : v2.14 Referencing: 1063ade772264cc40a88e0d72db5e26b74439a6e From git at git.haskell.org Tue Mar 11 10:24:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Mar 2014 10:24:43 +0000 (UTC) Subject: [commit: haddock] v2.14: Fix up CPP preparing for release with GHC 7.8. (1063ade) Message-ID: <20140311102443.9E2D72406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : v2.14 Link : http://git.haskell.org/haddock.git/commitdiff/1063ade772264cc40a88e0d72db5e26b74439a6e >--------------------------------------------------------------- commit 1063ade772264cc40a88e0d72db5e26b74439a6e Author: Mateusz Kowalczyk Date: Tue Mar 11 10:21:09 2014 +0000 Fix up CPP preparing for release with GHC 7.8. >--------------------------------------------------------------- 1063ade772264cc40a88e0d72db5e26b74439a6e src/Haddock/InterfaceFile.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Haddock/InterfaceFile.hs b/src/Haddock/InterfaceFile.hs index 924829d..c8af7bc 100644 --- a/src/Haddock/InterfaceFile.hs +++ b/src/Haddock/InterfaceFile.hs @@ -76,7 +76,7 @@ binaryInterfaceMagic = 0xD0Cface -- (2) set `binaryInterfaceVersionCompatibility` to [binaryInterfaceVersion] -- binaryInterfaceVersion :: Word16 -#if __GLASGOW_HASKELL__ == 709 +#if __GLASGOW_HASKELL__ == 708 binaryInterfaceVersion = 25 binaryInterfaceVersionCompatibility :: [Word16] From git at git.haskell.org Tue Mar 11 10:24:58 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Mar 2014 10:24:58 +0000 (UTC) Subject: [commit: haddock] tag 'haddock-2.14.0-release' created Message-ID: <20140311102458.8B8762406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock New tag : haddock-2.14.0-release Referencing: 57803a4118c729bfd4705cf19f262740563f722e From git at git.haskell.org Tue Mar 11 11:16:07 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Mar 2014 11:16:07 +0000 (UTC) Subject: [commit: ghc] master: Comments only (a10ed3e) Message-ID: <20140311111609.09D5F2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a10ed3e64336e272137e1743c36970b36f7076c7/ghc >--------------------------------------------------------------- commit a10ed3e64336e272137e1743c36970b36f7076c7 Author: Simon Peyton Jones Date: Thu Mar 6 11:54:33 2014 +0000 Comments only >--------------------------------------------------------------- a10ed3e64336e272137e1743c36970b36f7076c7 compiler/coreSyn/CoreArity.lhs | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/compiler/coreSyn/CoreArity.lhs b/compiler/coreSyn/CoreArity.lhs index 080a6fd..12d4274 100644 --- a/compiler/coreSyn/CoreArity.lhs +++ b/compiler/coreSyn/CoreArity.lhs @@ -325,8 +325,8 @@ this transformation. So we try to limit it as much as possible: (3) Do NOT move a lambda outside a case unless (a) The scrutinee is ok-for-speculation, or - (b) more liberally: the scrutinee is cheap and -fpedantic-bottoms is not - enforced + (b) more liberally: the scrutinee is cheap (e.g. a variable), and + -fpedantic-bottoms is not enforced (see Trac #2915 for an example) Of course both (1) and (2) are readily defeated by disguising the bottoms. @@ -753,10 +753,10 @@ arityType env (Case scrut _ _ alts) | otherwise -> ABot 0 -- if RHS is bottomming -- See Note [Dealing with bottom (2)] - ATop as | not (ae_ped_bot env) -- Check -fpedantic-bottoms + ATop as | not (ae_ped_bot env) -- See Note [Dealing with bottom (3)] , ae_cheap_fn env scrut Nothing -> ATop as - | exprOkForSpeculation scrut -> ATop as - | otherwise -> ATop (takeWhile isOneShotInfo as) + | exprOkForSpeculation scrut -> ATop as + | otherwise -> ATop (takeWhile isOneShotInfo as) where alts_type = foldr1 andArityType [arityType env rhs | (_,_,rhs) <- alts] From git at git.haskell.org Tue Mar 11 11:16:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Mar 2014 11:16:11 +0000 (UTC) Subject: [commit: ghc] master: Make SetLevels do substitution properly (fixes Trac #8714) (ef44a42) Message-ID: <20140311111611.5AEAD2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ef44a429af4a630a153b5774d0e19dbcad8328d5/ghc >--------------------------------------------------------------- commit ef44a429af4a630a153b5774d0e19dbcad8328d5 Author: Simon Peyton Jones Date: Tue Mar 11 11:13:31 2014 +0000 Make SetLevels do substitution properly (fixes Trac #8714) Nowadays SetLevels floats case expressions as well as let-bindings, and case expressions bind type variables. We need to clone all such floated binders, to avoid accidental name capture. But I'd forgotten to substitute for the cloned type variables, causing #8714. (In the olden days only Ids were cloned, from let-bindings.) This patch fixes the bug and does quite a bit of clean-up refactoring as well, by putting the context level in the LvlEnv. There is no effect on performance, except that nofib 'rewrite' improves allocations by 3%. On investigation I think it was a fluke to do with loop-cutting in big letrec nests. But at least it's a fluke in the right direction. Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- Min -0.4% -3.0% -19.4% -19.4% -26.7% Max -0.0% +0.0% +17.9% +17.9% 0.0% Geometric Mean -0.1% -0.0% -0.7% -0.7% -0.4% >--------------------------------------------------------------- ef44a429af4a630a153b5774d0e19dbcad8328d5 compiler/coreSyn/CoreSubst.lhs | 2 +- compiler/coreSyn/CoreSyn.lhs | 21 +- compiler/simplCore/SetLevels.lhs | 602 ++++++++++----------- testsuite/tests/simplCore/should_compile/T8714.hs | 9 + testsuite/tests/simplCore/should_compile/all.T | 1 + 5 files changed, 312 insertions(+), 323 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ef44a429af4a630a153b5774d0e19dbcad8328d5 From git at git.haskell.org Tue Mar 11 12:48:36 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Mar 2014 12:48:36 +0000 (UTC) Subject: [commit: ghc] master: Fix last-minute typo in SetLevels commit ef44a4 (41f8031) Message-ID: <20140311124836.B1D5D2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/41f803105999ffe51a40d3c72d5994520496b7ea/ghc >--------------------------------------------------------------- commit 41f803105999ffe51a40d3c72d5994520496b7ea Author: Simon Peyton Jones Date: Tue Mar 11 12:47:57 2014 +0000 Fix last-minute typo in SetLevels commit ef44a4 Sorry about that... >--------------------------------------------------------------- 41f803105999ffe51a40d3c72d5994520496b7ea compiler/simplCore/SetLevels.lhs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/compiler/simplCore/SetLevels.lhs b/compiler/simplCore/SetLevels.lhs index cc72164..6edadb8 100644 --- a/compiler/simplCore/SetLevels.lhs +++ b/compiler/simplCore/SetLevels.lhs @@ -479,7 +479,8 @@ lvlMFE strict_ctxt env ann_expr@(fvs, _) ; return (Let (NonRec (TB var (FloatMe dest_lvl)) expr') (mkVarApps (Var var) abs_vars)) } where - is_bot = exprIsBottom (deAnnotate ann_expr) -- Note [Bottoming floats] + expr = deAnnotate ann_expr + is_bot = exprIsBottom expr -- Note [Bottoming floats] dest_lvl = destLevel env fvs (isFunction ann_expr) is_bot abs_vars = abstractVars dest_lvl env fvs From git at git.haskell.org Tue Mar 11 20:30:57 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Mar 2014 20:30:57 +0000 (UTC) Subject: [commit: ghc] master: Represent offsets into heap objects with byte, not word, offsets (a70e7b4) Message-ID: <20140311203057.2626B2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a70e7b4762c75812254f7781bcd48139c4ec40dd/ghc >--------------------------------------------------------------- commit a70e7b4762c75812254f7781bcd48139c4ec40dd Author: Simon Marlow Date: Fri Nov 29 10:32:26 2013 +0000 Represent offsets into heap objects with byte, not word, offsets I'd like to be able to pack together non-pointer fields that are less than a word in size, and this is a necessary prerequisite. >--------------------------------------------------------------- a70e7b4762c75812254f7781bcd48139c4ec40dd compiler/cmm/CmmUtils.hs | 9 +++++---- compiler/cmm/SMRep.lhs | 16 ++++++++++++--- compiler/codeGen/StgCmmBind.hs | 13 ++++++------ compiler/codeGen/StgCmmCon.hs | 1 + compiler/codeGen/StgCmmHeap.hs | 9 ++++----- compiler/codeGen/StgCmmLayout.hs | 41 +++++++++++++++++++++++--------------- compiler/codeGen/StgCmmUtils.hs | 5 +++-- 7 files changed, 58 insertions(+), 36 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a70e7b4762c75812254f7781bcd48139c4ec40dd From git at git.haskell.org Tue Mar 11 20:30:59 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Mar 2014 20:30:59 +0000 (UTC) Subject: [commit: ghc] master: Fix incorrect loop condition in inline array allocation (c1d74ab) Message-ID: <20140311203059.B694D2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c1d74ab96df7607529596d01223bc8654abf71b9/ghc >--------------------------------------------------------------- commit c1d74ab96df7607529596d01223bc8654abf71b9 Author: Johan Tibell Date: Tue Mar 11 13:54:29 2014 +0100 Fix incorrect loop condition in inline array allocation Also make sure allocHeapClosure updates profiling counters with the memory allocated. >--------------------------------------------------------------- c1d74ab96df7607529596d01223bc8654abf71b9 compiler/codeGen/StgCmmHeap.hs | 5 +++-- compiler/codeGen/StgCmmPrim.hs | 11 ++++++----- compiler/codeGen/StgCmmTicky.hs | 4 +++- 3 files changed, 12 insertions(+), 8 deletions(-) diff --git a/compiler/codeGen/StgCmmHeap.hs b/compiler/codeGen/StgCmmHeap.hs index 2a0eaf9..488a0e0 100644 --- a/compiler/codeGen/StgCmmHeap.hs +++ b/compiler/codeGen/StgCmmHeap.hs @@ -99,7 +99,6 @@ allocDynClosureCmm mb_id info_tbl lf_info use_cc _blame_cc amodes_w_offsets = do -- SAY WHAT WE ARE ABOUT TO DO let rep = cit_rep info_tbl tickyDynAlloc mb_id rep lf_info - profDynAlloc rep use_cc let info_ptr = CmmLit (CmmLabel (cit_lbl info_tbl)) allocHeapClosure rep info_ptr use_cc amodes_w_offsets @@ -112,6 +111,8 @@ allocHeapClosure -> [(CmmExpr,ByteOff)] -- ^ payload -> FCode CmmExpr -- ^ returns the address of the object allocHeapClosure rep info_ptr use_cc payload = do + profDynAlloc rep use_cc + virt_hp <- getVirtHp -- Find the offset of the info-ptr word @@ -122,7 +123,7 @@ allocHeapClosure rep info_ptr use_cc payload = do -- ie 1 *before* the info-ptr word of new object. base <- getHpRelOffset info_offset - emitComment $ mkFastString "allocDynClosure" + emitComment $ mkFastString "allocHeapClosure" emitSetDynHdr base info_ptr use_cc -- Fill in the fields diff --git a/compiler/codeGen/StgCmmPrim.hs b/compiler/codeGen/StgCmmPrim.hs index a4327c4..22f6ec1 100644 --- a/compiler/codeGen/StgCmmPrim.hs +++ b/compiler/codeGen/StgCmmPrim.hs @@ -1535,14 +1535,14 @@ doNewArrayOp res_r n init = do dflags <- getDynFlags let info_ptr = mkLblExpr mkMAP_DIRTY_infoLabel + rep = arrPtrsRep dflags (fromIntegral n) - -- ToDo: this probably isn't right (card size?) tickyAllocPrim (mkIntExpr dflags (arrPtrsHdrSize dflags)) - (mkIntExpr dflags (fromInteger n * wORD_SIZE dflags)) + (mkIntExpr dflags (wordsToBytes dflags (heapClosureSizeW dflags rep))) (zeroExpr dflags) - let rep = arrPtrsRep dflags (fromIntegral n) - hdr_size = fixedHdrSize dflags * wORD_SIZE dflags + let hdr_size = wordsToBytes dflags (fixedHdrSize dflags) + base <- allocHeapClosure rep info_ptr curCCS [ (mkIntExpr dflags (fromInteger n), hdr_size + oFFSET_StgMutArrPtrs_ptrs dflags) @@ -1563,7 +1563,8 @@ doNewArrayOp res_r n init = do , mkBranch for ] emit =<< mkCmmIfThen (cmmULtWord dflags (CmmReg (CmmLocal p)) - (cmmOffsetW dflags (CmmReg arr) (fromInteger n))) + (cmmOffsetW dflags (CmmReg arr) + (arrPtrsHdrSizeW dflags + fromInteger n))) (catAGraphs loopBody) emit $ mkAssign (CmmLocal res_r) (CmmReg arr) diff --git a/compiler/codeGen/StgCmmTicky.hs b/compiler/codeGen/StgCmmTicky.hs index 50112f1..b121820 100644 --- a/compiler/codeGen/StgCmmTicky.hs +++ b/compiler/codeGen/StgCmmTicky.hs @@ -485,7 +485,9 @@ tickyAllocHeap genuine hp -- the units are bytes -tickyAllocPrim :: CmmExpr -> CmmExpr -> CmmExpr -> FCode () +tickyAllocPrim :: CmmExpr -- ^ size of the full header, in bytes + -> CmmExpr -- ^ size of the payload, in bytes + -> CmmExpr -> FCode () tickyAllocPrim _hdr _goods _slop = ifTicky $ do bumpTickyCounter (fsLit "ALLOC_PRIM_ctr") bumpTickyCounterByE (fsLit "ALLOC_PRIM_adm") _hdr From git at git.haskell.org Tue Mar 11 20:31:02 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Mar 2014 20:31:02 +0000 (UTC) Subject: [commit: ghc] master: codeGen: allocate small arrays of statically known size inline (22f010e) Message-ID: <20140311203103.B68FB2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/22f010e08e58ba40b0ab59ec7a7c02cce0938cce/ghc >--------------------------------------------------------------- commit 22f010e08e58ba40b0ab59ec7a7c02cce0938cce Author: Johan Tibell Date: Wed Sep 25 09:10:13 2013 -0400 codeGen: allocate small arrays of statically known size inline This results in a 46% runtime decrease when allocating an array of 16 unit elements on a 64-bit machine. In order to allow newArray# to have both an inline and an out-of-line implementation, cgOpApp is refactored slightly. The new implementation of cgOpApp should make it easier to add other primops with both inline and out-of-line implementations in the future. >--------------------------------------------------------------- 22f010e08e58ba40b0ab59ec7a7c02cce0938cce compiler/codeGen/StgCmmPrim.hs | 197 ++++++++++++++++++++++++++++++++-------- 1 file changed, 159 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 22f010e08e58ba40b0ab59ec7a7c02cce0938cce From git at git.haskell.org Tue Mar 11 20:31:05 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Mar 2014 20:31:05 +0000 (UTC) Subject: [commit: ghc] master: Refactor inline array allocation (b684f27) Message-ID: <20140311203105.4EB7A2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b684f27ec7b3538ffd9401de70ef5685b8b71978/ghc >--------------------------------------------------------------- commit b684f27ec7b3538ffd9401de70ef5685b8b71978 Author: Simon Marlow Date: Mon Mar 10 21:43:15 2014 +0000 Refactor inline array allocation - Move array representation knowledge into SMRep - Separate out low-level heap-object allocation so that we can reuse it from doNewArrayOp - remove card-table initialisation, we can safely ignore the card table for newly allocated arrays. >--------------------------------------------------------------- b684f27ec7b3538ffd9401de70ef5685b8b71978 compiler/cmm/SMRep.lhs | 65 ++++++++++++++++++++++++------ compiler/codeGen/StgCmmHeap.hs | 84 +++++++++++++++++++++------------------ compiler/codeGen/StgCmmPrim.hs | 75 +++++++++------------------------- compiler/codeGen/StgCmmProf.hs | 2 +- compiler/codeGen/StgCmmTicky.hs | 2 +- 5 files changed, 120 insertions(+), 108 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b684f27ec7b3538ffd9401de70ef5685b8b71978 From git at git.haskell.org Tue Mar 11 20:31:08 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Mar 2014 20:31:08 +0000 (UTC) Subject: [commit: ghc] master: Add test for inline array allocation (22e4bba) Message-ID: <20140311203108.427702406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/22e4bba2df99a2c9ad2822b3a7a5ac6de0f805e4/ghc >--------------------------------------------------------------- commit 22e4bba2df99a2c9ad2822b3a7a5ac6de0f805e4 Author: Johan Tibell Date: Tue Mar 11 16:01:19 2014 +0100 Add test for inline array allocation >--------------------------------------------------------------- 22e4bba2df99a2c9ad2822b3a7a5ac6de0f805e4 .../tests/codeGen/should_run/StaticArraySize.hs | 87 ++++++++++++++++++++ .../{T8256.stdout => StaticArraySize.stdout} | 0 testsuite/tests/codeGen/should_run/all.T | 1 + 3 files changed, 88 insertions(+) diff --git a/testsuite/tests/codeGen/should_run/StaticArraySize.hs b/testsuite/tests/codeGen/should_run/StaticArraySize.hs new file mode 100644 index 0000000..1052e2d --- /dev/null +++ b/testsuite/tests/codeGen/should_run/StaticArraySize.hs @@ -0,0 +1,87 @@ +{-# LANGUAGE BangPatterns, MagicHash, UnboxedTuples #-} + +-- Test allocation of statically sized arrays. There's an optimization +-- that targets these and we want to make sure that the code generated +-- in the optimized case is correct. +-- +-- The tests proceeds by allocating a bunch of arrays of different +-- sizes and reading elements from them, to try to provoke GC crashes, +-- which would be a symptom of the optimization not generating correct +-- code. +module Main where + +import GHC.Exts +import GHC.IO +import Prelude hiding (read) + +main :: IO () +main = do + loop 1000 + putStrLn "success" + where + loop :: Int -> IO () + loop 0 = return () + loop i = do + -- Sizes have been picked to match the triggering of the + -- optimization and to match boundary conditions. Sizes are + -- given explicitly as to not rely on other optimizations to + -- make the static size known to the compiler. + marr0 <- newArray 0 + marr1 <- newArray 1 + marr2 <- newArray 2 + marr3 <- newArray 3 + marr4 <- newArray 4 + marr5 <- newArray 5 + marr6 <- newArray 6 + marr7 <- newArray 7 + marr8 <- newArray 8 + marr9 <- newArray 9 + marr10 <- newArray 10 + marr11 <- newArray 11 + marr12 <- newArray 12 + marr13 <- newArray 13 + marr14 <- newArray 14 + marr15 <- newArray 15 + marr16 <- newArray 16 + marr17 <- newArray 17 + let marrs = [marr0, marr1, marr2, marr3, marr4, marr5, marr6, marr7, + marr8, marr9, marr10, marr11, marr12, marr13, marr14, + marr15, marr16, marr17] + print `fmap` sumManyArrays marrs + loop (i-1) + +sumManyArrays :: [MArray] -> IO Int +sumManyArrays = go 0 + where + go !acc [] = return acc + go acc (marr:marrs) = do + n <- sumArray marr + go (acc+n) marrs + +sumArray :: MArray -> IO Int +sumArray marr = go 0 0 + where + go :: Int -> Int -> IO Int + go !acc i + | i < len = do + k <- read marr i + go (acc + k) (i+1) + | otherwise = return acc + len = lengthM marr + +data MArray = MArray { unMArray :: !(MutableArray# RealWorld Int) } + +newArray :: Int -> IO MArray +newArray (I# sz#) = IO $ \s -> case newArray# sz# 1 s of + (# s', marr #) -> (# s', MArray marr #) +{-# INLINE newArray #-} -- to make sure optimization triggers + +lengthM :: MArray -> Int +lengthM marr = I# (sizeofMutableArray# (unMArray marr)) + +read :: MArray -> Int -> IO Int +read marr i@(I# i#) + | i < 0 || i >= len = + error $ "bounds error, offset " ++ show i ++ ", length " ++ show len + | otherwise = IO $ \ s -> readArray# (unMArray marr) i# s + where len = lengthM marr diff --git a/testsuite/tests/codeGen/should_run/T8256.stdout b/testsuite/tests/codeGen/should_run/StaticArraySize.stdout similarity index 100% copy from testsuite/tests/codeGen/should_run/T8256.stdout copy to testsuite/tests/codeGen/should_run/StaticArraySize.stdout diff --git a/testsuite/tests/codeGen/should_run/all.T b/testsuite/tests/codeGen/should_run/all.T index b1a9fd4..a8b013e 100644 --- a/testsuite/tests/codeGen/should_run/all.T +++ b/testsuite/tests/codeGen/should_run/all.T @@ -116,3 +116,4 @@ test('T8103', only_ways(['normal']), compile_and_run, ['']) test('T7953', reqlib('random'), compile_and_run, ['']) test('T8256', reqlib('vector'), compile_and_run, ['']) test('T6084',normal, compile_and_run, ['-O2']) +test('StaticArraySize', normal, compile_and_run, ['-O2']) From git at git.haskell.org Tue Mar 11 21:13:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Mar 2014 21:13:24 +0000 (UTC) Subject: [commit: ghc] master: Validate computed sums in inline array allocation test (d8b3826) Message-ID: <20140311211324.5ADA52406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d8b38265d6499914c12e19329203361cb2aa8ea3/ghc >--------------------------------------------------------------- commit d8b38265d6499914c12e19329203361cb2aa8ea3 Author: Johan Tibell Date: Tue Mar 11 22:12:31 2014 +0100 Validate computed sums in inline array allocation test >--------------------------------------------------------------- d8b38265d6499914c12e19329203361cb2aa8ea3 testsuite/tests/codeGen/should_run/StaticArraySize.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/codeGen/should_run/StaticArraySize.hs b/testsuite/tests/codeGen/should_run/StaticArraySize.hs index 1052e2d..06c8343 100644 --- a/testsuite/tests/codeGen/should_run/StaticArraySize.hs +++ b/testsuite/tests/codeGen/should_run/StaticArraySize.hs @@ -10,6 +10,7 @@ -- code. module Main where +import Control.Monad import GHC.Exts import GHC.IO import Prelude hiding (read) @@ -47,7 +48,9 @@ main = do let marrs = [marr0, marr1, marr2, marr3, marr4, marr5, marr6, marr7, marr8, marr9, marr10, marr11, marr12, marr13, marr14, marr15, marr16, marr17] - print `fmap` sumManyArrays marrs + total <- sumManyArrays marrs + unless (total == 153) $ + putStrLn "incorrect sum" loop (i-1) sumManyArrays :: [MArray] -> IO Int From git at git.haskell.org Tue Mar 11 21:39:32 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 11 Mar 2014 21:39:32 +0000 (UTC) Subject: [commit: ghc] master: Add perf test for inline array allocation (d793a14) Message-ID: <20140311213932.4E0BB2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d793a148917aa62e8860ffd7b66936d41bfa5737/ghc >--------------------------------------------------------------- commit d793a148917aa62e8860ffd7b66936d41bfa5737 Author: Johan Tibell Date: Tue Mar 11 22:39:00 2014 +0100 Add perf test for inline array allocation >--------------------------------------------------------------- d793a148917aa62e8860ffd7b66936d41bfa5737 testsuite/tests/perf/should_run/InlineArrayAlloc.hs | 16 ++++++++++++++++ testsuite/tests/perf/should_run/all.T | 6 ++++++ 2 files changed, 22 insertions(+) diff --git a/testsuite/tests/perf/should_run/InlineArrayAlloc.hs b/testsuite/tests/perf/should_run/InlineArrayAlloc.hs new file mode 100644 index 0000000..09f3e40 --- /dev/null +++ b/testsuite/tests/perf/should_run/InlineArrayAlloc.hs @@ -0,0 +1,16 @@ +{-# LANGUAGE BangPatterns, MagicHash, UnboxedTuples #-} +module Main where + +import GHC.Exts +import GHC.IO + +main :: IO () +main = loop 10000000 + where + loop :: Int -> IO () + loop 0 = return () + loop i = newArray >> loop (i-1) + +newArray :: IO () +newArray = IO $ \s -> case newArray# 16# () s of + (# s', _ #) -> (# s', () #) diff --git a/testsuite/tests/perf/should_run/all.T b/testsuite/tests/perf/should_run/all.T index 9ce4d45..ea1ba8f 100644 --- a/testsuite/tests/perf/should_run/all.T +++ b/testsuite/tests/perf/should_run/all.T @@ -331,3 +331,9 @@ test('T7619', compile_and_run, ['-O']) +test('InlineArrayAlloc', + [stats_num_field('bytes allocated', + [ (wordsize(64), 1600040960, 5)]), + only_ways(['normal'])], + compile_and_run, + ['-O2']) From git at git.haskell.org Wed Mar 12 09:21:33 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Mar 2014 09:21:33 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Update `Cabal` to 1.18.1.3 release (db9c4f4) Message-ID: <20140312092133.872B62406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/db9c4f4c48aa03c75700e98870565f31ee84bd2c/ghc >--------------------------------------------------------------- commit db9c4f4c48aa03c75700e98870565f31ee84bd2c Author: Herbert Valerio Riedel Date: Tue Mar 4 22:19:37 2014 +0100 Update `Cabal` to 1.18.1.3 release Signed-off-by: Herbert Valerio Riedel (cherry picked from commit 01f9ac3e977fb128388467a31f62e84d769e17ec) >--------------------------------------------------------------- db9c4f4c48aa03c75700e98870565f31ee84bd2c libraries/Cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Cabal b/libraries/Cabal index d310d87..c226c0d 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit d310d87c2c445f52987169a2ce4da03c14070918 +Subproject commit c226c0de042999bbe4c5c339c6c28a9be7f0c6d1 From git at git.haskell.org Wed Mar 12 10:18:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Mar 2014 10:18:17 +0000 (UTC) Subject: [commit: haddock] ghc-7.8: Merge tag 'haddock-2.14.0-release' into ghc-7.8 (3945c9a) Message-ID: <20140312101817.B6C2C2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : ghc-7.8 Link : http://git.haskell.org/haddock.git/commitdiff/3945c9aaf13064f768aceb1dc93a43e211e9f4e0 >--------------------------------------------------------------- commit 3945c9aaf13064f768aceb1dc93a43e211e9f4e0 Merge: e0865f5 1063ade Author: Herbert Valerio Riedel Date: Wed Mar 12 10:28:39 2014 +0100 Merge tag 'haddock-2.14.0-release' into ghc-7.8 This merge has been done in such a way that this commit's tree corresponds exactly to the tree pointed to by the haddock-2.14.0-release tag. Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 3945c9aaf13064f768aceb1dc93a43e211e9f4e0 CHANGES | 20 +- doc/haddock.xml | 30 ++ html-test/ref/{GADTRecords.html => Bug195.html} | 178 ++++----- html-test/ref/Bug8.html | 14 +- html-test/ref/Operators.html | 457 +++++++++++++++++++++++ html-test/src/Bug195.hs | 11 + html-test/src/Operators.hs | 64 ++++ html-test/src/TypeFamilies2.hs | 8 + resources/html/Ocean.std-theme/ocean.css | 13 + src/Haddock.hs | 6 +- src/Haddock/Backends/Hoogle.hs | 2 +- src/Haddock/Backends/LaTeX.hs | 11 +- src/Haddock/Backends/Xhtml.hs | 14 +- src/Haddock/Backends/Xhtml/Decl.hs | 299 +++++++++------ src/Haddock/Backends/Xhtml/Layout.hs | 12 +- src/Haddock/Backends/Xhtml/Types.hs | 12 +- src/Haddock/Backends/Xhtml/Utils.hs | 17 +- src/Haddock/Interface/AttachInstances.hs | 70 ++-- src/Haddock/Interface/Create.hs | 74 ++-- src/Haddock/Interface/Rename.hs | 10 +- src/Haddock/InterfaceFile.hs | 11 +- src/Haddock/Options.hs | 25 +- src/Haddock/Types.hs | 13 + 23 files changed, 1040 insertions(+), 331 deletions(-) From git at git.haskell.org Wed Mar 12 10:18:20 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Mar 2014 10:18:20 +0000 (UTC) Subject: [commit: haddock] ghc-7.8's head updated: Merge tag 'haddock-2.14.0-release' into ghc-7.8 (3945c9a) Message-ID: <20140312101820.538882406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock Branch 'ghc-7.8' now includes: 96838d2 Update CPP check for __GLASGOW_HASKELL__ cf73b00 <+>: Don't insert a space when concatenating empty nodes 7d2106e Fix @ code blocks 18e9417 Update tests 039b234 Handle infix vs prefix names correctly everywhere, by explicitly specifying the context 880b91e Correct whitespace in ?hidden? test for <+> change 1e21c67 Document module header. 01de3a3 Insert a space between module link and description 860d650 Ensure a space between type signature and ?Source? e0718f2 Add support for type/data families bc5756d Improve display of poly-kinded type operators 7e53f62 Add test case for PatternSynonyms d86f688 Get rid of re-implementation of sortBy 50d1d18 Only warn about missing docs when docs are missing 6b35adf Add test case for inter-module type/data family instances 91e2c21 Use a bespoke data type to indicate fixity fc7fd18 Strip a single leading space from bird tracks (#201) dfc006a Turn a source code comment into specs 49b2a05 Update test case for lifted GADT type rendering 1944b94 Don't shadow ?strip?. 14531f7 Make ImplicitParams render correctly (#260) 64850ca Lower precedence of equality constraints 6ca2767 Add RankNTypes test case to ImplicitParams.hs 1bf6869 Fix rendering of Contents when links are present daa0ae5 Fix wording in the docs e5bd27b Change rendering of duplicate record field docs 17970e6 Render fixity information 843c42c Reorder topDeclElem to move the source/wiki links to the top 9aa5a2a Use optLast instead of listToMaybe for sourceUrls/wikiUrls 003f117 Differentiate between TH splices (line-links) and regular names 68a7893 Group similar fixities together c40ee25 Update changelog 28e685d Include fixity information in the Interface file 3f6c34a Update changelog 72f655f Update appearance of fixity annotations b8efaf4 Filter family instances of hidden types b999504 Add documentation for --source-entity-line 5f02bd6 Revert "Reorder topDeclElem to move the source/wiki links to the top" 1063ade Fix up CPP preparing for release with GHC 7.8. 3945c9a Merge tag 'haddock-2.14.0-release' into ghc-7.8 From git at git.haskell.org Wed Mar 12 12:23:06 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Mar 2014 12:23:06 +0000 (UTC) Subject: [commit: ghc] master: Call Arity: Resurrect fakeBoringCalls (7f919de) Message-ID: <20140312122307.1A8252406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7f919dec1579641bbcd02978a0038c8a3723d8b7/ghc >--------------------------------------------------------------- commit 7f919dec1579641bbcd02978a0038c8a3723d8b7 Author: Joachim Breitner Date: Wed Mar 12 11:15:16 2014 +0100 Call Arity: Resurrect fakeBoringCalls (Otherwise the analysis was wrong, as covered by the new test case.) >--------------------------------------------------------------- 7f919dec1579641bbcd02978a0038c8a3723d8b7 compiler/simplCore/CallArity.hs | 16 ++++++++++++++-- testsuite/tests/callarity/unittest/CallArity1.hs | 4 ++++ testsuite/tests/callarity/unittest/CallArity1.stderr | 3 +++ testsuite/tests/perf/compiler/all.T | 3 ++- 4 files changed, 23 insertions(+), 3 deletions(-) diff --git a/compiler/simplCore/CallArity.hs b/compiler/simplCore/CallArity.hs index 6334d8d..db0406d 100644 --- a/compiler/simplCore/CallArity.hs +++ b/compiler/simplCore/CallArity.hs @@ -348,7 +348,8 @@ callArityTopLvl exported int1 (b:bs) exported' = filter isExportedId int2 ++ exported int' = int1 `addInterestingBinds` b (ae1, bs') = callArityTopLvl exported' int' bs - (ae2, b') = callArityBind ae1 int1 b + ae1' = fakeBoringCalls int' b ae1 + (ae2, b') = callArityBind ae1' int1 b callArityRHS :: CoreExpr -> CoreExpr @@ -434,7 +435,8 @@ callArityAnal arity int (Let bind e) where int_body = int `addInterestingBinds` bind (ae_body, e') = callArityAnal arity int_body e - (final_ae, bind') = callArityBind ae_body int bind + ae_body' = fakeBoringCalls int_body bind ae_body + (final_ae, bind') = callArityBind ae_body' int bind -- This is a variant of callArityAnal that is additionally told whether -- the expression is called once or multiple times, and treats thunks appropriately. @@ -468,6 +470,16 @@ addInterestingBinds int bind = int `delVarSetList` bindersOf bind -- Possible shadowing `extendVarSetList` interestingBinds bind +-- For every boring variable in the binder, this amends the CallArityRes to +-- report safe information about them (co-called with everything else, arity 0). +fakeBoringCalls :: VarSet -> CoreBind -> CallArityRes -> CallArityRes +fakeBoringCalls int bind res + = addCrossCoCalls (domRes boring) (domRes res) $ (boring `lubRes` res) + where + boring = ( emptyUnVarGraph + , mkVarEnv [ (v, 0) | v <- bindersOf bind, not (v `elemVarSet` int)]) + + -- Used for both local and top-level binds -- First argument is the demand from the body callArityBind :: CallArityRes -> VarSet -> CoreBind -> (CallArityRes, CoreBind) diff --git a/testsuite/tests/callarity/unittest/CallArity1.hs b/testsuite/tests/callarity/unittest/CallArity1.hs index 8a142d5..6dd6182 100644 --- a/testsuite/tests/callarity/unittest/CallArity1.hs +++ b/testsuite/tests/callarity/unittest/CallArity1.hs @@ -163,6 +163,10 @@ exprs = , (n, Var go `mkApps` [d `mkLApps` [1]]) , (go, mkLams [x] $ mkACase (Var n) (Var go `mkApps` [Var n `mkVarApps` [x]]) ) ]) $ Var go `mkApps` [mkLit 0, go `mkLApps` [0,1]] + , ("a thunk (non-function-type) co-calls with the body (d 1 would be bad)",) $ + mkLet d (f `mkLApps` [0]) $ + mkLet x (d `mkLApps` [1]) $ + Var d `mkVarApps` [x] ] main = do diff --git a/testsuite/tests/callarity/unittest/CallArity1.stderr b/testsuite/tests/callarity/unittest/CallArity1.stderr index d5d7d91..c331a64 100644 --- a/testsuite/tests/callarity/unittest/CallArity1.stderr +++ b/testsuite/tests/callarity/unittest/CallArity1.stderr @@ -78,3 +78,6 @@ a thunk (function type), in mutual recursion, still calls once, d part of mutual go 1 d 1 n 0 +a thunk (non-function-type) co-calls with the body (d 1 would be bad): + x 0 + d 0 diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index fc0abc9..b03a48f 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -133,7 +133,7 @@ test('T3294', # 2012-10-08: 1373514844 (x86/Linux) # 2013-11-13: 1478325844 (x86/Windows, 64bit machine) # 2014-01-12: 1565185140 (x86/Linux) - (wordsize(64), 2897630040, 5)]), + (wordsize(64), 2705289664, 5)]), # old: 1357587088 (amd64/Linux) # 29/08/2012: 2961778696 (amd64/Linux) # (^ increase due to new codegen, see #7198) @@ -141,6 +141,7 @@ test('T3294', # 08/06/2013: 2901451552 (amd64/Linux) (reason unknown) # 12/12/2013: 3083825616 (amd64/Linux) (reason unknown) # 18/02/2014: 2897630040 (amd64/Linux) (call arity improvements) + # 12/03/2014: 2705289664 (amd64/Linux) (more call arity improvements) conf_3294 ], compile, From git at git.haskell.org Wed Mar 12 12:40:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Mar 2014 12:40:17 +0000 (UTC) Subject: [commit: ghc] branch 'T8776' created Message-ID: <20140312124019.0A8952406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : T8776 Referencing: 69b666be35278e9e847512e33a5bd59e8e6c6c2f From git at git.haskell.org Wed Mar 12 12:40:20 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Mar 2014 12:40:20 +0000 (UTC) Subject: [commit: ghc] T8776: Add OutputableBndr instance for OccName (cc4b246) Message-ID: <20140312124020.E129B2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : T8776 Link : http://ghc.haskell.org/trac/ghc/changeset/cc4b24623e403b81e0a98ce8b4c428558269833f/ghc >--------------------------------------------------------------- commit cc4b24623e403b81e0a98ce8b4c428558269833f Author: Dr. ERDI Gergo Date: Wed Mar 12 20:37:22 2014 +0800 Add OutputableBndr instance for OccName >--------------------------------------------------------------- cc4b24623e403b81e0a98ce8b4c428558269833f compiler/basicTypes/OccName.lhs | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/compiler/basicTypes/OccName.lhs b/compiler/basicTypes/OccName.lhs index e993767..2d17b95 100644 --- a/compiler/basicTypes/OccName.lhs +++ b/compiler/basicTypes/OccName.lhs @@ -261,6 +261,11 @@ instance Data OccName where instance Outputable OccName where ppr = pprOccName +instance OutputableBndr OccName where + pprBndr _ = ppr + pprInfixOcc n = pprInfixVar (isSymOcc n) (ppr n) + pprPrefixOcc n = pprPrefixVar (isSymOcc n) (ppr n) + pprOccName :: OccName -> SDoc pprOccName (OccName sp occ) = getPprStyle $ \ sty -> From git at git.haskell.org Wed Mar 12 12:40:23 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Mar 2014 12:40:23 +0000 (UTC) Subject: [commit: ghc] T8776: pprIfaceContextArr: print a context including the "=>" arrow (1c990fc) Message-ID: <20140312124023.300752406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : T8776 Link : http://ghc.haskell.org/trac/ghc/changeset/1c990fca1ed91450a06868d6de3593414890f662/ghc >--------------------------------------------------------------- commit 1c990fca1ed91450a06868d6de3593414890f662 Author: Dr. ERDI Gergo Date: Wed Mar 12 20:38:26 2014 +0800 pprIfaceContextArr: print a context including the "=>" arrow >--------------------------------------------------------------- 1c990fca1ed91450a06868d6de3593414890f662 compiler/iface/IfaceSyn.lhs | 2 +- compiler/iface/IfaceType.lhs | 14 +++++++------- 2 files changed, 8 insertions(+), 8 deletions(-) diff --git a/compiler/iface/IfaceSyn.lhs b/compiler/iface/IfaceSyn.lhs index b582305..3691fca 100644 --- a/compiler/iface/IfaceSyn.lhs +++ b/compiler/iface/IfaceSyn.lhs @@ -1152,7 +1152,7 @@ instance Outputable IfaceAT where pprIfaceDeclHead :: IfaceContext -> OccName -> [IfaceTvBndr] -> SDoc pprIfaceDeclHead context thing tyvars - = hsep [pprIfaceContext context, parenSymOcc thing (ppr thing), + = hsep [pprIfaceContextArr context, parenSymOcc thing (ppr thing), pprIfaceTvBndrs tyvars] pp_condecls :: OccName -> IfaceConDecls -> SDoc diff --git a/compiler/iface/IfaceType.lhs b/compiler/iface/IfaceType.lhs index 822e3da..6d49658 100644 --- a/compiler/iface/IfaceType.lhs +++ b/compiler/iface/IfaceType.lhs @@ -22,7 +22,7 @@ module IfaceType ( toIfaceCoercion, -- Printing - pprIfaceType, pprParendIfaceType, pprIfaceContext, + pprIfaceType, pprParendIfaceType, pprIfaceContext, pprIfaceContextArr, pprIfaceIdBndr, pprIfaceTvBndr, pprIfaceTvBndrs, pprIfaceBndrs, tOP_PREC, tYCON_PREC, noParens, maybeParen, pprIfaceForAllPart, @@ -386,14 +386,14 @@ instance Binary IfaceTyLit where _ -> panic ("get IfaceTyLit " ++ show tag) ------------------- -pprIfaceContext :: Outputable a => [a] -> SDoc +pprIfaceContextArr :: Outputable a => [a] -> SDoc -- Prints "(C a, D b) =>", including the arrow -pprIfaceContext [] = empty -pprIfaceContext theta = ppr_preds theta <+> darrow +pprIfaceContextArr [] = empty +pprIfaceContextArr theta = pprIfaceContext theta <+> darrow -ppr_preds :: Outputable a => [a] -> SDoc -ppr_preds [pred] = ppr pred -- No parens -ppr_preds preds = parens (sep (punctuate comma (map ppr preds))) +pprIfaceContext :: Outputable a => [a] -> SDoc +pprIfaceContext [pred] = ppr pred -- No parens +pprIfaceContext preds = parens (sep (punctuate comma (map ppr preds))) instance Binary IfaceType where put_ bh (IfaceForAllTy aa ab) = do From git at git.haskell.org Wed Mar 12 12:40:26 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Mar 2014 12:40:26 +0000 (UTC) Subject: [commit: ghc] T8776: pprIfaceDecl for IfacePatSyn: use pprPatSynSig (7c4bd5d) Message-ID: <20140312124026.60DB02406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : T8776 Link : http://ghc.haskell.org/trac/ghc/changeset/7c4bd5d9c74c4922341afad9d0de391e6eb4f6e5/ghc >--------------------------------------------------------------- commit 7c4bd5d9c74c4922341afad9d0de391e6eb4f6e5 Author: Dr. ERDI Gergo Date: Wed Mar 12 20:38:54 2014 +0800 pprIfaceDecl for IfacePatSyn: use pprPatSynSig >--------------------------------------------------------------- 7c4bd5d9c74c4922341afad9d0de391e6eb4f6e5 compiler/iface/IfaceSyn.lhs | 26 +++++++++++--------------- 1 file changed, 11 insertions(+), 15 deletions(-) diff --git a/compiler/iface/IfaceSyn.lhs b/compiler/iface/IfaceSyn.lhs index 3691fca..8ca8582 100644 --- a/compiler/iface/IfaceSyn.lhs +++ b/compiler/iface/IfaceSyn.lhs @@ -55,6 +55,7 @@ import TysWiredIn ( eqTyConName ) import Fingerprint import Binary import BooleanFormula ( BooleanFormula ) +import HsBinds import Control.Monad import System.IO.Unsafe @@ -1104,27 +1105,22 @@ pprIfaceDecl (IfaceAxiom {ifName = name, ifTyCon = tycon, ifAxBranches = branche pprIfaceDecl (IfacePatSyn { ifName = name, ifPatHasWrapper = has_wrap, ifPatIsInfix = is_infix, - ifPatUnivTvs = univ_tvs, ifPatExTvs = ex_tvs, + ifPatUnivTvs = _univ_tvs, ifPatExTvs = _ex_tvs, ifPatProvCtxt = prov_ctxt, ifPatReqCtxt = req_ctxt, ifPatArgs = args, ifPatTy = ty }) - = hang (text "pattern" <+> header) - 4 details + = pprPatSynSig name has_wrap args' ty' (pprCtxt prov_ctxt) (pprCtxt req_ctxt) where - header = ppr name <+> dcolon <+> - (pprIfaceForAllPart univ_tvs req_ctxt $ - pprIfaceForAllPart ex_tvs prov_ctxt $ - pp_tau) + args' = case (is_infix, map snd args) of + (True, [left_ty, right_ty]) -> + InfixPatSyn (pprParendIfaceType left_ty) (pprParendIfaceType right_ty) + (_, tys) -> + PrefixPatSyn (map pprParendIfaceType tys) - details = sep [ if is_infix then text "Infix" else empty - , if has_wrap then text "HasWrapper" else empty - ] + ty' = pprParendIfaceType ty - pp_tau = case map pprParendIfaceType (arg_tys ++ [ty]) of - (t:ts) -> fsep (t : map (arrow <+>) ts) - [] -> panic "pp_tau" - - arg_tys = map snd args + pprCtxt [] = Nothing + pprCtxt ctxt = Just $ pprIfaceContext ctxt pprCType :: Maybe CType -> SDoc pprCType Nothing = ptext (sLit "No C type associated") From git at git.haskell.org Wed Mar 12 12:40:28 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 12 Mar 2014 12:40:28 +0000 (UTC) Subject: [commit: ghc] T8776: ppr_ty_thing: print PatSynCons via IfaceDecl (see #8776 for background) (69b666b) Message-ID: <20140312124029.62CA72406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : T8776 Link : http://ghc.haskell.org/trac/ghc/changeset/69b666be35278e9e847512e33a5bd59e8e6c6c2f/ghc >--------------------------------------------------------------- commit 69b666be35278e9e847512e33a5bd59e8e6c6c2f Author: Dr. ERDI Gergo Date: Wed Mar 12 20:39:42 2014 +0800 ppr_ty_thing: print PatSynCons via IfaceDecl (see #8776 for background) >--------------------------------------------------------------- 69b666be35278e9e847512e33a5bd59e8e6c6c2f compiler/main/PprTyThing.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/compiler/main/PprTyThing.hs b/compiler/main/PprTyThing.hs index 27e7390..53c24fc 100644 --- a/compiler/main/PprTyThing.hs +++ b/compiler/main/PprTyThing.hs @@ -37,6 +37,7 @@ import Type( tidyTopType, tidyOpenType, splitForAllTys, funResultTy ) import Kind( synTyConResKind ) import TypeRep( pprTvBndrs, pprForAll, suppressKinds ) import TysPrim( alphaTyVars ) +import MkIface ( tyThingToIfaceDecl ) import TcType import Name import VarEnv( emptyTidyEnv ) @@ -110,9 +111,9 @@ pprTyThingHdr (ACoAxiom ax) = pprCoAxiom ax ------------------------ ppr_ty_thing :: ShowSub -> TyThing -> SDoc ppr_ty_thing _ (AnId id) = pprId id -ppr_ty_thing _ (AConLike conLike) = case conLike of +ppr_ty_thing _ tyThing@(AConLike conLike) = case conLike of RealDataCon dataCon -> pprDataConSig dataCon - PatSynCon patSyn -> pprPatSyn patSyn + PatSynCon _patSyn -> ppr $ tyThingToIfaceDecl tyThing ppr_ty_thing ss (ATyCon tyCon) = pprTyCon ss tyCon ppr_ty_thing _ (ACoAxiom ax) = pprCoAxiom ax From git at git.haskell.org Thu Mar 13 12:25:09 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 12:25:09 +0000 (UTC) Subject: [commit: ghc] master: Comments on virtHp, realHp (Trac #8864) (b0416e7) Message-ID: <20140313122509.97D4B2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b0416e776d2959ac8b9903eb9301b7b967c53a8e/ghc >--------------------------------------------------------------- commit b0416e776d2959ac8b9903eb9301b7b967c53a8e Author: Simon Peyton Jones Date: Tue Mar 11 13:09:21 2014 +0000 Comments on virtHp, realHp (Trac #8864) Documentation in response to Johan's questions Plus, don't export hpRel from StgCmmHeap, StgCmmLayout (it is only used locally in StgCmmLayout) >--------------------------------------------------------------- b0416e776d2959ac8b9903eb9301b7b967c53a8e compiler/codeGen/StgCmmHeap.hs | 2 +- compiler/codeGen/StgCmmLayout.hs | 5 +++-- compiler/codeGen/StgCmmMonad.hs | 36 +++++++++++++++++++++++++++++++++--- 3 files changed, 37 insertions(+), 6 deletions(-) diff --git a/compiler/codeGen/StgCmmHeap.hs b/compiler/codeGen/StgCmmHeap.hs index 488a0e0..a3a47a6 100644 --- a/compiler/codeGen/StgCmmHeap.hs +++ b/compiler/codeGen/StgCmmHeap.hs @@ -8,7 +8,7 @@ module StgCmmHeap ( getVirtHp, setVirtHp, setRealHp, - getHpRelOffset, hpRel, + getHpRelOffset, entryHeapCheck, altHeapCheck, noEscapeHeapCheck, altHeapCheckReturnsTo, heapStackCheckGen, diff --git a/compiler/codeGen/StgCmmLayout.hs b/compiler/codeGen/StgCmmLayout.hs index 7fbcbce..59afc89 100644 --- a/compiler/codeGen/StgCmmLayout.hs +++ b/compiler/codeGen/StgCmmLayout.hs @@ -15,7 +15,7 @@ module StgCmmLayout ( slowCall, directCall, - mkVirtHeapOffsets, mkVirtConstrOffsets, getHpRelOffset, hpRel, + mkVirtHeapOffsets, mkVirtConstrOffsets, getHpRelOffset, ArgRep(..), toArgRep, argRepSizeW -- re-exported from StgCmmArgRep ) where @@ -366,13 +366,14 @@ slowArgs dflags args -- careful: reps contains voids (V), but args does not ---- Laying out objects on the heap and stack ------------------------------------------------------------------------- --- The heap always grows upwards, so hpRel is easy +-- The heap always grows upwards, so hpRel is easy to compute hpRel :: VirtualHpOffset -- virtual offset of Hp -> VirtualHpOffset -- virtual offset of The Thing -> WordOff -- integer word offset hpRel hp off = off - hp getHpRelOffset :: VirtualHpOffset -> FCode CmmExpr +-- See Note [Virtual and real heap pointers] in StgCmmMonad getHpRelOffset virtual_offset = do dflags <- getDynFlags hp_usg <- getHpUsage diff --git a/compiler/codeGen/StgCmmMonad.hs b/compiler/codeGen/StgCmmMonad.hs index 3d82e69..348b7b9 100644 --- a/compiler/codeGen/StgCmmMonad.hs +++ b/compiler/codeGen/StgCmmMonad.hs @@ -331,17 +331,47 @@ data CgState cgs_uniqs :: UniqSupply } -data HeapUsage = - HeapUsage { +data HeapUsage -- See Note [Virtual and real heap pointers] + = HeapUsage { virtHp :: VirtualHpOffset, -- Virtual offset of highest-allocated word -- Incremented whenever we allocate realHp :: VirtualHpOffset -- realHp: Virtual offset of real heap ptr -- Used in instruction addressing modes - } + } type VirtualHpOffset = WordOff +{- Note [Virtual and real heap pointers] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +The code generator can allocate one or more objects contiguously, performing +one heap check to cover allocation of all the objects at once. Let's call +this little chunk of heap space an "allocation chunk". The code generator +will emit code to + * Perform a heap-exhaustion check + * Move the heap pointer to the end of the allocation chunk + * Allocate multiple objects within the chunk + +The code generator uses VirtualHpOffsets to address words within a +single allocation chunk; these start at one and increase positively. +The first word of the chunk has VirtualHpOffset=1, the second has +VirtualHpOffset=2, and so on. + + * The field realHp tracks (the VirtualHpOffset) where the real Hp + register is pointing. Typically it'll be pointing to the end of the + allocation chunk. + + * The field virtHp gives the VirtualHpOffset of the highest-allocated + word so far. It starts at zero (meaning no word has been allocated), + and increases whenever an object is allocated. + +The difference between realHp and virtHp gives the offset from the +real Hp register of a particular word in the allocation chunk. This +is what getHpRelOffset does. Since the returned offset is relative +to the real Hp register, it is valid only until you change the real +Hp register. (Changing virtHp doesn't matter.) +-} + initCgState :: UniqSupply -> CgState initCgState uniqs From git at git.haskell.org Thu Mar 13 12:25:12 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 12:25:12 +0000 (UTC) Subject: [commit: ghc] master: A bit more tracing to do with SPECIALISE pragmas (b340681) Message-ID: <20140313122513.15B212406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b34068144ec3d7bfe4279b16ad16d54dd46f1c5a/ghc >--------------------------------------------------------------- commit b34068144ec3d7bfe4279b16ad16d54dd46f1c5a Author: Simon Peyton Jones Date: Thu Mar 13 08:36:28 2014 +0000 A bit more tracing to do with SPECIALISE pragmas >--------------------------------------------------------------- b34068144ec3d7bfe4279b16ad16d54dd46f1c5a compiler/deSugar/DsBinds.lhs | 6 +++--- compiler/typecheck/TcBinds.lhs | 3 ++- 2 files changed, 5 insertions(+), 4 deletions(-) diff --git a/compiler/deSugar/DsBinds.lhs b/compiler/deSugar/DsBinds.lhs index cd683ba..6d247dd 100644 --- a/compiler/deSugar/DsBinds.lhs +++ b/compiler/deSugar/DsBinds.lhs @@ -596,7 +596,7 @@ decomposeRuleLhs bndrs lhs where args' = [Type (idType bndr), Type ty, scrut, body] - _other -> Left bad_shape_msg + _other -> Left bad_shape_msg where opt_lhs = simpleOptExpr lhs @@ -614,9 +614,9 @@ decomposeRuleLhs bndrs lhs | d <- varSetElems (arg_fvs `delVarSetList` bndrs) , isDictId d] - bad_shape_msg = hang (ptext (sLit "RULE left-hand side too complicated to desugar")) - 2 (ppr opt_lhs) + 2 (vcat [ text "Optimised lhs:" <+> ppr opt_lhs + , text "Orig lhs:" <+> ppr lhs]) dead_msg bndr = hang (sep [ ptext (sLit "Forall'd") <+> pp_bndr bndr , ptext (sLit "is not bound in RULE lhs")]) 2 (ppr opt_lhs) diff --git a/compiler/typecheck/TcBinds.lhs b/compiler/typecheck/TcBinds.lhs index 5725e09..8b2928c 100644 --- a/compiler/typecheck/TcBinds.lhs +++ b/compiler/typecheck/TcBinds.lhs @@ -739,7 +739,8 @@ tcSpecPrags :: Id -> [LSig Name] -- Pre-condition: the poly_id is zonked -- Reason: required by tcSubExp tcSpecPrags poly_id prag_sigs - = do { unless (null bad_sigs) warn_discarded_sigs + = do { traceTc "tcSpecPrags" (ppr poly_id <+> ppr spec_sigs) + ; unless (null bad_sigs) warn_discarded_sigs ; mapAndRecoverM (wrapLocM (tcSpec poly_id)) spec_sigs } where spec_sigs = filter isSpecLSig prag_sigs From git at git.haskell.org Thu Mar 13 12:25:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 12:25:15 +0000 (UTC) Subject: [commit: ghc] master: Export runTcInteractive from TcRnDriver, and from GHC (Trac #8878) (60bbc0a) Message-ID: <20140313122515.4A4E52406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/60bbc0af79ddfe977d93e271b57c2bc25d3fcde6/ghc >--------------------------------------------------------------- commit 60bbc0af79ddfe977d93e271b57c2bc25d3fcde6 Author: Simon Peyton Jones Date: Thu Mar 13 12:13:49 2014 +0000 Export runTcInteractive from TcRnDriver, and from GHC (Trac #8878) >--------------------------------------------------------------- 60bbc0af79ddfe977d93e271b57c2bc25d3fcde6 compiler/main/GHC.hs | 2 ++ compiler/typecheck/TcRnDriver.lhs | 1 + 2 files changed, 3 insertions(+) diff --git a/compiler/main/GHC.hs b/compiler/main/GHC.hs index 553d1a9..5fe384e 100644 --- a/compiler/main/GHC.hs +++ b/compiler/main/GHC.hs @@ -102,6 +102,7 @@ module GHC ( parseName, RunResult(..), runStmt, runStmtWithLocation, runDecls, runDeclsWithLocation, + runTcInteractive, -- Desired by some clients (Trac #8878) parseImportDecl, SingleStep(..), resume, Resume(resumeStmt, resumeThreadId, resumeBreakInfo, resumeSpan, @@ -257,6 +258,7 @@ module GHC ( import ByteCodeInstr import BreakArray import InteractiveEval +import TcRnDriver ( runTcInteractive ) #endif import HscMain diff --git a/compiler/typecheck/TcRnDriver.lhs b/compiler/typecheck/TcRnDriver.lhs index dad2c67..90d7151 100644 --- a/compiler/typecheck/TcRnDriver.lhs +++ b/compiler/typecheck/TcRnDriver.lhs @@ -13,6 +13,7 @@ module TcRnDriver ( getModuleInterface, tcRnDeclsi, isGHCiMonad, + runTcInteractive, -- Used by GHC API clients (Trac #8878) #endif tcRnLookupName, tcRnGetInfo, From git at git.haskell.org Thu Mar 13 12:25:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 12:25:17 +0000 (UTC) Subject: [commit: ghc] master: Comments only (7ef90e3) Message-ID: <20140313122518.383332406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7ef90e3a4d1e043ebb574b05c8da0d4148ed297b/ghc >--------------------------------------------------------------- commit 7ef90e3a4d1e043ebb574b05c8da0d4148ed297b Author: Simon Peyton Jones Date: Thu Mar 13 12:14:11 2014 +0000 Comments only >--------------------------------------------------------------- 7ef90e3a4d1e043ebb574b05c8da0d4148ed297b compiler/typecheck/TcTyClsDecls.lhs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/compiler/typecheck/TcTyClsDecls.lhs b/compiler/typecheck/TcTyClsDecls.lhs index 0c5ceea..05dc029 100644 --- a/compiler/typecheck/TcTyClsDecls.lhs +++ b/compiler/typecheck/TcTyClsDecls.lhs @@ -1019,7 +1019,9 @@ tcFamTyPats :: Name -- of the family ToCon -> Kind -- of the family TyCon -> HsWithBndrs [LHsType Name] -- patterns -> (TcKind -> TcM ()) -- kind-checker for RHS - -> ([TKVar] -> [TcType] -> Kind -> TcM a) + -> ([TKVar] -- Kind and type variables + -> [TcType] -- Kind and type arguments + -> Kind -> TcM a) -> TcM a tcFamTyPats fam_tc_name kind pats kind_checker thing_inside = do { (fam_arg_kinds, typats, res_kind) From git at git.haskell.org Thu Mar 13 12:25:20 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 12:25:20 +0000 (UTC) Subject: [commit: ghc] master: Add BuiltinRules for constant-folding not# and notI# (logical complement) (8fd7d58) Message-ID: <20140313122520.730932406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8fd7d581da448d81fc2f9d47366c36c5f57ed564/ghc >--------------------------------------------------------------- commit 8fd7d581da448d81fc2f9d47366c36c5f57ed564 Author: Simon Peyton Jones Date: Thu Mar 13 12:15:52 2014 +0000 Add BuiltinRules for constant-folding not# and notI# (logical complement) I don't know why these constant-folding rules were implemented for and/or/xor but not for 'not'. Adding them is part of the fix for Trac #8832. (The other part is in Data.Bits.) >--------------------------------------------------------------- 8fd7d581da448d81fc2f9d47366c36c5f57ed564 compiler/prelude/PrelRules.lhs | 9 +++++++++ 1 file changed, 9 insertions(+) diff --git a/compiler/prelude/PrelRules.lhs b/compiler/prelude/PrelRules.lhs index 11367ed..7867806 100644 --- a/compiler/prelude/PrelRules.lhs +++ b/compiler/prelude/PrelRules.lhs @@ -111,6 +111,8 @@ primOpRules nm OrIOp = mkPrimOpRule nm 2 [ binaryLit (intOp2 (.|.)) primOpRules nm XorIOp = mkPrimOpRule nm 2 [ binaryLit (intOp2 xor) , identityDynFlags zeroi , equalArgs >> retLit zeroi ] +primOpRules nm NotIOp = mkPrimOpRule nm 1 [ unaryLit complementOp + , inversePrimOp NotIOp ] primOpRules nm IntNegOp = mkPrimOpRule nm 1 [ unaryLit negOp , inversePrimOp IntNegOp ] primOpRules nm ISllOp = mkPrimOpRule nm 2 [ binaryLit (intOp2 Bits.shiftL) @@ -141,6 +143,8 @@ primOpRules nm OrOp = mkPrimOpRule nm 2 [ binaryLit (wordOp2 (.|.)) primOpRules nm XorOp = mkPrimOpRule nm 2 [ binaryLit (wordOp2 xor) , identityDynFlags zerow , equalArgs >> retLit zerow ] +primOpRules nm NotOp = mkPrimOpRule nm 1 [ unaryLit complementOp + , inversePrimOp NotOp ] primOpRules nm SllOp = mkPrimOpRule nm 2 [ wordShiftRule Bits.shiftL ] primOpRules nm SrlOp = mkPrimOpRule nm 2 [ wordShiftRule shiftRightLogical ] @@ -345,6 +349,11 @@ negOp dflags (MachDouble d) = Just (mkDoubleVal dflags (-d)) negOp dflags (MachInt i) = intResult dflags (-i) negOp _ _ = Nothing +complementOp :: DynFlags -> Literal -> Maybe CoreExpr -- Binary complement +complementOp dflags (MachWord i) = wordResult dflags (complement i) +complementOp dflags (MachInt i) = intResult dflags (complement i) +complementOp _ _ = Nothing + -------------------------- intOp2 :: (Integral a, Integral b) => (a -> b -> Integer) From git at git.haskell.org Thu Mar 13 12:25:23 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 12:25:23 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #8832 (ea6dcef) Message-ID: <20140313122524.051EB2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ea6dcef1d9800953b1791304d52884359f415ad9/ghc >--------------------------------------------------------------- commit ea6dcef1d9800953b1791304d52884359f415ad9 Author: Simon Peyton Jones Date: Thu Mar 13 12:24:49 2014 +0000 Test Trac #8832 The test is a bit crude; -ddump-simpl | grep '#'. I'm concerned that the -ddump-simpl output may differ on 32 and 64-bit platforms. So far I've only put in output for 64-bit platforms. >--------------------------------------------------------------- ea6dcef1d9800953b1791304d52884359f415ad9 testsuite/tests/simplCore/should_compile/Makefile | 4 +++ testsuite/tests/simplCore/should_compile/T8832.hs | 28 ++++++++++++++++++++ .../tests/simplCore/should_compile/T8832.stdout | 10 +++++++ testsuite/tests/simplCore/should_compile/all.T | 5 +++- 4 files changed, 46 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/simplCore/should_compile/Makefile b/testsuite/tests/simplCore/should_compile/Makefile index 60ad4c7..ca0d552 100644 --- a/testsuite/tests/simplCore/should_compile/Makefile +++ b/testsuite/tests/simplCore/should_compile/Makefile @@ -2,6 +2,10 @@ TOP=../../.. include $(TOP)/mk/boilerplate.mk include $(TOP)/mk/test.mk +T8832: + $(RM) -f T8832.o T8832.hi + '$(TEST_HC)' $(TEST_HC_OPTS) -O -c -ddump-simpl T8832.hs | grep '#' + T7865: $(RM) -f T7865.o T7865.hi '$(TEST_HC)' $(TEST_HC_OPTS) -dsuppress-uniques -O2 -c -ddump-simpl T7865.hs | grep expensive diff --git a/testsuite/tests/simplCore/should_compile/T8832.hs b/testsuite/tests/simplCore/should_compile/T8832.hs new file mode 100644 index 0000000..9059a18 --- /dev/null +++ b/testsuite/tests/simplCore/should_compile/T8832.hs @@ -0,0 +1,28 @@ +{-# LANGUAGE CPP #-} + +-- I'm concerned that the -ddump-simpl output may differ on 32 and 64-bit +-- platforms. So far I've only put in output for 64-bit platforms. + +module T8832 where + +import Data.Bits +import Data.Int +import Data.Word + +#define T(s,T) \ +s :: T ; \ +s = clearBit (bit 0) 0 ; \ + +T(i,Int) +T(i8,Int8) +T(i16,Int16) +T(i32,Int32) +T(i64,Int64) + +T(w,Word) +T(w8,Word8) +T(w16,Word16) +T(w32,Word32) +T(w64,Word64) + +T(z,Integer) \ No newline at end of file diff --git a/testsuite/tests/simplCore/should_compile/T8832.stdout b/testsuite/tests/simplCore/should_compile/T8832.stdout new file mode 100644 index 0000000..2719631 --- /dev/null +++ b/testsuite/tests/simplCore/should_compile/T8832.stdout @@ -0,0 +1,10 @@ +T8832.i = GHC.Types.I# 0 +T8832.i8 = GHC.Int.I8# 0 +T8832.i16 = GHC.Int.I16# 0 +T8832.i32 = GHC.Int.I32# 0 +T8832.i64 = GHC.Int.I64# 0 +T8832.w = GHC.Types.W# (__word 0) +T8832.w8 = GHC.Word.W8# (__word 0) +T8832.w16 = GHC.Word.W16# (__word 0) +T8832.w32 = GHC.Word.W32# (__word 0) +T8832.w64 = GHC.Word.W64# (__word 0) diff --git a/testsuite/tests/simplCore/should_compile/all.T b/testsuite/tests/simplCore/should_compile/all.T index 2f2b337..9e77926 100644 --- a/testsuite/tests/simplCore/should_compile/all.T +++ b/testsuite/tests/simplCore/should_compile/all.T @@ -198,4 +198,7 @@ test('T5996', run_command, ['$MAKE -s --no-print-directory T5996']) test('T8537', normal, compile, ['']) -test('T8714', normal, compile, ['']) +test('T8832', + extra_clean(['T8832.hi', 'T8832a.o']), + run_command, + ['$MAKE -s --no-print-directory T8832']) From git at git.haskell.org Thu Mar 13 12:26:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 12:26:47 +0000 (UTC) Subject: [commit: packages/base] master: Add shiftR and shiftL implementations to instance Bits Integer (f7a7b58) Message-ID: <20140313122651.B6C762406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/base On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f7a7b586bc89ca7fd56792da4172bd93a2acdae9/base >--------------------------------------------------------------- commit f7a7b586bc89ca7fd56792da4172bd93a2acdae9 Author: Simon Peyton Jones Date: Thu Mar 13 12:11:01 2014 +0000 Add shiftR and shiftL implementations to instance Bits Integer Apart from simply making sense (avoid the conditional in 'shift'), this makes left and right shifts on Integer more likely to inline (plain 'shift' is just too large); and this in turn is important when fixing the Integer case of #8832 >--------------------------------------------------------------- f7a7b586bc89ca7fd56792da4172bd93a2acdae9 Data/Bits.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/Data/Bits.hs b/Data/Bits.hs index 28cd024..81b180b 100644 --- a/Data/Bits.hs +++ b/Data/Bits.hs @@ -437,6 +437,9 @@ instance Bits Integer where complement = complementInteger shift x i@(I# i#) | i >= 0 = shiftLInteger x i# | otherwise = shiftRInteger x (negateInt# i#) + shiftL x (I# i#) = shiftLInteger x i# + shiftR x (I# i#) = shiftRInteger x i# + testBit x (I# i) = testBitInteger x i zeroBits = 0 From git at git.haskell.org Thu Mar 13 12:26:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 12:26:50 +0000 (UTC) Subject: [commit: packages/base] master: Comments only, about the "RA" and "RL" nomenclature for shifts (f109bb0) Message-ID: <20140313122651.EDB8C24069@ghc.haskell.org> Repository : ssh://git at git.haskell.org/base On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f109bb03353dd81a1fa2820de3a199e3e5841ee0/base >--------------------------------------------------------------- commit f109bb03353dd81a1fa2820de3a199e3e5841ee0 Author: Simon Peyton Jones Date: Thu Mar 13 12:11:36 2014 +0000 Comments only, about the "RA" and "RL" nomenclature for shifts >--------------------------------------------------------------- f109bb03353dd81a1fa2820de3a199e3e5841ee0 GHC/Base.lhs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/GHC/Base.lhs b/GHC/Base.lhs index d876202..0a2dd80 100644 --- a/GHC/Base.lhs +++ b/GHC/Base.lhs @@ -694,6 +694,8 @@ a `shiftL#` b | isTrue# (b >=# WORD_SIZE_IN_BITS#) = 0## -- | Shift the argument right by the specified number of bits -- (which must be non-negative). +-- The "RL" means "right, logical" (as opposed to RA for arithmetic) +-- (although an arithmetic right shift wouldn't make sense for Word#) shiftRL# :: Word# -> Int# -> Word# a `shiftRL#` b | isTrue# (b >=# WORD_SIZE_IN_BITS#) = 0## | otherwise = a `uncheckedShiftRL#` b @@ -706,6 +708,7 @@ a `iShiftL#` b | isTrue# (b >=# WORD_SIZE_IN_BITS#) = 0# -- | Shift the argument right (signed) by the specified number of bits -- (which must be non-negative). +-- The "RA" means "right, arithmetic" (as opposed to RL for logical) iShiftRA# :: Int# -> Int# -> Int# a `iShiftRA#` b | isTrue# (b >=# WORD_SIZE_IN_BITS#) = if isTrue# (a <# 0#) then (-1#) @@ -714,6 +717,7 @@ a `iShiftRA#` b | isTrue# (b >=# WORD_SIZE_IN_BITS#) = if isTrue# (a <# 0#) -- | Shift the argument right (unsigned) by the specified number of bits -- (which must be non-negative). +-- The "RL" means "right, logical" (as opposed to RA for arithmetic) iShiftRL# :: Int# -> Int# -> Int# a `iShiftRL#` b | isTrue# (b >=# WORD_SIZE_IN_BITS#) = 0# | otherwise = a `uncheckedIShiftRL#` b From git at git.haskell.org Thu Mar 13 12:26:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 12:26:52 +0000 (UTC) Subject: [commit: packages/base] master: Use not# rather than (`xor#` (-1)) for complement (b2dce68) Message-ID: <20140313122652.6E8E82406F@ghc.haskell.org> Repository : ssh://git at git.haskell.org/base On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b2dce687bd5d1f568fa7ef50ee201310ee24fe80/base >--------------------------------------------------------------- commit b2dce687bd5d1f568fa7ef50ee201310ee24fe80 Author: Simon Peyton Jones Date: Thu Mar 13 12:12:53 2014 +0000 Use not# rather than (`xor#` (-1)) for complement I'm not sure why we weren't using not# before; maybe it wasn't a primpop at that stage? Strange. >--------------------------------------------------------------- b2dce687bd5d1f568fa7ef50ee201310ee24fe80 GHC/Int.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/GHC/Int.hs b/GHC/Int.hs index b9a807e..899d9ad 100644 --- a/GHC/Int.hs +++ b/GHC/Int.hs @@ -139,7 +139,7 @@ instance Bits Int8 where (I8# x#) .&. (I8# y#) = I8# (word2Int# (int2Word# x# `and#` int2Word# y#)) (I8# x#) .|. (I8# y#) = I8# (word2Int# (int2Word# x# `or#` int2Word# y#)) (I8# x#) `xor` (I8# y#) = I8# (word2Int# (int2Word# x# `xor#` int2Word# y#)) - complement (I8# x#) = I8# (word2Int# (int2Word# x# `xor#` int2Word# (-1#))) + complement (I8# x#) = I8# (word2Int# (not# (int2Word# x#))) (I8# x#) `shift` (I# i#) | isTrue# (i# >=# 0#) = I8# (narrow8Int# (x# `iShiftL#` i#)) | otherwise = I8# (x# `iShiftRA#` negateInt# i#) @@ -298,7 +298,7 @@ instance Bits Int16 where (I16# x#) .&. (I16# y#) = I16# (word2Int# (int2Word# x# `and#` int2Word# y#)) (I16# x#) .|. (I16# y#) = I16# (word2Int# (int2Word# x# `or#` int2Word# y#)) (I16# x#) `xor` (I16# y#) = I16# (word2Int# (int2Word# x# `xor#` int2Word# y#)) - complement (I16# x#) = I16# (word2Int# (int2Word# x# `xor#` int2Word# (-1#))) + complement (I16# x#) = I16# (word2Int# (not# (int2Word# x#))) (I16# x#) `shift` (I# i#) | isTrue# (i# >=# 0#) = I16# (narrow16Int# (x# `iShiftL#` i#)) | otherwise = I16# (x# `iShiftRA#` negateInt# i#) @@ -462,7 +462,7 @@ instance Bits Int32 where (I32# x#) .&. (I32# y#) = I32# (word2Int# (int2Word# x# `and#` int2Word# y#)) (I32# x#) .|. (I32# y#) = I32# (word2Int# (int2Word# x# `or#` int2Word# y#)) (I32# x#) `xor` (I32# y#) = I32# (word2Int# (int2Word# x# `xor#` int2Word# y#)) - complement (I32# x#) = I32# (word2Int# (int2Word# x# `xor#` int2Word# (-1#))) + complement (I32# x#) = I32# (word2Int# (not# (int2Word# x#))) (I32# x#) `shift` (I# i#) | isTrue# (i# >=# 0#) = I32# (narrow32Int# (x# `iShiftL#` i#)) | otherwise = I32# (x# `iShiftRA#` negateInt# i#) From git at git.haskell.org Thu Mar 13 13:13:55 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 13:13:55 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T8776' created Message-ID: <20140313131356.2341D2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T8776 Referencing: 14d306bbffe5f820424b0ae46c04ceb5d368b3ae From git at git.haskell.org Thu Mar 13 13:13:58 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 13:13:58 +0000 (UTC) Subject: [commit: ghc] wip/T8776: pprIfaceDecl for IfacePatSyn: use pprPatSynSig (880a37b) Message-ID: <20140313131358.55E4F2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8776 Link : http://ghc.haskell.org/trac/ghc/changeset/880a37bd08b431699d8585c522e7f5b9ac33bc21/ghc >--------------------------------------------------------------- commit 880a37bd08b431699d8585c522e7f5b9ac33bc21 Author: Dr. ERDI Gergo Date: Wed Mar 12 20:38:54 2014 +0800 pprIfaceDecl for IfacePatSyn: use pprPatSynSig >--------------------------------------------------------------- 880a37bd08b431699d8585c522e7f5b9ac33bc21 compiler/iface/IfaceSyn.lhs | 26 +++++++++++--------------- 1 file changed, 11 insertions(+), 15 deletions(-) diff --git a/compiler/iface/IfaceSyn.lhs b/compiler/iface/IfaceSyn.lhs index 3691fca..8ca8582 100644 --- a/compiler/iface/IfaceSyn.lhs +++ b/compiler/iface/IfaceSyn.lhs @@ -55,6 +55,7 @@ import TysWiredIn ( eqTyConName ) import Fingerprint import Binary import BooleanFormula ( BooleanFormula ) +import HsBinds import Control.Monad import System.IO.Unsafe @@ -1104,27 +1105,22 @@ pprIfaceDecl (IfaceAxiom {ifName = name, ifTyCon = tycon, ifAxBranches = branche pprIfaceDecl (IfacePatSyn { ifName = name, ifPatHasWrapper = has_wrap, ifPatIsInfix = is_infix, - ifPatUnivTvs = univ_tvs, ifPatExTvs = ex_tvs, + ifPatUnivTvs = _univ_tvs, ifPatExTvs = _ex_tvs, ifPatProvCtxt = prov_ctxt, ifPatReqCtxt = req_ctxt, ifPatArgs = args, ifPatTy = ty }) - = hang (text "pattern" <+> header) - 4 details + = pprPatSynSig name has_wrap args' ty' (pprCtxt prov_ctxt) (pprCtxt req_ctxt) where - header = ppr name <+> dcolon <+> - (pprIfaceForAllPart univ_tvs req_ctxt $ - pprIfaceForAllPart ex_tvs prov_ctxt $ - pp_tau) + args' = case (is_infix, map snd args) of + (True, [left_ty, right_ty]) -> + InfixPatSyn (pprParendIfaceType left_ty) (pprParendIfaceType right_ty) + (_, tys) -> + PrefixPatSyn (map pprParendIfaceType tys) - details = sep [ if is_infix then text "Infix" else empty - , if has_wrap then text "HasWrapper" else empty - ] + ty' = pprParendIfaceType ty - pp_tau = case map pprParendIfaceType (arg_tys ++ [ty]) of - (t:ts) -> fsep (t : map (arrow <+>) ts) - [] -> panic "pp_tau" - - arg_tys = map snd args + pprCtxt [] = Nothing + pprCtxt ctxt = Just $ pprIfaceContext ctxt pprCType :: Maybe CType -> SDoc pprCType Nothing = ptext (sLit "No C type associated") From git at git.haskell.org Thu Mar 13 13:14:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 13:14:01 +0000 (UTC) Subject: [commit: ghc] wip/T8776: pprIfaceContextArr: print a context including the "=>" arrow (2277d0e) Message-ID: <20140313131401.96E932406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8776 Link : http://ghc.haskell.org/trac/ghc/changeset/2277d0ea9533d5da5b45d7503a792c282bc1b37e/ghc >--------------------------------------------------------------- commit 2277d0ea9533d5da5b45d7503a792c282bc1b37e Author: Dr. ERDI Gergo Date: Wed Mar 12 20:38:26 2014 +0800 pprIfaceContextArr: print a context including the "=>" arrow >--------------------------------------------------------------- 2277d0ea9533d5da5b45d7503a792c282bc1b37e compiler/iface/IfaceSyn.lhs | 2 +- compiler/iface/IfaceType.lhs | 16 ++++++++-------- 2 files changed, 9 insertions(+), 9 deletions(-) diff --git a/compiler/iface/IfaceSyn.lhs b/compiler/iface/IfaceSyn.lhs index b582305..3691fca 100644 --- a/compiler/iface/IfaceSyn.lhs +++ b/compiler/iface/IfaceSyn.lhs @@ -1152,7 +1152,7 @@ instance Outputable IfaceAT where pprIfaceDeclHead :: IfaceContext -> OccName -> [IfaceTvBndr] -> SDoc pprIfaceDeclHead context thing tyvars - = hsep [pprIfaceContext context, parenSymOcc thing (ppr thing), + = hsep [pprIfaceContextArr context, parenSymOcc thing (ppr thing), pprIfaceTvBndrs tyvars] pp_condecls :: OccName -> IfaceConDecls -> SDoc diff --git a/compiler/iface/IfaceType.lhs b/compiler/iface/IfaceType.lhs index 822e3da..8c1791a 100644 --- a/compiler/iface/IfaceType.lhs +++ b/compiler/iface/IfaceType.lhs @@ -22,7 +22,7 @@ module IfaceType ( toIfaceCoercion, -- Printing - pprIfaceType, pprParendIfaceType, pprIfaceContext, + pprIfaceType, pprParendIfaceType, pprIfaceContext, pprIfaceContextArr, pprIfaceIdBndr, pprIfaceTvBndr, pprIfaceTvBndrs, pprIfaceBndrs, tOP_PREC, tYCON_PREC, noParens, maybeParen, pprIfaceForAllPart, @@ -253,7 +253,7 @@ ppr_ty ctxt_prec ty@(IfaceForAllTy _ _) -- generality pprIfaceForAllPart :: Outputable a => [IfaceTvBndr] -> [a] -> SDoc -> SDoc pprIfaceForAllPart tvs ctxt doc - = sep [ppr_tvs, pprIfaceContext ctxt, doc] + = sep [ppr_tvs, pprIfaceContextArr ctxt, doc] where ppr_tvs | null tvs = empty | otherwise = ptext (sLit "forall") <+> pprIfaceTvBndrs tvs <> dot @@ -386,14 +386,14 @@ instance Binary IfaceTyLit where _ -> panic ("get IfaceTyLit " ++ show tag) ------------------- -pprIfaceContext :: Outputable a => [a] -> SDoc +pprIfaceContextArr :: Outputable a => [a] -> SDoc -- Prints "(C a, D b) =>", including the arrow -pprIfaceContext [] = empty -pprIfaceContext theta = ppr_preds theta <+> darrow +pprIfaceContextArr [] = empty +pprIfaceContextArr theta = pprIfaceContext theta <+> darrow -ppr_preds :: Outputable a => [a] -> SDoc -ppr_preds [pred] = ppr pred -- No parens -ppr_preds preds = parens (sep (punctuate comma (map ppr preds))) +pprIfaceContext :: Outputable a => [a] -> SDoc +pprIfaceContext [pred] = ppr pred -- No parens +pprIfaceContext preds = parens (sep (punctuate comma (map ppr preds))) instance Binary IfaceType where put_ bh (IfaceForAllTy aa ab) = do From git at git.haskell.org Thu Mar 13 13:14:03 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 13:14:03 +0000 (UTC) Subject: [commit: ghc] wip/T8776: Pretty-print the following TyThings via their IfaceDecl counterpart: * AnId * ACoAxiom * AConLike (14d306b) Message-ID: <20140313131403.EC4462406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8776 Link : http://ghc.haskell.org/trac/ghc/changeset/14d306bbffe5f820424b0ae46c04ceb5d368b3ae/ghc >--------------------------------------------------------------- commit 14d306bbffe5f820424b0ae46c04ceb5d368b3ae Author: Dr. ERDI Gergo Date: Thu Mar 13 21:07:23 2014 +0800 Pretty-print the following TyThings via their IfaceDecl counterpart: * AnId * ACoAxiom * AConLike >--------------------------------------------------------------- 14d306bbffe5f820424b0ae46c04ceb5d368b3ae compiler/iface/IfaceSyn.lhs | 2 +- compiler/iface/MkIface.lhs | 10 +++++++- compiler/main/PprTyThing.hs | 57 +++++++++---------------------------------- 3 files changed, 21 insertions(+), 48 deletions(-) diff --git a/compiler/iface/IfaceSyn.lhs b/compiler/iface/IfaceSyn.lhs index 8ca8582..7484b37 100644 --- a/compiler/iface/IfaceSyn.lhs +++ b/compiler/iface/IfaceSyn.lhs @@ -1100,7 +1100,7 @@ pprIfaceDecl (IfaceClass {ifCtxt = context, ifName = clas, ifTyVars = tyvars, sep (map ppr sigs)]) pprIfaceDecl (IfaceAxiom {ifName = name, ifTyCon = tycon, ifAxBranches = branches }) - = hang (ptext (sLit "axiom") <+> ppr name <> colon) + = hang (ptext (sLit "axiom") <+> ppr name <> dcolon) 2 (vcat $ map (pprAxBranch $ Just tycon) branches) pprIfaceDecl (IfacePatSyn { ifName = name, ifPatHasWrapper = has_wrap, diff --git a/compiler/iface/MkIface.lhs b/compiler/iface/MkIface.lhs index 0af9af6..51df08c 100644 --- a/compiler/iface/MkIface.lhs +++ b/compiler/iface/MkIface.lhs @@ -1461,7 +1461,7 @@ tyThingToIfaceDecl (AnId id) = idToIfaceDecl id tyThingToIfaceDecl (ATyCon tycon) = tyConToIfaceDecl emptyTidyEnv tycon tyThingToIfaceDecl (ACoAxiom ax) = coAxiomToIfaceDecl ax tyThingToIfaceDecl (AConLike cl) = case cl of - RealDataCon dc -> pprPanic "toIfaceDecl" (ppr dc) -- Should be trimmed out earlier + RealDataCon dc -> dataConToIfaceDecl dc -- for ppr purposes only PatSynCon ps -> patSynToIfaceDecl ps -------------------------- @@ -1477,6 +1477,14 @@ idToIfaceDecl id ifIdInfo = toIfaceIdInfo (idInfo id) } -------------------------- +dataConToIfaceDecl :: DataCon -> IfaceDecl +dataConToIfaceDecl dataCon + = IfaceId { ifName = getOccName dataCon, + ifType = toIfaceType (dataConUserType dataCon), + ifIdDetails = IfVanillaId, + ifIdInfo = NoInfo } + +-------------------------- patSynToIfaceDecl :: PatSyn -> IfaceDecl patSynToIfaceDecl ps = IfacePatSyn { ifName = getOccName . getName $ ps diff --git a/compiler/main/PprTyThing.hs b/compiler/main/PprTyThing.hs index 27e7390..6b16bcd 100644 --- a/compiler/main/PprTyThing.hs +++ b/compiler/main/PprTyThing.hs @@ -23,20 +23,18 @@ module PprTyThing ( ) where import TypeRep ( TyThing(..) ) -import ConLike import DataCon -import PatSyn import Id import TyCon import Class -import Coercion( pprCoAxiom, pprCoAxBranch ) +import Coercion( pprCoAxBranch ) import CoAxiom( CoAxiom(..), brListMap ) import HscTypes( tyThingParent_maybe ) -import HsBinds( pprPatSynSig ) import Type( tidyTopType, tidyOpenType, splitForAllTys, funResultTy ) import Kind( synTyConResKind ) import TypeRep( pprTvBndrs, pprForAll, suppressKinds ) import TysPrim( alphaTyVars ) +import MkIface ( tyThingToIfaceDecl ) import TcType import Name import VarEnv( emptyTidyEnv ) @@ -44,7 +42,6 @@ import StaticFlags( opt_PprStyle_Debug ) import DynFlags import Outputable import FastString -import Data.Maybe -- ----------------------------------------------------------------------------- -- Pretty-printing entities that we get from the GHC API @@ -76,7 +73,7 @@ pprTyThingLoc tyThing -- | Pretty-prints a 'TyThing'. pprTyThing :: TyThing -> SDoc -pprTyThing thing = ppr_ty_thing showAll thing +pprTyThing thing = ppr_ty_thing (Just showAll) thing -- | Pretty-prints a 'TyThing' in context: that is, if the entity -- is a data constructor, record selector, or class method, then @@ -88,7 +85,7 @@ pprTyThingInContext thing where go ss thing = case tyThingParent_maybe thing of Just parent -> go (getName thing : ss) parent - Nothing -> ppr_ty_thing ss thing + Nothing -> ppr_ty_thing (Just ss) thing -- | Like 'pprTyThingInContext', but adds the defining location. pprTyThingInContextLoc :: TyThing -> SDoc @@ -100,21 +97,15 @@ pprTyThingInContextLoc tyThing -- the function is equivalent to 'pprTyThing' but for type constructors -- and classes it prints only the header part of the declaration. pprTyThingHdr :: TyThing -> SDoc -pprTyThingHdr (AnId id) = pprId id -pprTyThingHdr (AConLike conLike) = case conLike of - RealDataCon dataCon -> pprDataConSig dataCon - PatSynCon patSyn -> pprPatSyn patSyn -pprTyThingHdr (ATyCon tyCon) = pprTyConHdr tyCon -pprTyThingHdr (ACoAxiom ax) = pprCoAxiom ax +pprTyThingHdr = ppr_ty_thing Nothing ------------------------ -ppr_ty_thing :: ShowSub -> TyThing -> SDoc -ppr_ty_thing _ (AnId id) = pprId id -ppr_ty_thing _ (AConLike conLike) = case conLike of - RealDataCon dataCon -> pprDataConSig dataCon - PatSynCon patSyn -> pprPatSyn patSyn -ppr_ty_thing ss (ATyCon tyCon) = pprTyCon ss tyCon -ppr_ty_thing _ (ACoAxiom ax) = pprCoAxiom ax +ppr_ty_thing :: Maybe ShowSub -> TyThing -> SDoc +ppr_ty_thing mss tyThing = case tyThing of + ATyCon tyCon -> case mss of + Nothing -> pprTyConHdr tyCon + Just ss -> pprTyCon ss tyCon + _ -> ppr $ tyThingToIfaceDecl tyThing pprTyConHdr :: TyCon -> SDoc pprTyConHdr tyCon @@ -143,10 +134,6 @@ pprTyConHdr tyCon | isAlgTyCon tyCon = pprThetaArrowTy (tyConStupidTheta tyCon) | otherwise = empty -- Returns 'empty' if null theta -pprDataConSig :: DataCon -> SDoc -pprDataConSig dataCon - = ppr_bndr dataCon <+> dcolon <+> pprTypeForUser (dataConUserType dataCon) - pprClassHdr :: Class -> SDoc pprClassHdr cls = sdocWithDynFlags $ \dflags -> @@ -158,28 +145,6 @@ pprClassHdr cls where (tvs, funDeps) = classTvsFds cls -pprId :: Var -> SDoc -pprId ident - = hang (ppr_bndr ident <+> dcolon) - 2 (pprTypeForUser (idType ident)) - -pprPatSyn :: PatSyn -> SDoc -pprPatSyn patSyn - = pprPatSynSig ident is_bidir args (pprTypeForUser rhs_ty) prov req - where - ident = patSynId patSyn - is_bidir = isJust $ patSynWrapper patSyn - - args = fmap pprParendType (patSynTyDetails patSyn) - prov = pprThetaOpt prov_theta - req = pprThetaOpt req_theta - - pprThetaOpt [] = Nothing - pprThetaOpt theta = Just $ pprTheta theta - - (_univ_tvs, _ex_tvs, (prov_theta, req_theta)) = patSynSig patSyn - rhs_ty = patSynType patSyn - pprTypeForUser :: Type -> SDoc -- We do two things here. -- a) We tidy the type, regardless From git at git.haskell.org Thu Mar 13 13:18:51 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 13:18:51 +0000 (UTC) Subject: [commit: ghc] wip/T8776: Pretty-print the following TyThings via their IfaceDecl counterpart: * AnId * ACoAxiom * AConLike (1ea0229) Message-ID: <20140313131851.B4C232406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8776 Link : http://ghc.haskell.org/trac/ghc/changeset/1ea02299a6a46f8badf54740e3ee14b015f81546/ghc >--------------------------------------------------------------- commit 1ea02299a6a46f8badf54740e3ee14b015f81546 Author: Dr. ERDI Gergo Date: Thu Mar 13 21:18:39 2014 +0800 Pretty-print the following TyThings via their IfaceDecl counterpart: * AnId * ACoAxiom * AConLike >--------------------------------------------------------------- 1ea02299a6a46f8badf54740e3ee14b015f81546 compiler/iface/IfaceSyn.lhs | 2 +- compiler/iface/MkIface.lhs | 10 +++++++- compiler/main/PprTyThing.hs | 59 ++++++++++--------------------------------- 3 files changed, 23 insertions(+), 48 deletions(-) diff --git a/compiler/iface/IfaceSyn.lhs b/compiler/iface/IfaceSyn.lhs index 8ca8582..7484b37 100644 --- a/compiler/iface/IfaceSyn.lhs +++ b/compiler/iface/IfaceSyn.lhs @@ -1100,7 +1100,7 @@ pprIfaceDecl (IfaceClass {ifCtxt = context, ifName = clas, ifTyVars = tyvars, sep (map ppr sigs)]) pprIfaceDecl (IfaceAxiom {ifName = name, ifTyCon = tycon, ifAxBranches = branches }) - = hang (ptext (sLit "axiom") <+> ppr name <> colon) + = hang (ptext (sLit "axiom") <+> ppr name <> dcolon) 2 (vcat $ map (pprAxBranch $ Just tycon) branches) pprIfaceDecl (IfacePatSyn { ifName = name, ifPatHasWrapper = has_wrap, diff --git a/compiler/iface/MkIface.lhs b/compiler/iface/MkIface.lhs index 0af9af6..51df08c 100644 --- a/compiler/iface/MkIface.lhs +++ b/compiler/iface/MkIface.lhs @@ -1461,7 +1461,7 @@ tyThingToIfaceDecl (AnId id) = idToIfaceDecl id tyThingToIfaceDecl (ATyCon tycon) = tyConToIfaceDecl emptyTidyEnv tycon tyThingToIfaceDecl (ACoAxiom ax) = coAxiomToIfaceDecl ax tyThingToIfaceDecl (AConLike cl) = case cl of - RealDataCon dc -> pprPanic "toIfaceDecl" (ppr dc) -- Should be trimmed out earlier + RealDataCon dc -> dataConToIfaceDecl dc -- for ppr purposes only PatSynCon ps -> patSynToIfaceDecl ps -------------------------- @@ -1477,6 +1477,14 @@ idToIfaceDecl id ifIdInfo = toIfaceIdInfo (idInfo id) } -------------------------- +dataConToIfaceDecl :: DataCon -> IfaceDecl +dataConToIfaceDecl dataCon + = IfaceId { ifName = getOccName dataCon, + ifType = toIfaceType (dataConUserType dataCon), + ifIdDetails = IfVanillaId, + ifIdInfo = NoInfo } + +-------------------------- patSynToIfaceDecl :: PatSyn -> IfaceDecl patSynToIfaceDecl ps = IfacePatSyn { ifName = getOccName . getName $ ps diff --git a/compiler/main/PprTyThing.hs b/compiler/main/PprTyThing.hs index 27e7390..fb92b5a 100644 --- a/compiler/main/PprTyThing.hs +++ b/compiler/main/PprTyThing.hs @@ -23,20 +23,18 @@ module PprTyThing ( ) where import TypeRep ( TyThing(..) ) -import ConLike import DataCon -import PatSyn import Id import TyCon import Class -import Coercion( pprCoAxiom, pprCoAxBranch ) +import Coercion( pprCoAxBranch ) import CoAxiom( CoAxiom(..), brListMap ) import HscTypes( tyThingParent_maybe ) -import HsBinds( pprPatSynSig ) import Type( tidyTopType, tidyOpenType, splitForAllTys, funResultTy ) import Kind( synTyConResKind ) import TypeRep( pprTvBndrs, pprForAll, suppressKinds ) import TysPrim( alphaTyVars ) +import MkIface ( tyThingToIfaceDecl ) import TcType import Name import VarEnv( emptyTidyEnv ) @@ -44,7 +42,6 @@ import StaticFlags( opt_PprStyle_Debug ) import DynFlags import Outputable import FastString -import Data.Maybe -- ----------------------------------------------------------------------------- -- Pretty-printing entities that we get from the GHC API @@ -76,7 +73,7 @@ pprTyThingLoc tyThing -- | Pretty-prints a 'TyThing'. pprTyThing :: TyThing -> SDoc -pprTyThing thing = ppr_ty_thing showAll thing +pprTyThing thing = ppr_ty_thing (Just showAll) thing -- | Pretty-prints a 'TyThing' in context: that is, if the entity -- is a data constructor, record selector, or class method, then @@ -88,7 +85,7 @@ pprTyThingInContext thing where go ss thing = case tyThingParent_maybe thing of Just parent -> go (getName thing : ss) parent - Nothing -> ppr_ty_thing ss thing + Nothing -> ppr_ty_thing (Just ss) thing -- | Like 'pprTyThingInContext', but adds the defining location. pprTyThingInContextLoc :: TyThing -> SDoc @@ -100,21 +97,17 @@ pprTyThingInContextLoc tyThing -- the function is equivalent to 'pprTyThing' but for type constructors -- and classes it prints only the header part of the declaration. pprTyThingHdr :: TyThing -> SDoc -pprTyThingHdr (AnId id) = pprId id -pprTyThingHdr (AConLike conLike) = case conLike of - RealDataCon dataCon -> pprDataConSig dataCon - PatSynCon patSyn -> pprPatSyn patSyn -pprTyThingHdr (ATyCon tyCon) = pprTyConHdr tyCon -pprTyThingHdr (ACoAxiom ax) = pprCoAxiom ax +pprTyThingHdr = ppr_ty_thing Nothing ------------------------ -ppr_ty_thing :: ShowSub -> TyThing -> SDoc -ppr_ty_thing _ (AnId id) = pprId id -ppr_ty_thing _ (AConLike conLike) = case conLike of - RealDataCon dataCon -> pprDataConSig dataCon - PatSynCon patSyn -> pprPatSyn patSyn -ppr_ty_thing ss (ATyCon tyCon) = pprTyCon ss tyCon -ppr_ty_thing _ (ACoAxiom ax) = pprCoAxiom ax +-- NOTE: We pretty-print 'TyThing' via 'IfaceDecl' so that we can reuse the +-- 'TyCon' tidying happening in 'tyThingToIfaceDecl'. See #8776 for details. +ppr_ty_thing :: Maybe ShowSub -> TyThing -> SDoc +ppr_ty_thing mss tyThing = case tyThing of + ATyCon tyCon -> case mss of + Nothing -> pprTyConHdr tyCon + Just ss -> pprTyCon ss tyCon + _ -> ppr $ tyThingToIfaceDecl tyThing pprTyConHdr :: TyCon -> SDoc pprTyConHdr tyCon @@ -143,10 +136,6 @@ pprTyConHdr tyCon | isAlgTyCon tyCon = pprThetaArrowTy (tyConStupidTheta tyCon) | otherwise = empty -- Returns 'empty' if null theta -pprDataConSig :: DataCon -> SDoc -pprDataConSig dataCon - = ppr_bndr dataCon <+> dcolon <+> pprTypeForUser (dataConUserType dataCon) - pprClassHdr :: Class -> SDoc pprClassHdr cls = sdocWithDynFlags $ \dflags -> @@ -158,28 +147,6 @@ pprClassHdr cls where (tvs, funDeps) = classTvsFds cls -pprId :: Var -> SDoc -pprId ident - = hang (ppr_bndr ident <+> dcolon) - 2 (pprTypeForUser (idType ident)) - -pprPatSyn :: PatSyn -> SDoc -pprPatSyn patSyn - = pprPatSynSig ident is_bidir args (pprTypeForUser rhs_ty) prov req - where - ident = patSynId patSyn - is_bidir = isJust $ patSynWrapper patSyn - - args = fmap pprParendType (patSynTyDetails patSyn) - prov = pprThetaOpt prov_theta - req = pprThetaOpt req_theta - - pprThetaOpt [] = Nothing - pprThetaOpt theta = Just $ pprTheta theta - - (_univ_tvs, _ex_tvs, (prov_theta, req_theta)) = patSynSig patSyn - rhs_ty = patSynType patSyn - pprTypeForUser :: Type -> SDoc -- We do two things here. -- a) We tidy the type, regardless From git at git.haskell.org Thu Mar 13 13:21:36 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 13:21:36 +0000 (UTC) Subject: [commit: ghc] master: pprIfaceDecl for IfacePatSyn: use pprPatSynSig (24eea38) Message-ID: <20140313132136.BA5F92406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/24eea38c70eae90d166de26d71a178fb0c1ffc30/ghc >--------------------------------------------------------------- commit 24eea38c70eae90d166de26d71a178fb0c1ffc30 Author: Dr. ERDI Gergo Date: Wed Mar 12 20:38:54 2014 +0800 pprIfaceDecl for IfacePatSyn: use pprPatSynSig >--------------------------------------------------------------- 24eea38c70eae90d166de26d71a178fb0c1ffc30 compiler/iface/IfaceSyn.lhs | 26 +++++++++++--------------- 1 file changed, 11 insertions(+), 15 deletions(-) diff --git a/compiler/iface/IfaceSyn.lhs b/compiler/iface/IfaceSyn.lhs index 3691fca..8ca8582 100644 --- a/compiler/iface/IfaceSyn.lhs +++ b/compiler/iface/IfaceSyn.lhs @@ -55,6 +55,7 @@ import TysWiredIn ( eqTyConName ) import Fingerprint import Binary import BooleanFormula ( BooleanFormula ) +import HsBinds import Control.Monad import System.IO.Unsafe @@ -1104,27 +1105,22 @@ pprIfaceDecl (IfaceAxiom {ifName = name, ifTyCon = tycon, ifAxBranches = branche pprIfaceDecl (IfacePatSyn { ifName = name, ifPatHasWrapper = has_wrap, ifPatIsInfix = is_infix, - ifPatUnivTvs = univ_tvs, ifPatExTvs = ex_tvs, + ifPatUnivTvs = _univ_tvs, ifPatExTvs = _ex_tvs, ifPatProvCtxt = prov_ctxt, ifPatReqCtxt = req_ctxt, ifPatArgs = args, ifPatTy = ty }) - = hang (text "pattern" <+> header) - 4 details + = pprPatSynSig name has_wrap args' ty' (pprCtxt prov_ctxt) (pprCtxt req_ctxt) where - header = ppr name <+> dcolon <+> - (pprIfaceForAllPart univ_tvs req_ctxt $ - pprIfaceForAllPart ex_tvs prov_ctxt $ - pp_tau) + args' = case (is_infix, map snd args) of + (True, [left_ty, right_ty]) -> + InfixPatSyn (pprParendIfaceType left_ty) (pprParendIfaceType right_ty) + (_, tys) -> + PrefixPatSyn (map pprParendIfaceType tys) - details = sep [ if is_infix then text "Infix" else empty - , if has_wrap then text "HasWrapper" else empty - ] + ty' = pprParendIfaceType ty - pp_tau = case map pprParendIfaceType (arg_tys ++ [ty]) of - (t:ts) -> fsep (t : map (arrow <+>) ts) - [] -> panic "pp_tau" - - arg_tys = map snd args + pprCtxt [] = Nothing + pprCtxt ctxt = Just $ pprIfaceContext ctxt pprCType :: Maybe CType -> SDoc pprCType Nothing = ptext (sLit "No C type associated") From git at git.haskell.org Thu Mar 13 13:21:39 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 13:21:39 +0000 (UTC) Subject: [commit: ghc] master: pprIfaceContextArr: print a context including the "=>" arrow (23c0f1e) Message-ID: <20140313132141.9ED9D2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/23c0f1ec2cf06c0178c2ae7414fe57ea648689e7/ghc >--------------------------------------------------------------- commit 23c0f1ec2cf06c0178c2ae7414fe57ea648689e7 Author: Dr. ERDI Gergo Date: Wed Mar 12 20:38:26 2014 +0800 pprIfaceContextArr: print a context including the "=>" arrow >--------------------------------------------------------------- 23c0f1ec2cf06c0178c2ae7414fe57ea648689e7 compiler/iface/IfaceSyn.lhs | 2 +- compiler/iface/IfaceType.lhs | 16 ++++++++-------- 2 files changed, 9 insertions(+), 9 deletions(-) diff --git a/compiler/iface/IfaceSyn.lhs b/compiler/iface/IfaceSyn.lhs index b582305..3691fca 100644 --- a/compiler/iface/IfaceSyn.lhs +++ b/compiler/iface/IfaceSyn.lhs @@ -1152,7 +1152,7 @@ instance Outputable IfaceAT where pprIfaceDeclHead :: IfaceContext -> OccName -> [IfaceTvBndr] -> SDoc pprIfaceDeclHead context thing tyvars - = hsep [pprIfaceContext context, parenSymOcc thing (ppr thing), + = hsep [pprIfaceContextArr context, parenSymOcc thing (ppr thing), pprIfaceTvBndrs tyvars] pp_condecls :: OccName -> IfaceConDecls -> SDoc diff --git a/compiler/iface/IfaceType.lhs b/compiler/iface/IfaceType.lhs index 822e3da..8c1791a 100644 --- a/compiler/iface/IfaceType.lhs +++ b/compiler/iface/IfaceType.lhs @@ -22,7 +22,7 @@ module IfaceType ( toIfaceCoercion, -- Printing - pprIfaceType, pprParendIfaceType, pprIfaceContext, + pprIfaceType, pprParendIfaceType, pprIfaceContext, pprIfaceContextArr, pprIfaceIdBndr, pprIfaceTvBndr, pprIfaceTvBndrs, pprIfaceBndrs, tOP_PREC, tYCON_PREC, noParens, maybeParen, pprIfaceForAllPart, @@ -253,7 +253,7 @@ ppr_ty ctxt_prec ty@(IfaceForAllTy _ _) -- generality pprIfaceForAllPart :: Outputable a => [IfaceTvBndr] -> [a] -> SDoc -> SDoc pprIfaceForAllPart tvs ctxt doc - = sep [ppr_tvs, pprIfaceContext ctxt, doc] + = sep [ppr_tvs, pprIfaceContextArr ctxt, doc] where ppr_tvs | null tvs = empty | otherwise = ptext (sLit "forall") <+> pprIfaceTvBndrs tvs <> dot @@ -386,14 +386,14 @@ instance Binary IfaceTyLit where _ -> panic ("get IfaceTyLit " ++ show tag) ------------------- -pprIfaceContext :: Outputable a => [a] -> SDoc +pprIfaceContextArr :: Outputable a => [a] -> SDoc -- Prints "(C a, D b) =>", including the arrow -pprIfaceContext [] = empty -pprIfaceContext theta = ppr_preds theta <+> darrow +pprIfaceContextArr [] = empty +pprIfaceContextArr theta = pprIfaceContext theta <+> darrow -ppr_preds :: Outputable a => [a] -> SDoc -ppr_preds [pred] = ppr pred -- No parens -ppr_preds preds = parens (sep (punctuate comma (map ppr preds))) +pprIfaceContext :: Outputable a => [a] -> SDoc +pprIfaceContext [pred] = ppr pred -- No parens +pprIfaceContext preds = parens (sep (punctuate comma (map ppr preds))) instance Binary IfaceType where put_ bh (IfaceForAllTy aa ab) = do From git at git.haskell.org Thu Mar 13 13:21:42 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 13:21:42 +0000 (UTC) Subject: [commit: ghc] master: Add OutputableBndr instance for OccName (4d1b7b4) Message-ID: <20140313132142.5AC362406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4d1b7b4a9b986e87755784478b4ea4883a5e203e/ghc >--------------------------------------------------------------- commit 4d1b7b4a9b986e87755784478b4ea4883a5e203e Author: Dr. ERDI Gergo Date: Wed Mar 12 20:37:22 2014 +0800 Add OutputableBndr instance for OccName >--------------------------------------------------------------- 4d1b7b4a9b986e87755784478b4ea4883a5e203e compiler/basicTypes/OccName.lhs | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/compiler/basicTypes/OccName.lhs b/compiler/basicTypes/OccName.lhs index e993767..2d17b95 100644 --- a/compiler/basicTypes/OccName.lhs +++ b/compiler/basicTypes/OccName.lhs @@ -261,6 +261,11 @@ instance Data OccName where instance Outputable OccName where ppr = pprOccName +instance OutputableBndr OccName where + pprBndr _ = ppr + pprInfixOcc n = pprInfixVar (isSymOcc n) (ppr n) + pprPrefixOcc n = pprPrefixVar (isSymOcc n) (ppr n) + pprOccName :: OccName -> SDoc pprOccName (OccName sp occ) = getPprStyle $ \ sty -> From git at git.haskell.org Thu Mar 13 13:21:45 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 13:21:45 +0000 (UTC) Subject: [commit: ghc] master: Pretty-print the following TyThings via their IfaceDecl counterpart: * AnId * ACoAxiom * AConLike (065c35a) Message-ID: <20140313132145.1D9472406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/065c35a9d6d48060c8fac8d755833349ce58b35b/ghc >--------------------------------------------------------------- commit 065c35a9d6d48060c8fac8d755833349ce58b35b Author: Dr. ERDI Gergo Date: Thu Mar 13 21:18:39 2014 +0800 Pretty-print the following TyThings via their IfaceDecl counterpart: * AnId * ACoAxiom * AConLike >--------------------------------------------------------------- 065c35a9d6d48060c8fac8d755833349ce58b35b compiler/iface/IfaceSyn.lhs | 2 +- compiler/iface/MkIface.lhs | 10 +++++++- compiler/main/PprTyThing.hs | 59 ++++++++++--------------------------------- 3 files changed, 23 insertions(+), 48 deletions(-) diff --git a/compiler/iface/IfaceSyn.lhs b/compiler/iface/IfaceSyn.lhs index 8ca8582..7484b37 100644 --- a/compiler/iface/IfaceSyn.lhs +++ b/compiler/iface/IfaceSyn.lhs @@ -1100,7 +1100,7 @@ pprIfaceDecl (IfaceClass {ifCtxt = context, ifName = clas, ifTyVars = tyvars, sep (map ppr sigs)]) pprIfaceDecl (IfaceAxiom {ifName = name, ifTyCon = tycon, ifAxBranches = branches }) - = hang (ptext (sLit "axiom") <+> ppr name <> colon) + = hang (ptext (sLit "axiom") <+> ppr name <> dcolon) 2 (vcat $ map (pprAxBranch $ Just tycon) branches) pprIfaceDecl (IfacePatSyn { ifName = name, ifPatHasWrapper = has_wrap, diff --git a/compiler/iface/MkIface.lhs b/compiler/iface/MkIface.lhs index 0af9af6..51df08c 100644 --- a/compiler/iface/MkIface.lhs +++ b/compiler/iface/MkIface.lhs @@ -1461,7 +1461,7 @@ tyThingToIfaceDecl (AnId id) = idToIfaceDecl id tyThingToIfaceDecl (ATyCon tycon) = tyConToIfaceDecl emptyTidyEnv tycon tyThingToIfaceDecl (ACoAxiom ax) = coAxiomToIfaceDecl ax tyThingToIfaceDecl (AConLike cl) = case cl of - RealDataCon dc -> pprPanic "toIfaceDecl" (ppr dc) -- Should be trimmed out earlier + RealDataCon dc -> dataConToIfaceDecl dc -- for ppr purposes only PatSynCon ps -> patSynToIfaceDecl ps -------------------------- @@ -1477,6 +1477,14 @@ idToIfaceDecl id ifIdInfo = toIfaceIdInfo (idInfo id) } -------------------------- +dataConToIfaceDecl :: DataCon -> IfaceDecl +dataConToIfaceDecl dataCon + = IfaceId { ifName = getOccName dataCon, + ifType = toIfaceType (dataConUserType dataCon), + ifIdDetails = IfVanillaId, + ifIdInfo = NoInfo } + +-------------------------- patSynToIfaceDecl :: PatSyn -> IfaceDecl patSynToIfaceDecl ps = IfacePatSyn { ifName = getOccName . getName $ ps diff --git a/compiler/main/PprTyThing.hs b/compiler/main/PprTyThing.hs index 27e7390..fb92b5a 100644 --- a/compiler/main/PprTyThing.hs +++ b/compiler/main/PprTyThing.hs @@ -23,20 +23,18 @@ module PprTyThing ( ) where import TypeRep ( TyThing(..) ) -import ConLike import DataCon -import PatSyn import Id import TyCon import Class -import Coercion( pprCoAxiom, pprCoAxBranch ) +import Coercion( pprCoAxBranch ) import CoAxiom( CoAxiom(..), brListMap ) import HscTypes( tyThingParent_maybe ) -import HsBinds( pprPatSynSig ) import Type( tidyTopType, tidyOpenType, splitForAllTys, funResultTy ) import Kind( synTyConResKind ) import TypeRep( pprTvBndrs, pprForAll, suppressKinds ) import TysPrim( alphaTyVars ) +import MkIface ( tyThingToIfaceDecl ) import TcType import Name import VarEnv( emptyTidyEnv ) @@ -44,7 +42,6 @@ import StaticFlags( opt_PprStyle_Debug ) import DynFlags import Outputable import FastString -import Data.Maybe -- ----------------------------------------------------------------------------- -- Pretty-printing entities that we get from the GHC API @@ -76,7 +73,7 @@ pprTyThingLoc tyThing -- | Pretty-prints a 'TyThing'. pprTyThing :: TyThing -> SDoc -pprTyThing thing = ppr_ty_thing showAll thing +pprTyThing thing = ppr_ty_thing (Just showAll) thing -- | Pretty-prints a 'TyThing' in context: that is, if the entity -- is a data constructor, record selector, or class method, then @@ -88,7 +85,7 @@ pprTyThingInContext thing where go ss thing = case tyThingParent_maybe thing of Just parent -> go (getName thing : ss) parent - Nothing -> ppr_ty_thing ss thing + Nothing -> ppr_ty_thing (Just ss) thing -- | Like 'pprTyThingInContext', but adds the defining location. pprTyThingInContextLoc :: TyThing -> SDoc @@ -100,21 +97,17 @@ pprTyThingInContextLoc tyThing -- the function is equivalent to 'pprTyThing' but for type constructors -- and classes it prints only the header part of the declaration. pprTyThingHdr :: TyThing -> SDoc -pprTyThingHdr (AnId id) = pprId id -pprTyThingHdr (AConLike conLike) = case conLike of - RealDataCon dataCon -> pprDataConSig dataCon - PatSynCon patSyn -> pprPatSyn patSyn -pprTyThingHdr (ATyCon tyCon) = pprTyConHdr tyCon -pprTyThingHdr (ACoAxiom ax) = pprCoAxiom ax +pprTyThingHdr = ppr_ty_thing Nothing ------------------------ -ppr_ty_thing :: ShowSub -> TyThing -> SDoc -ppr_ty_thing _ (AnId id) = pprId id -ppr_ty_thing _ (AConLike conLike) = case conLike of - RealDataCon dataCon -> pprDataConSig dataCon - PatSynCon patSyn -> pprPatSyn patSyn -ppr_ty_thing ss (ATyCon tyCon) = pprTyCon ss tyCon -ppr_ty_thing _ (ACoAxiom ax) = pprCoAxiom ax +-- NOTE: We pretty-print 'TyThing' via 'IfaceDecl' so that we can reuse the +-- 'TyCon' tidying happening in 'tyThingToIfaceDecl'. See #8776 for details. +ppr_ty_thing :: Maybe ShowSub -> TyThing -> SDoc +ppr_ty_thing mss tyThing = case tyThing of + ATyCon tyCon -> case mss of + Nothing -> pprTyConHdr tyCon + Just ss -> pprTyCon ss tyCon + _ -> ppr $ tyThingToIfaceDecl tyThing pprTyConHdr :: TyCon -> SDoc pprTyConHdr tyCon @@ -143,10 +136,6 @@ pprTyConHdr tyCon | isAlgTyCon tyCon = pprThetaArrowTy (tyConStupidTheta tyCon) | otherwise = empty -- Returns 'empty' if null theta -pprDataConSig :: DataCon -> SDoc -pprDataConSig dataCon - = ppr_bndr dataCon <+> dcolon <+> pprTypeForUser (dataConUserType dataCon) - pprClassHdr :: Class -> SDoc pprClassHdr cls = sdocWithDynFlags $ \dflags -> @@ -158,28 +147,6 @@ pprClassHdr cls where (tvs, funDeps) = classTvsFds cls -pprId :: Var -> SDoc -pprId ident - = hang (ppr_bndr ident <+> dcolon) - 2 (pprTypeForUser (idType ident)) - -pprPatSyn :: PatSyn -> SDoc -pprPatSyn patSyn - = pprPatSynSig ident is_bidir args (pprTypeForUser rhs_ty) prov req - where - ident = patSynId patSyn - is_bidir = isJust $ patSynWrapper patSyn - - args = fmap pprParendType (patSynTyDetails patSyn) - prov = pprThetaOpt prov_theta - req = pprThetaOpt req_theta - - pprThetaOpt [] = Nothing - pprThetaOpt theta = Just $ pprTheta theta - - (_univ_tvs, _ex_tvs, (prov_theta, req_theta)) = patSynSig patSyn - rhs_ty = patSynType patSyn - pprTypeForUser :: Type -> SDoc -- We do two things here. -- a) We tidy the type, regardless From git at git.haskell.org Thu Mar 13 17:18:39 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 17:18:39 +0000 (UTC) Subject: [commit: ghc] master: Improve copy/clone array primop docs (ed2a8f0) Message-ID: <20140313171839.A05302406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ed2a8f07a7b77f72682fc57b54908f30eb4b7c33/ghc >--------------------------------------------------------------- commit ed2a8f07a7b77f72682fc57b54908f30eb4b7c33 Author: Johan Tibell Date: Thu Mar 13 18:10:41 2014 +0100 Improve copy/clone array primop docs Clarify the order of the arguments. Also, remove any use of # in the comments, which would make the rest of that comment line disappear in the docs, due to being treated as a comment by the preprocessor. >--------------------------------------------------------------- ed2a8f07a7b77f72682fc57b54908f30eb4b7c33 compiler/prelude/primops.txt.pp | 42 +++++++++++++++++++++++++++------------ 1 file changed, 29 insertions(+), 13 deletions(-) diff --git a/compiler/prelude/primops.txt.pp b/compiler/prelude/primops.txt.pp index d2978dc..63aef0f 100644 --- a/compiler/prelude/primops.txt.pp +++ b/compiler/prelude/primops.txt.pp @@ -762,9 +762,13 @@ primop UnsafeThawArrayOp "unsafeThawArray#" GenPrimOp primop CopyArrayOp "copyArray#" GenPrimOp Array# a -> Int# -> MutableArray# s a -> Int# -> Int# -> State# s -> State# s - {Copy a range of the Array# to the specified region in the MutableArray#. - Both arrays must fully contain the specified ranges, but this is not checked. - The two arrays must not be the same array in different states, but this is not checked either.} + {Given a source array, an offset into the source array, a + destination array, an offset into the destination array, and a + number of elements to copy, copy the elements from the source array + to the destination array. Both arrays must fully contain the + specified ranges, but this is not checked. The two arrays must not + be the same array in different states, but this is not checked + either.} with has_side_effects = True can_fail = True @@ -772,8 +776,12 @@ primop CopyArrayOp "copyArray#" GenPrimOp primop CopyMutableArrayOp "copyMutableArray#" GenPrimOp MutableArray# s a -> Int# -> MutableArray# s a -> Int# -> Int# -> State# s -> State# s - {Copy a range of the first MutableArray# to the specified region in the second MutableArray#. - Both arrays must fully contain the specified ranges, but this is not checked.} + {Given a source array, an offset into the source array, a + destination array, an offset into the destination array, and a + number of elements to copy, copy the elements from the source array + to the destination array. The source and destination arrays can + refer to the same array. Both arrays must fully contain the + specified ranges, but this is not checked.} with has_side_effects = True can_fail = True @@ -781,32 +789,40 @@ primop CopyMutableArrayOp "copyMutableArray#" GenPrimOp primop CloneArrayOp "cloneArray#" GenPrimOp Array# a -> Int# -> Int# -> Array# a - {Return a newly allocated Array# with the specified subrange of the provided Array#. - The provided Array# should contain the full subrange specified by the two Int#s, but this is not checked.} + {Given a source array, an offset into the source array, and a number + of elements to copy, create a new array with the elements from the + source array. The provided array must fully contain the specified + range, but this is not checked.} with has_side_effects = True code_size = { primOpCodeSizeForeignCall + 4 } primop CloneMutableArrayOp "cloneMutableArray#" GenPrimOp MutableArray# s a -> Int# -> Int# -> State# s -> (# State# s, MutableArray# s a #) - {Return a newly allocated Array# with the specified subrange of the provided Array#. - The provided MutableArray# should contain the full subrange specified by the two Int#s, but this is not checked.} + {Given a source array, an offset into the source array, and a number + of elements to copy, create a new array with the elements from the + source array. The provided array must fully contain the specified + range, but this is not checked.} with has_side_effects = True code_size = { primOpCodeSizeForeignCall + 4 } primop FreezeArrayOp "freezeArray#" GenPrimOp MutableArray# s a -> Int# -> Int# -> State# s -> (# State# s, Array# a #) - {Return a newly allocated Array# with the specified subrange of the provided MutableArray#. - The provided MutableArray# should contain the full subrange specified by the two Int#s, but this is not checked.} + {Given a source array, an offset into the source array, and a number + of elements to copy, create a new array with the elements from the + source array. The provided array must fully contain the specified + range, but this is not checked.} with has_side_effects = True code_size = { primOpCodeSizeForeignCall + 4 } primop ThawArrayOp "thawArray#" GenPrimOp Array# a -> Int# -> Int# -> State# s -> (# State# s, MutableArray# s a #) - {Return a newly allocated Array# with the specified subrange of the provided MutableArray#. - The provided Array# should contain the full subrange specified by the two Int#s, but this is not checked.} + {Given a source array, an offset into the source array, and a number + of elements to copy, create a new array with the elements from the + source array. The provided array must fully contain the specified + range, but this is not checked.} with has_side_effects = True code_size = { primOpCodeSizeForeignCall + 4 } From git at git.haskell.org Thu Mar 13 19:58:40 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 19:58:40 +0000 (UTC) Subject: [commit: haddock] v2.14: Add UnicodeSyntax alternatives for * and -> (1fda06f) Message-ID: <20140313195841.00D3A2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : v2.14 Link : http://git.haskell.org/haddock.git/commitdiff/1fda06fd41239acef228e83a55871c71e1a4856c >--------------------------------------------------------------- commit 1fda06fd41239acef228e83a55871c71e1a4856c Author: Niklas Haas Date: Thu Mar 13 07:01:27 2014 +0100 Add UnicodeSyntax alternatives for * and -> I could not find a cleaner way to do this other than checking for string equality with the given built-in types. But seeing as it's actually equivalent to string rewriting in GHC's implementation of UnicodeSyntax, it's probably fitting. >--------------------------------------------------------------- 1fda06fd41239acef228e83a55871c71e1a4856c src/Haddock/Backends/Xhtml/Decl.hs | 9 +++++++-- 1 file changed, 7 insertions(+), 2 deletions(-) diff --git a/src/Haddock/Backends/Xhtml/Decl.hs b/src/Haddock/Backends/Xhtml/Decl.hs index c1b9032..cd504d8 100644 --- a/src/Haddock/Backends/Xhtml/Decl.hs +++ b/src/Haddock/Backends/Xhtml/Decl.hs @@ -769,10 +769,10 @@ ppCtxType unicode qual ty = ppr_mono_ty pREC_CTX ty unicode qual ppParendType unicode qual ty = ppr_mono_ty pREC_CON ty unicode qual ppFunLhType unicode qual ty = ppr_mono_ty pREC_FUN ty unicode qual -ppLKind :: Unicode -> Qualification-> LHsKind DocName -> Html +ppLKind :: Unicode -> Qualification -> LHsKind DocName -> Html ppLKind unicode qual y = ppKind unicode qual (unLoc y) -ppKind :: Unicode -> Qualification-> HsKind DocName -> Html +ppKind :: Unicode -> Qualification -> HsKind DocName -> Html ppKind unicode qual ki = ppr_mono_ty pREC_TOP ki unicode qual -- Drop top-level for-all type variables in user style @@ -798,6 +798,11 @@ ppr_mono_ty ctxt_prec (HsForAllTy expl tvs ctxt ty) unicode qual = maybeParen ctxt_prec pREC_FUN $ hsep [ppForAll expl tvs ctxt unicode qual, ppr_mono_lty pREC_TOP ty unicode qual] +-- UnicodeSyntax alternatives +ppr_mono_ty _ (HsTyVar name) True _ + | getOccString (getName name) == "*" = toHtml "?" + | getOccString (getName name) == "(->)" = toHtml "(?)" + ppr_mono_ty _ (HsBangTy b ty) u q = ppBang b +++ ppLParendType u q ty ppr_mono_ty _ (HsTyVar name) _ q = ppDocName q Prefix True name ppr_mono_ty ctxt_prec (HsFunTy ty1 ty2) u q = ppr_fun_ty ctxt_prec ty1 ty2 u q From git at git.haskell.org Thu Mar 13 19:58:42 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 19:58:42 +0000 (UTC) Subject: [commit: haddock] v2.14: Hide RHS of TFs with non-exported right hand sides (0a09910) Message-ID: <20140313195843.001672406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : v2.14 Link : http://git.haskell.org/haddock.git/commitdiff/0a09910ee19c694af6142bdf5bb782e7659f6615 >--------------------------------------------------------------- commit 0a09910ee19c694af6142bdf5bb782e7659f6615 Author: Niklas Haas Date: Wed Mar 12 10:31:31 2014 +0100 Hide RHS of TFs with non-exported right hand sides Not sure what to do about data families yet, since technically it would not make a lot of sense to display constructors that cannot be used by the user. >--------------------------------------------------------------- 0a09910ee19c694af6142bdf5bb782e7659f6615 html-test/ref/TypeFamilies2.html | 92 ++++++++++++++++++++++-------- html-test/src/TypeFamilies2.hs | 32 ++++++++--- src/Haddock/Backends/LaTeX.hs | 3 +- src/Haddock/Backends/Xhtml/Decl.hs | 2 +- src/Haddock/Convert.hs | 7 ++- src/Haddock/Interface/AttachInstances.hs | 5 +- src/Haddock/Interface/Rename.hs | 2 +- src/Haddock/Types.hs | 6 +- 8 files changed, 105 insertions(+), 44 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 0a09910ee19c694af6142bdf5bb782e7659f6615 From git at git.haskell.org Thu Mar 13 19:58:45 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 19:58:45 +0000 (UTC) Subject: [commit: haddock] v2.14: Display minimal complete definitions for type classes (1c8c2f2) Message-ID: <20140313195845.31F712406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : v2.14 Link : http://git.haskell.org/haddock.git/commitdiff/1c8c2f249d4e9ef6eed93721876f9e7a65b09a77 >--------------------------------------------------------------- commit 1c8c2f249d4e9ef6eed93721876f9e7a65b09a77 Author: Niklas Haas Date: Thu Mar 13 08:53:41 2014 +0100 Display minimal complete definitions for type classes This corresponds to the new {-# MINIMAL #-} pragma present in GHC 7.8+. I also cleaned up some of the places in which ExportDecl is used to make adding fields easier in the future. Lots of test cases have been updated since they now render with minimality information. >--------------------------------------------------------------- 1c8c2f249d4e9ef6eed93721876f9e7a65b09a77 html-test/ref/DeprecatedClass.html | 16 ++ html-test/ref/Hash.html | 8 + html-test/ref/Minimal.html | 273 ++++++++++++++++++++++++++++++++++ html-test/ref/Test.html | 14 ++ html-test/ref/Ticket61.html | 8 + html-test/src/Test.hs | 1 + src/Haddock/Backends/Hoogle.hs | 6 +- src/Haddock/Backends/LaTeX.hs | 6 +- src/Haddock/Backends/Xhtml.hs | 6 +- src/Haddock/Backends/Xhtml/Decl.hs | 28 +++- src/Haddock/Backends/Xhtml/Layout.hs | 4 + src/Haddock/Convert.hs | 5 +- src/Haddock/GhcUtils.hs | 11 +- src/Haddock/Interface/Create.hs | 41 +++-- src/Haddock/Interface/Rename.hs | 1 + 15 files changed, 398 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 1c8c2f249d4e9ef6eed93721876f9e7a65b09a77 From git at git.haskell.org Thu Mar 13 19:58:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 19:58:47 +0000 (UTC) Subject: [commit: haddock] v2.14: Strip links from recently added html tests (c67d38a) Message-ID: <20140313195847.C26132406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : v2.14 Link : http://git.haskell.org/haddock.git/commitdiff/c67d38a261dd0ba6217d35cf32c4c9f42e58e26d >--------------------------------------------------------------- commit c67d38a261dd0ba6217d35cf32c4c9f42e58e26d Author: Niklas Haas Date: Thu Mar 13 13:52:40 2014 +0100 Strip links from recently added html tests These were accidentally left there when the tests were originally added >--------------------------------------------------------------- c67d38a261dd0ba6217d35cf32c4c9f42e58e26d html-test/ref/ImplicitParams.html | 20 ++-- html-test/ref/Operators.html | 72 ++++++------ html-test/ref/PatternSyns.html | 58 +++++----- html-test/ref/TypeFamilies.html | 230 ++++++++++++++++++------------------- html-test/ref/TypeFamilies2.html | 38 +++--- html-test/ref/TypeOperators.html | 16 +-- 6 files changed, 217 insertions(+), 217 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c67d38a261dd0ba6217d35cf32c4c9f42e58e26d From git at git.haskell.org Thu Mar 13 19:58:49 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 19:58:49 +0000 (UTC) Subject: [commit: haddock] v2.14: Bump version to 2.14.1 and update changelog (de306e6) Message-ID: <20140313195849.516852406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : v2.14 Link : http://git.haskell.org/haddock.git/commitdiff/de306e6c79d391f67dfae9da23b73d619c4de51c >--------------------------------------------------------------- commit de306e6c79d391f67dfae9da23b73d619c4de51c Author: Niklas Haas Date: Thu Mar 13 14:11:25 2014 +0100 Bump version to 2.14.1 and update changelog >--------------------------------------------------------------- de306e6c79d391f67dfae9da23b73d619c4de51c CHANGES | 8 ++++++++ doc/haddock.xml | 2 +- haddock.cabal | 2 +- haddock.spec | 2 +- html-test/ref/A.html | 2 +- html-test/ref/AdvanceTypes.html | 2 +- html-test/ref/B.html | 2 +- html-test/ref/Bold.html | 2 +- html-test/ref/Bug1.html | 2 +- html-test/ref/Bug195.html | 2 +- html-test/ref/Bug2.html | 2 +- html-test/ref/Bug3.html | 2 +- html-test/ref/Bug4.html | 2 +- html-test/ref/Bug6.html | 2 +- html-test/ref/Bug7.html | 2 +- html-test/ref/Bug8.html | 2 +- html-test/ref/BugDeprecated.html | 2 +- html-test/ref/BugExportHeadings.html | 2 +- html-test/ref/Bugs.html | 2 +- html-test/ref/DeprecatedClass.html | 2 +- html-test/ref/DeprecatedData.html | 2 +- html-test/ref/DeprecatedFunction.html | 2 +- html-test/ref/DeprecatedFunction2.html | 2 +- html-test/ref/DeprecatedFunction3.html | 2 +- html-test/ref/DeprecatedModule.html | 2 +- html-test/ref/DeprecatedModule2.html | 2 +- html-test/ref/DeprecatedNewtype.html | 2 +- html-test/ref/DeprecatedReExport.html | 2 +- html-test/ref/DeprecatedRecord.html | 2 +- html-test/ref/DeprecatedTypeFamily.html | 2 +- html-test/ref/DeprecatedTypeSynonym.html | 2 +- html-test/ref/Examples.html | 2 +- html-test/ref/Extensions.html | 2 +- html-test/ref/FunArgs.html | 2 +- html-test/ref/GADTRecords.html | 2 +- html-test/ref/Hash.html | 2 +- html-test/ref/HiddenInstances.html | 2 +- html-test/ref/HiddenInstancesB.html | 2 +- html-test/ref/Hyperlinks.html | 2 +- html-test/ref/IgnoreExports.html | 2 +- html-test/ref/ImplicitParams.html | 2 +- html-test/ref/Minimal.html | 2 +- html-test/ref/ModuleWithWarning.html | 2 +- html-test/ref/NamedDoc.html | 2 +- html-test/ref/Nesting.html | 2 +- html-test/ref/NoLayout.html | 2 +- html-test/ref/NonGreedy.html | 2 +- html-test/ref/Operators.html | 2 +- html-test/ref/PatternSyns.html | 2 +- html-test/ref/Properties.html | 2 +- html-test/ref/PruneWithWarning.html | 2 +- html-test/ref/QuasiExpr.html | 2 +- html-test/ref/QuasiQuote.html | 2 +- html-test/ref/SpuriousSuperclassConstraints.html | 2 +- html-test/ref/TH.html | 2 +- html-test/ref/TH2.html | 2 +- html-test/ref/Test.html | 2 +- html-test/ref/Ticket112.html | 2 +- html-test/ref/Ticket253_1.html | 2 +- html-test/ref/Ticket253_2.html | 2 +- html-test/ref/Ticket61.html | 2 +- html-test/ref/Ticket75.html | 2 +- html-test/ref/TitledPicture.html | 2 +- html-test/ref/TypeFamilies.html | 2 +- html-test/ref/TypeFamilies2.html | 2 +- html-test/ref/TypeOperators.html | 2 +- html-test/ref/Unicode.html | 2 +- html-test/ref/Visible.html | 2 +- 68 files changed, 75 insertions(+), 67 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc de306e6c79d391f67dfae9da23b73d619c4de51c From git at git.haskell.org Thu Mar 13 19:59:13 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 19:59:13 +0000 (UTC) Subject: [commit: haddock] master: Hide RHS of TFs with non-exported right hand sides (3606ad5) Message-ID: <20140313195913.5E2982406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : master Link : http://git.haskell.org/haddock.git/commitdiff/3606ad5fdb8b9c2c3f9a62de1d26702ad41f9a10 >--------------------------------------------------------------- commit 3606ad5fdb8b9c2c3f9a62de1d26702ad41f9a10 Author: Niklas Haas Date: Wed Mar 12 10:31:31 2014 +0100 Hide RHS of TFs with non-exported right hand sides Not sure what to do about data families yet, since technically it would not make a lot of sense to display constructors that cannot be used by the user. >--------------------------------------------------------------- 3606ad5fdb8b9c2c3f9a62de1d26702ad41f9a10 html-test/ref/TypeFamilies2.html | 92 ++++++++++++++++++++++-------- html-test/src/TypeFamilies2.hs | 32 ++++++++--- src/Haddock/Backends/LaTeX.hs | 3 +- src/Haddock/Backends/Xhtml/Decl.hs | 2 +- src/Haddock/Convert.hs | 7 ++- src/Haddock/Interface/AttachInstances.hs | 5 +- src/Haddock/Interface/Rename.hs | 2 +- src/Haddock/Types.hs | 6 +- 8 files changed, 105 insertions(+), 44 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 3606ad5fdb8b9c2c3f9a62de1d26702ad41f9a10 From git at git.haskell.org Thu Mar 13 19:59:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 19:59:15 +0000 (UTC) Subject: [commit: haddock] master: Add UnicodeSyntax alternatives for * and -> (64175d6) Message-ID: <20140313195915.6C5A52406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : master Link : http://git.haskell.org/haddock.git/commitdiff/64175d6ade5717b7e0c7fa0a122d16cae6779031 >--------------------------------------------------------------- commit 64175d6ade5717b7e0c7fa0a122d16cae6779031 Author: Niklas Haas Date: Thu Mar 13 07:01:27 2014 +0100 Add UnicodeSyntax alternatives for * and -> I could not find a cleaner way to do this other than checking for string equality with the given built-in types. But seeing as it's actually equivalent to string rewriting in GHC's implementation of UnicodeSyntax, it's probably fitting. >--------------------------------------------------------------- 64175d6ade5717b7e0c7fa0a122d16cae6779031 src/Haddock/Backends/Xhtml/Decl.hs | 9 +++++++-- 1 file changed, 7 insertions(+), 2 deletions(-) diff --git a/src/Haddock/Backends/Xhtml/Decl.hs b/src/Haddock/Backends/Xhtml/Decl.hs index c1b9032..cd504d8 100644 --- a/src/Haddock/Backends/Xhtml/Decl.hs +++ b/src/Haddock/Backends/Xhtml/Decl.hs @@ -769,10 +769,10 @@ ppCtxType unicode qual ty = ppr_mono_ty pREC_CTX ty unicode qual ppParendType unicode qual ty = ppr_mono_ty pREC_CON ty unicode qual ppFunLhType unicode qual ty = ppr_mono_ty pREC_FUN ty unicode qual -ppLKind :: Unicode -> Qualification-> LHsKind DocName -> Html +ppLKind :: Unicode -> Qualification -> LHsKind DocName -> Html ppLKind unicode qual y = ppKind unicode qual (unLoc y) -ppKind :: Unicode -> Qualification-> HsKind DocName -> Html +ppKind :: Unicode -> Qualification -> HsKind DocName -> Html ppKind unicode qual ki = ppr_mono_ty pREC_TOP ki unicode qual -- Drop top-level for-all type variables in user style @@ -798,6 +798,11 @@ ppr_mono_ty ctxt_prec (HsForAllTy expl tvs ctxt ty) unicode qual = maybeParen ctxt_prec pREC_FUN $ hsep [ppForAll expl tvs ctxt unicode qual, ppr_mono_lty pREC_TOP ty unicode qual] +-- UnicodeSyntax alternatives +ppr_mono_ty _ (HsTyVar name) True _ + | getOccString (getName name) == "*" = toHtml "?" + | getOccString (getName name) == "(->)" = toHtml "(?)" + ppr_mono_ty _ (HsBangTy b ty) u q = ppBang b +++ ppLParendType u q ty ppr_mono_ty _ (HsTyVar name) _ q = ppDocName q Prefix True name ppr_mono_ty ctxt_prec (HsFunTy ty1 ty2) u q = ppr_fun_ty ctxt_prec ty1 ty2 u q From git at git.haskell.org Thu Mar 13 19:59:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 19:59:17 +0000 (UTC) Subject: [commit: haddock] master: Display minimal complete definitions for type classes (eaf0a0b) Message-ID: <20140313195917.8CED22406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : master Link : http://git.haskell.org/haddock.git/commitdiff/eaf0a0b51f452398f3c64882a334f90b920df794 >--------------------------------------------------------------- commit eaf0a0b51f452398f3c64882a334f90b920df794 Author: Niklas Haas Date: Thu Mar 13 08:53:41 2014 +0100 Display minimal complete definitions for type classes This corresponds to the new {-# MINIMAL #-} pragma present in GHC 7.8+. I also cleaned up some of the places in which ExportDecl is used to make adding fields easier in the future. Lots of test cases have been updated since they now render with minimality information. >--------------------------------------------------------------- eaf0a0b51f452398f3c64882a334f90b920df794 html-test/ref/DeprecatedClass.html | 16 ++ html-test/ref/Hash.html | 8 + html-test/ref/Minimal.html | 273 ++++++++++++++++++++++++++++++++++ html-test/ref/Test.html | 14 ++ html-test/ref/Ticket61.html | 8 + html-test/src/Test.hs | 1 + src/Haddock/Backends/Hoogle.hs | 6 +- src/Haddock/Backends/LaTeX.hs | 6 +- src/Haddock/Backends/Xhtml.hs | 6 +- src/Haddock/Backends/Xhtml/Decl.hs | 28 +++- src/Haddock/Backends/Xhtml/Layout.hs | 4 + src/Haddock/Convert.hs | 5 +- src/Haddock/GhcUtils.hs | 11 +- src/Haddock/Interface/Create.hs | 41 +++-- src/Haddock/Interface/Rename.hs | 1 + 15 files changed, 398 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 eaf0a0b51f452398f3c64882a334f90b920df794 From git at git.haskell.org Thu Mar 13 19:59:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 19:59:19 +0000 (UTC) Subject: [commit: haddock] master: Strip links from recently added html tests (4ebde6b) Message-ID: <20140313195919.7E7A42406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : master Link : http://git.haskell.org/haddock.git/commitdiff/4ebde6b0846d29ccab283e9211162dd9c09ccf9a >--------------------------------------------------------------- commit 4ebde6b0846d29ccab283e9211162dd9c09ccf9a Author: Niklas Haas Date: Thu Mar 13 13:52:40 2014 +0100 Strip links from recently added html tests These were accidentally left there when the tests were originally added >--------------------------------------------------------------- 4ebde6b0846d29ccab283e9211162dd9c09ccf9a html-test/ref/ImplicitParams.html | 20 ++-- html-test/ref/Operators.html | 72 ++++++------ html-test/ref/PatternSyns.html | 58 +++++----- html-test/ref/TypeFamilies.html | 230 ++++++++++++++++++------------------- html-test/ref/TypeFamilies2.html | 38 +++--- html-test/ref/TypeOperators.html | 16 +-- 6 files changed, 217 insertions(+), 217 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 4ebde6b0846d29ccab283e9211162dd9c09ccf9a From git at git.haskell.org Thu Mar 13 19:59:21 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 19:59:21 +0000 (UTC) Subject: [commit: haddock] master: Update changelog (385db9a) Message-ID: <20140313195921.9AFC92406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : master Link : http://git.haskell.org/haddock.git/commitdiff/385db9ab8cec14b21c06632eb1fcbe14ac3c3859 >--------------------------------------------------------------- commit 385db9ab8cec14b21c06632eb1fcbe14ac3c3859 Author: Mateusz Kowalczyk Date: Thu Mar 13 19:19:31 2014 +0000 Update changelog >--------------------------------------------------------------- 385db9ab8cec14b21c06632eb1fcbe14ac3c3859 CHANGES | 8 ++++++++ 1 file changed, 8 insertions(+) diff --git a/CHANGES b/CHANGES index e067785..a98a0e0 100644 --- a/CHANGES +++ b/CHANGES @@ -1,3 +1,11 @@ +Changes in version 2.14.1 + + * Render * and -> with their UnicodeSyntax equivalents if -U is enabled + + * Display minimal complete definitions for type classes + + * Hide right hand side of TF instances with hidden names on the RHS + Changes in version 2.14.0 * Print entities with missing documentation (#258) From git at git.haskell.org Thu Mar 13 21:07:07 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 21:07:07 +0000 (UTC) Subject: [commit: packages/containers] ghc-head: Add README with instructions for contributors (df732aa) Message-ID: <20140313210707.55E592406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : ghc-head Link : http://git.haskell.org/packages/containers.git/commitdiff/df732aaf4640c521c0851623ce5d71fad4139dcc >--------------------------------------------------------------- commit df732aaf4640c521c0851623ce5d71fad4139dcc Author: kardboardb Date: Thu Feb 20 10:19:29 2014 -0800 Add README with instructions for contributors >--------------------------------------------------------------- df732aaf4640c521c0851623ce5d71fad4139dcc README | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/README b/README new file mode 100644 index 0000000..1fb326b --- /dev/null +++ b/README @@ -0,0 +1,6 @@ +POTENTIAL CONTRIBUTORS +====================== + +Please follow the guidelines outlined on the Haskell Wiki when proposing an API change. + +http://www.haskell.org/haskellwiki/Library_submissions#Guidance_for_proposers From git at git.haskell.org Thu Mar 13 21:07:09 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 21:07:09 +0000 (UTC) Subject: [commit: packages/containers] ghc-head: Merge pull request #38 from kardboardb/master (536d85a) Message-ID: <20140313210709.D49E72406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : ghc-head Link : http://git.haskell.org/packages/containers.git/commitdiff/536d85ae8746b118c1f51759c0bf140c908a789d >--------------------------------------------------------------- commit 536d85ae8746b118c1f51759c0bf140c908a789d Merge: 13902bd df732aa Author: Milan Straka Date: Fri Feb 21 09:14:11 2014 +0100 Merge pull request #38 from kardboardb/master Add a README with instructions for contributors >--------------------------------------------------------------- 536d85ae8746b118c1f51759c0bf140c908a789d README | 6 ++++++ 1 file changed, 6 insertions(+) From git at git.haskell.org Thu Mar 13 21:07:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 21:07:11 +0000 (UTC) Subject: [commit: packages/containers] ghc-head: Add role annotations to Map and Set. (c243512) Message-ID: <20140313210711.5F77624069@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : ghc-head Link : http://git.haskell.org/packages/containers.git/commitdiff/c24351257bf22627226a3fb94c140353fd611197 >--------------------------------------------------------------- commit c24351257bf22627226a3fb94c140353fd611197 Author: Richard Eisenberg Date: Thu Mar 13 16:06:59 2014 -0400 Add role annotations to Map and Set. See thread beginning here: http://www.haskell.org/pipermail/libraries/2014-March/022321.html >--------------------------------------------------------------- c24351257bf22627226a3fb94c140353fd611197 Data/Map/Base.hs | 4 ++++ Data/Set/Base.hs | 4 ++++ containers.cabal | 2 ++ 3 files changed, 10 insertions(+) diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs index 1f6512f..6a93a73 100644 --- a/Data/Map/Base.hs +++ b/Data/Map/Base.hs @@ -327,6 +327,10 @@ data Map k a = Bin {-# UNPACK #-} !Size !k a !(Map k a) !(Map k a) type Size = Int +#if __GLASGOW_HASKELL__ >= 708 +type role Map nominal representational +#endif + instance (Ord k) => Monoid (Map k v) where mempty = empty mappend = union diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs index 675c966..720ffb5 100644 --- a/Data/Set/Base.hs +++ b/Data/Set/Base.hs @@ -229,6 +229,10 @@ data Set a = Bin {-# UNPACK #-} !Size !a !(Set a) !(Set a) type Size = Int +#if __GLASGOW_HASKELL >= 708 +type role Set nominal +#endif + instance Ord a => Monoid (Set a) where mempty = empty mappend = union diff --git a/containers.cabal b/containers.cabal index b67548c..90bfa9c 100644 --- a/containers.cabal +++ b/containers.cabal @@ -63,6 +63,8 @@ Library if impl(ghc<7.0) extensions: MagicHash, DeriveDataTypeable, StandaloneDeriving, Rank2Types + if impl(ghc >= 7.8) + extensions: RoleAnnotations ------------------- -- T E S T I N G -- From git at git.haskell.org Thu Mar 13 21:07:13 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 21:07:13 +0000 (UTC) Subject: [commit: packages/containers] ghc-head: Bump version number to 0.5.5.0 (02cc94d) Message-ID: <20140313210713.5B3472406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : ghc-head Link : http://git.haskell.org/packages/containers.git/commitdiff/02cc94d727e0332df64deb7818fd246e3caab172 >--------------------------------------------------------------- commit 02cc94d727e0332df64deb7818fd246e3caab172 Author: Johan Tibell Date: Thu Mar 13 21:40:26 2014 +0100 Bump version number to 0.5.5.0 Two new role annotations were added. >--------------------------------------------------------------- 02cc94d727e0332df64deb7818fd246e3caab172 containers.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/containers.cabal b/containers.cabal index 90bfa9c..1d7d8bf 100644 --- a/containers.cabal +++ b/containers.cabal @@ -1,5 +1,5 @@ name: containers -version: 0.5.4.0 +version: 0.5.5.0 license: BSD3 license-file: LICENSE maintainer: fox at ucw.cz From git at git.haskell.org Thu Mar 13 21:08:32 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 21:08:32 +0000 (UTC) Subject: [commit: packages/containers] tag 'containers-0.5.5.0-release' created Message-ID: <20140313210833.0CA812406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers New tag : containers-0.5.5.0-release Referencing: 0d0269d150c869c7a7550cffc51608528794c29f From git at git.haskell.org Thu Mar 13 21:14:20 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 21:14:20 +0000 (UTC) Subject: [commit: ghc] master: Update to containers-0.5.5.0 (e55acf0) Message-ID: <20140313211421.C01A62406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e55acf007f5109b42a2e388eaca63445bbbc7376/ghc >--------------------------------------------------------------- commit e55acf007f5109b42a2e388eaca63445bbbc7376 Author: Herbert Valerio Riedel Date: Thu Mar 13 22:09:56 2014 +0100 Update to containers-0.5.5.0 This adds role annotations to Map and Set and therefore addresses #8718 Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- e55acf007f5109b42a2e388eaca63445bbbc7376 libraries/containers | 2 +- testsuite/tests/th/TH_Roles2.stderr | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/libraries/containers b/libraries/containers index 13902bd..02cc94d 160000 --- a/libraries/containers +++ b/libraries/containers @@ -1 +1 @@ -Subproject commit 13902bd436b54f400a1ddddba6f4ee4e9e517a26 +Subproject commit 02cc94d727e0332df64deb7818fd246e3caab172 diff --git a/testsuite/tests/th/TH_Roles2.stderr b/testsuite/tests/th/TH_Roles2.stderr index 8d71257..10fb988 100644 --- a/testsuite/tests/th/TH_Roles2.stderr +++ b/testsuite/tests/th/TH_Roles2.stderr @@ -9,7 +9,7 @@ TYPE CONSTRUCTORS FamilyInstance: none COERCION AXIOMS Dependent modules: [] -Dependent packages: [array-0.5.0.0, base, containers-0.5.4.0, +Dependent packages: [array-0.5.0.0, base, containers-0.5.5.0, deepseq-1.3.0.2, ghc-prim, integer-gmp, pretty-1.1.1.1, template-haskell] From git at git.haskell.org Thu Mar 13 21:20:10 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 21:20:10 +0000 (UTC) Subject: [commit: haddock] master: Always read in prologue files as UTF8 (#286). (5bcc099) Message-ID: <20140313212010.7A4012406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : master Link : http://git.haskell.org/haddock.git/commitdiff/5bcc09947718bec704ff9561dc193ba3c50a1ccf >--------------------------------------------------------------- commit 5bcc09947718bec704ff9561dc193ba3c50a1ccf Author: Mateusz Kowalczyk Date: Thu Mar 13 21:19:07 2014 +0000 Always read in prologue files as UTF8 (#286). >--------------------------------------------------------------- 5bcc09947718bec704ff9561dc193ba3c50a1ccf CHANGES | 4 ++++ src/Haddock.hs | 14 +++++++++----- 2 files changed, 13 insertions(+), 5 deletions(-) diff --git a/CHANGES b/CHANGES index a98a0e0..c59051a 100644 --- a/CHANGES +++ b/CHANGES @@ -1,3 +1,7 @@ +Changes in version 2.15.0 + + * Always read in prologue files as UTF8 (#286 and Cabal #1721) + Changes in version 2.14.1 * Render * and -> with their UnicodeSyntax equivalents if -U is enabled diff --git a/src/Haddock.hs b/src/Haddock.hs index e4c7fdc..67c4536 100644 --- a/src/Haddock.hs +++ b/src/Haddock.hs @@ -4,7 +4,8 @@ -- | -- Module : Haddock -- Copyright : (c) Simon Marlow 2003-2006, --- David Waern 2006-2010 +-- David Waern 2006-2010, +-- Mateusz Kowalczyk 2014 -- License : BSD-like -- -- Maintainer : haddock at projects.haskell.org @@ -447,10 +448,13 @@ getPrologue dflags flags = case [filename | Flag_Prologue filename <- flags ] of [] -> return Nothing [filename] -> do - str <- readFile filename - case parseParasMaybe dflags str of - Nothing -> throwE $ "failed to parse haddock prologue from file: " ++ filename - Just doc -> return (Just doc) + withFile filename ReadMode $ \h -> do + hSetEncoding h utf8 + str <- hGetContents h + case parseParasMaybe dflags str of + Nothing -> + throwE $ "failed to parse haddock prologue from file: " ++ filename + Just doc -> return (Just doc) _otherwise -> throwE "multiple -p/--prologue options" From git at git.haskell.org Thu Mar 13 21:28:21 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 21:28:21 +0000 (UTC) Subject: [commit: haddock] master: Style only (f5532d2) Message-ID: <20140313212821.A241A2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : master Link : http://git.haskell.org/haddock.git/commitdiff/f5532d27aa6849305dfa7042ccbf900a56555a2f >--------------------------------------------------------------- commit f5532d27aa6849305dfa7042ccbf900a56555a2f Author: Mateusz Kowalczyk Date: Thu Mar 13 21:28:09 2014 +0000 Style only >--------------------------------------------------------------- f5532d27aa6849305dfa7042ccbf900a56555a2f src/Haddock.hs | 60 ++++++++++++++++++++++++++------------------------------ 1 file changed, 28 insertions(+), 32 deletions(-) diff --git a/src/Haddock.hs b/src/Haddock.hs index 67c4536..6d975c9 100644 --- a/src/Haddock.hs +++ b/src/Haddock.hs @@ -1,5 +1,6 @@ {-# OPTIONS_GHC -Wwarn #-} {-# LANGUAGE CPP, ScopedTypeVariables #-} +{-# LANGUAGE LambdaCase #-} ----------------------------------------------------------------------------- -- | -- Module : Haddock @@ -296,9 +297,8 @@ readInterfaceFiles name_cache_accessor pairs = do catMaybes `liftM` mapM tryReadIface pairs where -- try to read an interface, warn if we can't - tryReadIface (paths, file) = do - eIface <- readInterfaceFile name_cache_accessor file - case eIface of + tryReadIface (paths, file) = + readInterfaceFile name_cache_accessor file >>= \case Left err -> liftIO $ do putStrLn ("Warning: Cannot read " ++ file ++ ":") putStrLn (" " ++ err) @@ -315,22 +315,21 @@ readInterfaceFiles name_cache_accessor pairs = do -- | Start a GHC session with the -haddock flag set. Also turn off -- compilation and linking. Then run the given 'Ghc' action. withGhc :: String -> [String] -> (DynFlags -> Ghc a) -> IO a -withGhc libDir flags ghcActs = do - runGhc (Just libDir) $ do - dynflags <- getSessionDynFlags - let dynflags' = gopt_set dynflags Opt_Haddock - let dynflags'' = dynflags' { - hscTarget = HscNothing, - ghcMode = CompManager, - ghcLink = NoLink - } - dynflags''' <- parseGhcFlags dynflags'' - defaultCleanupHandler dynflags''' $ do - -- ignore the following return-value, which is a list of packages - -- that may need to be re-linked: Haddock doesn't do any - -- dynamic or static linking at all! - _ <- setSessionDynFlags dynflags''' - ghcActs dynflags''' +withGhc libDir flags ghcActs = runGhc (Just libDir) $ do + dynflags <- getSessionDynFlags + let dynflags' = gopt_set dynflags Opt_Haddock + let dynflags'' = dynflags' { + hscTarget = HscNothing, + ghcMode = CompManager, + ghcLink = NoLink + } + dynflags''' <- parseGhcFlags dynflags'' + defaultCleanupHandler dynflags''' $ do + -- ignore the following return-value, which is a list of packages + -- that may need to be re-linked: Haddock doesn't do any + -- dynamic or static linking at all! + _ <- setSessionDynFlags dynflags''' + ghcActs dynflags''' where parseGhcFlags :: MonadIO m => DynFlags -> m DynFlags parseGhcFlags dynflags = do @@ -447,25 +446,22 @@ getPrologue :: DynFlags -> [Flag] -> IO (Maybe (Doc RdrName)) getPrologue dflags flags = case [filename | Flag_Prologue filename <- flags ] of [] -> return Nothing - [filename] -> do - withFile filename ReadMode $ \h -> do - hSetEncoding h utf8 - str <- hGetContents h - case parseParasMaybe dflags str of - Nothing -> - throwE $ "failed to parse haddock prologue from file: " ++ filename - Just doc -> return (Just doc) + [filename] -> withFile filename ReadMode $ \h -> do + hSetEncoding h utf8 + str <- hGetContents h + case parseParasMaybe dflags str of + Nothing -> + throwE $ "failed to parse haddock prologue from file: " ++ filename + Just doc -> return (Just doc) _otherwise -> throwE "multiple -p/--prologue options" #ifdef IN_GHC_TREE getInTreeDir :: IO String -getInTreeDir = do - m <- getExecDir - case m of - Nothing -> error "No GhcDir found" - Just d -> return (d ".." "lib") +getInTreeDir = getExecDir >>= \case + Nothing -> error "No GhcDir found" + Just d -> return (d ".." "lib") getExecDir :: IO (Maybe String) From git at git.haskell.org Thu Mar 13 21:39:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 21:39:19 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Update to containers-0.5.5.0 (5902b3b) Message-ID: <20140313213920.17C9D2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/5902b3bca7a4759fd615b0dfba1320c71c335c51/ghc >--------------------------------------------------------------- commit 5902b3bca7a4759fd615b0dfba1320c71c335c51 Author: Herbert Valerio Riedel Date: Thu Mar 13 22:09:56 2014 +0100 Update to containers-0.5.5.0 This adds role annotations to Map and Set and therefore addresses #8718 Signed-off-by: Herbert Valerio Riedel (cherry picked from commit e55acf007f5109b42a2e388eaca63445bbbc7376) >--------------------------------------------------------------- 5902b3bca7a4759fd615b0dfba1320c71c335c51 libraries/containers | 2 +- testsuite/tests/th/TH_Roles2.stderr | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/libraries/containers b/libraries/containers index 13902bd..02cc94d 160000 --- a/libraries/containers +++ b/libraries/containers @@ -1 +1 @@ -Subproject commit 13902bd436b54f400a1ddddba6f4ee4e9e517a26 +Subproject commit 02cc94d727e0332df64deb7818fd246e3caab172 diff --git a/testsuite/tests/th/TH_Roles2.stderr b/testsuite/tests/th/TH_Roles2.stderr index 8d71257..10fb988 100644 --- a/testsuite/tests/th/TH_Roles2.stderr +++ b/testsuite/tests/th/TH_Roles2.stderr @@ -9,7 +9,7 @@ TYPE CONSTRUCTORS FamilyInstance: none COERCION AXIOMS Dependent modules: [] -Dependent packages: [array-0.5.0.0, base, containers-0.5.4.0, +Dependent packages: [array-0.5.0.0, base, containers-0.5.5.0, deepseq-1.3.0.2, ghc-prim, integer-gmp, pretty-1.1.1.1, template-haskell] From git at git.haskell.org Thu Mar 13 21:39:23 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 21:39:23 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Update time to 1.4.2 release (cbdb63e) Message-ID: <20140313213923.664AA2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/cbdb63e46b2af432a7749316d06fe0d261edd30a/ghc >--------------------------------------------------------------- commit cbdb63e46b2af432a7749316d06fe0d261edd30a Author: Herbert Valerio Riedel Date: Mon Mar 3 09:25:45 2014 +0100 Update time to 1.4.2 release Note: The only visible change in `time-1.4.2` is at the SafeHaskell level Signed-off-by: Herbert Valerio Riedel (cherry picked from commit afb42a54bc0c5cd0dfb69750d3b5e76bcb66ff5a) >--------------------------------------------------------------- cbdb63e46b2af432a7749316d06fe0d261edd30a libraries/time | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/time b/libraries/time index d4f019b..adafac2 160000 --- a/libraries/time +++ b/libraries/time @@ -1 +1 @@ -Subproject commit d4f019b2c6a332be5443b5bf88d0c7fef91523c6 +Subproject commit adafac26307cffab0be20c126385ab161c259237 From git at git.haskell.org Thu Mar 13 21:39:42 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 21:39:42 +0000 (UTC) Subject: [commit: haddock] ghc-7.8: Merge remote-tracking branch 'v2.14' into ghc-7.8 (d74fe55) Message-ID: <20140313213942.753CE2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : ghc-7.8 Link : http://git.haskell.org/haddock.git/commitdiff/d74fe55f8e592a36978a2ec80402609d9b1352fa >--------------------------------------------------------------- commit d74fe55f8e592a36978a2ec80402609d9b1352fa Merge: 3945c9a de306e6 Author: Herbert Valerio Riedel Date: Thu Mar 13 21:49:36 2014 +0100 Merge remote-tracking branch 'v2.14' into ghc-7.8 This effectively updates to the haddock-2.14.1 "RC" Changes in version 2.14.1: - Render * and -> with their UnicodeSyntax equivalents if -U is enabled - Display minimal complete definitions for type classes - Hide right hand side of TF instances with hidden names on the RHS Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- d74fe55f8e592a36978a2ec80402609d9b1352fa CHANGES | 8 + doc/haddock.xml | 2 +- haddock.cabal | 2 +- haddock.spec | 2 +- html-test/ref/A.html | 2 +- html-test/ref/AdvanceTypes.html | 2 +- html-test/ref/B.html | 2 +- html-test/ref/Bold.html | 2 +- html-test/ref/Bug1.html | 2 +- html-test/ref/Bug195.html | 2 +- html-test/ref/Bug2.html | 2 +- html-test/ref/Bug3.html | 2 +- html-test/ref/Bug4.html | 2 +- html-test/ref/Bug6.html | 2 +- html-test/ref/Bug7.html | 2 +- html-test/ref/Bug8.html | 2 +- html-test/ref/BugDeprecated.html | 2 +- html-test/ref/BugExportHeadings.html | 2 +- html-test/ref/Bugs.html | 2 +- html-test/ref/DeprecatedClass.html | 18 +- html-test/ref/DeprecatedData.html | 2 +- html-test/ref/DeprecatedFunction.html | 2 +- html-test/ref/DeprecatedFunction2.html | 2 +- html-test/ref/DeprecatedFunction3.html | 2 +- html-test/ref/DeprecatedModule.html | 2 +- html-test/ref/DeprecatedModule2.html | 2 +- html-test/ref/DeprecatedNewtype.html | 2 +- html-test/ref/DeprecatedReExport.html | 2 +- html-test/ref/DeprecatedRecord.html | 2 +- html-test/ref/DeprecatedTypeFamily.html | 2 +- html-test/ref/DeprecatedTypeSynonym.html | 2 +- html-test/ref/Examples.html | 2 +- html-test/ref/Extensions.html | 2 +- html-test/ref/FunArgs.html | 2 +- html-test/ref/GADTRecords.html | 2 +- html-test/ref/Hash.html | 10 +- html-test/ref/HiddenInstances.html | 2 +- html-test/ref/HiddenInstancesB.html | 2 +- html-test/ref/Hyperlinks.html | 2 +- html-test/ref/IgnoreExports.html | 2 +- html-test/ref/ImplicitParams.html | 22 +- html-test/ref/Minimal.html | 273 ++++++++++++++++++++++ html-test/ref/ModuleWithWarning.html | 2 +- html-test/ref/NamedDoc.html | 2 +- html-test/ref/Nesting.html | 2 +- html-test/ref/NoLayout.html | 2 +- html-test/ref/NonGreedy.html | 2 +- html-test/ref/Operators.html | 74 +++--- html-test/ref/PatternSyns.html | 60 ++--- html-test/ref/Properties.html | 2 +- html-test/ref/PruneWithWarning.html | 2 +- html-test/ref/QuasiExpr.html | 2 +- html-test/ref/QuasiQuote.html | 2 +- html-test/ref/SpuriousSuperclassConstraints.html | 2 +- html-test/ref/TH.html | 2 +- html-test/ref/TH2.html | 2 +- html-test/ref/Test.html | 16 +- html-test/ref/Ticket112.html | 2 +- html-test/ref/Ticket253_1.html | 2 +- html-test/ref/Ticket253_2.html | 2 +- html-test/ref/Ticket61.html | 10 +- html-test/ref/Ticket75.html | 2 +- html-test/ref/TitledPicture.html | 2 +- html-test/ref/TypeFamilies.html | 232 +++++++++--------- html-test/ref/TypeFamilies2.html | 118 +++++++--- html-test/ref/TypeOperators.html | 18 +- html-test/ref/Unicode.html | 2 +- html-test/ref/Visible.html | 2 +- html-test/src/Test.hs | 1 + html-test/src/TypeFamilies2.hs | 32 ++- src/Haddock/Backends/Hoogle.hs | 6 +- src/Haddock/Backends/LaTeX.hs | 9 +- src/Haddock/Backends/Xhtml.hs | 6 +- src/Haddock/Backends/Xhtml/Decl.hs | 39 +++- src/Haddock/Backends/Xhtml/Layout.hs | 4 + src/Haddock/Convert.hs | 12 +- src/Haddock/GhcUtils.hs | 11 +- src/Haddock/Interface/AttachInstances.hs | 5 +- src/Haddock/Interface/Create.hs | 41 ++-- src/Haddock/Interface/Rename.hs | 3 +- src/Haddock/Types.hs | 6 +- 81 files changed, 794 insertions(+), 352 deletions(-) From git at git.haskell.org Thu Mar 13 21:39:44 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 21:39:44 +0000 (UTC) Subject: [commit: haddock] ghc-7.8's head updated: Merge remote-tracking branch 'v2.14' into ghc-7.8 (d74fe55) Message-ID: <20140313213944.8B7A22406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock Branch 'ghc-7.8' now includes: 0a09910 Hide RHS of TFs with non-exported right hand sides 1fda06f Add UnicodeSyntax alternatives for * and -> 1c8c2f2 Display minimal complete definitions for type classes c67d38a Strip links from recently added html tests de306e6 Bump version to 2.14.1 and update changelog d74fe55 Merge remote-tracking branch 'v2.14' into ghc-7.8 From git at git.haskell.org Thu Mar 13 22:00:21 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 22:00:21 +0000 (UTC) Subject: [commit: ghc] master: Fix two issues in stg_newArrayzh (46d05ba) Message-ID: <20140313220021.1BF3E2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/46d05ba03d1491cade4a3fe33f0b8c404ad3c760/ghc >--------------------------------------------------------------- commit 46d05ba03d1491cade4a3fe33f0b8c404ad3c760 Author: Johan Tibell Date: Thu Mar 13 22:24:24 2014 +0100 Fix two issues in stg_newArrayzh The implementations of newArray# and newArrayArray#, stg_newArrayzh and stg_newArrayArrayzh, had three issues: * The condition for the loop that fills the array with the initial element was incorrect. It would write into the card table as well. The condition for the loop that filled the card table was never executed, as its condition was also wrong. In the end this didn't lead to any disasters as the value of the card table doesn't matter for newly allocated arrays. * The card table was unnecessarily initialized. The card table is only used when the array isn't copied, which new arrays always are. By not writing the card table at all we save some cycles. * The ticky allocation accounting was wrong. The second argument to TICK_ALLOC_PRIM is the size of the closure excluding the header size, but the header size was incorrectly included. Fixes #8867. >--------------------------------------------------------------- 46d05ba03d1491cade4a3fe33f0b8c404ad3c760 rts/PrimOps.cmm | 22 ++++------------------ 1 file changed, 4 insertions(+), 18 deletions(-) diff --git a/rts/PrimOps.cmm b/rts/PrimOps.cmm index db65a4a..0e547be 100644 --- a/rts/PrimOps.cmm +++ b/rts/PrimOps.cmm @@ -178,7 +178,7 @@ stg_newArrayzh ( W_ n /* words */, gcptr init ) size = n + mutArrPtrsCardWords(n); words = BYTES_TO_WDS(SIZEOF_StgMutArrPtrs) + size; ("ptr" arr) = ccall allocate(MyCapability() "ptr",words); - TICK_ALLOC_PRIM(SIZEOF_StgMutArrPtrs, WDS(n), 0); + TICK_ALLOC_PRIM(SIZEOF_StgMutArrPtrs, WDS(size), 0); SET_HDR(arr, stg_MUT_ARR_PTRS_DIRTY_info, CCCS); StgMutArrPtrs_ptrs(arr) = n; @@ -187,18 +187,11 @@ stg_newArrayzh ( W_ n /* words */, gcptr init ) // Initialise all elements of the the array with the value in R2 p = arr + SIZEOF_StgMutArrPtrs; for: - if (p < arr + WDS(words)) { + if (p < arr + SIZEOF_StgMutArrPtrs + WDS(n)) { W_[p] = init; p = p + WDS(1); goto for; } - // Initialise the mark bits with 0 - for2: - if (p < arr + WDS(size)) { - W_[p] = 0; - p = p + WDS(1); - goto for2; - } return (arr); } @@ -270,7 +263,7 @@ stg_newArrayArrayzh ( W_ n /* words */ ) size = n + mutArrPtrsCardWords(n); words = BYTES_TO_WDS(SIZEOF_StgMutArrPtrs) + size; ("ptr" arr) = ccall allocate(MyCapability() "ptr",words); - TICK_ALLOC_PRIM(SIZEOF_StgMutArrPtrs, WDS(n), 0); + TICK_ALLOC_PRIM(SIZEOF_StgMutArrPtrs, WDS(size), 0); SET_HDR(arr, stg_MUT_ARR_PTRS_DIRTY_info, W_[CCCS]); StgMutArrPtrs_ptrs(arr) = n; @@ -279,18 +272,11 @@ stg_newArrayArrayzh ( W_ n /* words */ ) // Initialise all elements of the array with a pointer to the new array p = arr + SIZEOF_StgMutArrPtrs; for: - if (p < arr + WDS(words)) { + if (p < arr + SIZEOF_StgMutArrPtrs + WDS(n)) { W_[p] = arr; p = p + WDS(1); goto for; } - // Initialise the mark bits with 0 - for2: - if (p < arr + WDS(size)) { - W_[p] = 0; - p = p + WDS(1); - goto for2; - } return (arr); } From git at git.haskell.org Thu Mar 13 22:57:51 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 22:57:51 +0000 (UTC) Subject: [commit: ghc] master: fix SHELL makefile variable to be set by the configure script (fixes #8783) (a0bcbb5) Message-ID: <20140313225752.0C6222406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a0bcbb54481297f9ff329766529a8343c4853e3f/ghc >--------------------------------------------------------------- commit a0bcbb54481297f9ff329766529a8343c4853e3f Author: Karel Gardas Date: Wed Mar 12 16:14:49 2014 +0100 fix SHELL makefile variable to be set by the configure script (fixes #8783) The patch provided by Christian Maeder Signed-off-by: Karel Gardas Signed-off-by: Austin Seipp >--------------------------------------------------------------- a0bcbb54481297f9ff329766529a8343c4853e3f 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 b805a14..f24c495 100644 --- a/mk/config.mk.in +++ b/mk/config.mk.in @@ -652,7 +652,7 @@ PIC = pic RANLIB_CMD = @RANLIB_CMD@ REAL_RANLIB_CMD = @REAL_RANLIB_CMD@ SED = @SedCmd@ -SHELL = /bin/sh +SHELL = @SHELL@ HaveDtrace = @HaveDtrace@ USE_DTRACE = $(HaveDtrace) From git at git.haskell.org Thu Mar 13 22:57:55 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 22:57:55 +0000 (UTC) Subject: [commit: ghc] master: Fix incorrect blocksize calculation on Win64 (b7e5d72) Message-ID: <20140313225755.4B0EB2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b7e5d722c6811f34253d8202540dd9b0ec1b6766/ghc >--------------------------------------------------------------- commit b7e5d722c6811f34253d8202540dd9b0ec1b6766 Author: Kyrill Briantsev Date: Wed Mar 12 14:31:21 2014 -0500 Fix incorrect blocksize calculation on Win64 Fixes #8839 Signed-off-by: Austin Seipp >--------------------------------------------------------------- b7e5d722c6811f34253d8202540dd9b0ec1b6766 includes/rts/storage/Block.h | 14 ++++++++++++-- 1 file changed, 12 insertions(+), 2 deletions(-) diff --git a/includes/rts/storage/Block.h b/includes/rts/storage/Block.h index 5567bf4..29c081b 100644 --- a/includes/rts/storage/Block.h +++ b/includes/rts/storage/Block.h @@ -9,16 +9,26 @@ #ifndef RTS_STORAGE_BLOCK_H #define RTS_STORAGE_BLOCK_H +#include "ghcconfig.h" + /* The actual block and megablock-size constants are defined in * includes/Constants.h, all constants here are derived from these. */ /* Block related constants (BLOCK_SHIFT is defined in Constants.h) */ +#if SIZEOF_LONG == SIZEOF_VOID_P +#define UNIT 1UL +#elif SIZEOF_LONG_LONG == SIZEOF_VOID_P +#define UNIT 1ULL +#else +#error "Size of pointer is suspicious." +#endif + #ifdef CMINUSMINUS #define BLOCK_SIZE (1< Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b99ace39cb2484bfc2d648b55a1a43ed78e4b9a0/ghc >--------------------------------------------------------------- commit b99ace39cb2484bfc2d648b55a1a43ed78e4b9a0 Author: Kyrill Briantsev Date: Thu Mar 13 17:00:17 2014 -0500 Fix incorrect maxStkSize calculation (#8858) Signed-off-by: Austin Seipp >--------------------------------------------------------------- b99ace39cb2484bfc2d648b55a1a43ed78e4b9a0 rts/RtsFlags.c | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/rts/RtsFlags.c b/rts/RtsFlags.c index 573e701..af1b204 100644 --- a/rts/RtsFlags.c +++ b/rts/RtsFlags.c @@ -97,12 +97,12 @@ void initRtsFlagsDefaults(void) StgWord64 maxStkSize = 8 * getPhysicalMemorySize() / 10; // if getPhysicalMemorySize fails just move along with an 8MB limit if (maxStkSize == 0) - maxStkSize = (8 * 1024 * 1024) / sizeof(W_); + maxStkSize = 8 * 1024 * 1024; RtsFlags.GcFlags.statsFile = NULL; RtsFlags.GcFlags.giveStats = NO_GC_STATS; - RtsFlags.GcFlags.maxStkSize = maxStkSize; + RtsFlags.GcFlags.maxStkSize = maxStkSize / sizeof(W_); RtsFlags.GcFlags.initialStkSize = 1024 / sizeof(W_); RtsFlags.GcFlags.stkChunkSize = (32 * 1024) / sizeof(W_); RtsFlags.GcFlags.stkChunkBufferSize = (1 * 1024) / sizeof(W_); From git at git.haskell.org Thu Mar 13 22:58:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 22:58:01 +0000 (UTC) Subject: [commit: ghc] master: config.mk.in: ARM now supports dynamic linking with the LLVM backend (d574fcb) Message-ID: <20140313225801.967DB2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d574fcbba09fd6c9d10a79e19daf5f15bb0a6cde/ghc >--------------------------------------------------------------- commit d574fcbba09fd6c9d10a79e19daf5f15bb0a6cde Author: Ben Gamari Date: Thu Mar 6 21:22:28 2014 +0100 config.mk.in: ARM now supports dynamic linking with the LLVM backend Signed-off-by: Austin Seipp >--------------------------------------------------------------- d574fcbba09fd6c9d10a79e19daf5f15bb0a6cde mk/config.mk.in | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/mk/config.mk.in b/mk/config.mk.in index 2c997de..fef1fb8 100644 --- a/mk/config.mk.in +++ b/mk/config.mk.in @@ -95,8 +95,7 @@ TargetElf = YES endif # Some platforms don't support shared libraries -NoSharedLibsPlatformList = arm-unknown-linux \ - powerpc-unknown-linux \ +NoSharedLibsPlatformList = powerpc-unknown-linux \ x86_64-unknown-mingw32 \ i386-unknown-mingw32 \ sparc-sun-solaris2 \ From git at git.haskell.org Thu Mar 13 22:58:04 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 22:58:04 +0000 (UTC) Subject: [commit: ghc] master: Fix T2110 now that base has map/coerce rule. (cbdd832) Message-ID: <20140313225804.AC66C2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cbdd83288bc3d3d2f07eadf800e9f2b27916c168/ghc >--------------------------------------------------------------- commit cbdd83288bc3d3d2f07eadf800e9f2b27916c168 Author: Austin Seipp Date: Thu Mar 13 17:56:18 2014 -0500 Fix T2110 now that base has map/coerce rule. Signed-off-by: Austin Seipp >--------------------------------------------------------------- cbdd83288bc3d3d2f07eadf800e9f2b27916c168 testsuite/tests/simplCore/should_run/T2110.hs | 4 ---- 1 file changed, 4 deletions(-) diff --git a/testsuite/tests/simplCore/should_run/T2110.hs b/testsuite/tests/simplCore/should_run/T2110.hs index fb65781..610be09 100644 --- a/testsuite/tests/simplCore/should_run/T2110.hs +++ b/testsuite/tests/simplCore/should_run/T2110.hs @@ -3,10 +3,6 @@ import GHC.Exts import Unsafe.Coerce -{-# RULES -"map/coerce" map coerce = coerce - #-} - newtype Age = Age Int fooAge :: [Int] -> [Age] From git at git.haskell.org Thu Mar 13 22:58:06 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 22:58:06 +0000 (UTC) Subject: [commit: ghc] master: DriverPipeline: Ensure -globalopt is passed to LLVM opt (b84b5da) Message-ID: <20140313225806.9A64D2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b84b5da4430aacd5bf8422b06a861cd0584f99cf/ghc >--------------------------------------------------------------- commit b84b5da4430aacd5bf8422b06a861cd0584f99cf Author: Ben Gamari Date: Thu Mar 6 21:20:02 2014 +0100 DriverPipeline: Ensure -globalopt is passed to LLVM opt While -O1 and -O2 both include -globalopt, the order in which the passes are run means that aliases aren't resolved which then causes llc to fall over. See GHC bug #8855. Signed-off-by: Austin Seipp >--------------------------------------------------------------- b84b5da4430aacd5bf8422b06a861cd0584f99cf compiler/main/DriverPipeline.hs | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs index f6d9e03..564edd2 100644 --- a/compiler/main/DriverPipeline.hs +++ b/compiler/main/DriverPipeline.hs @@ -1337,7 +1337,7 @@ runPhase (RealPhase LlvmOpt) input_fn dflags -- passes only, so if the user is passing us extra options we assume -- they know what they are doing and don't get in the way. optFlag = if null (getOpts dflags opt_lo) - then map SysTools.Option $ words (llvmOpts !! opt_lvl) + then map SysTools.Option $ words (llvmOpts ver !! opt_lvl) else [] tbaa | ver < 29 = "" -- no tbaa in 2.8 and earlier | gopt Opt_LlvmTBAA dflags = "--enable-tbaa=true" @@ -1357,7 +1357,11 @@ runPhase (RealPhase LlvmOpt) input_fn dflags where -- we always (unless -optlo specified) run Opt since we rely on it to -- fix up some pretty big deficiencies in the code we generate - llvmOpts = ["-mem2reg -globalopt", "-O1", "-O2"] + llvmOpts ver = [ "-mem2reg -globalopt" + , if ver >= 34 then "-O1 -globalopt" else "-O1" + -- LLVM 3.4 -O1 doesn't eliminate aliases reliably (bug #8855) + , "-O2" + ] ----------------------------------------------------------------------------- -- LlvmLlc phase From git at git.haskell.org Thu Mar 13 22:58:09 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 22:58:09 +0000 (UTC) Subject: [commit: ghc] master: disable shared libs on sparc (linux/solaris) (fixes #8857) (623883f) Message-ID: <20140313225812.42E902406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/623883f1ed0ee11cc925c4590fb09565403fd231/ghc >--------------------------------------------------------------- commit 623883f1ed0ee11cc925c4590fb09565403fd231 Author: Karel Gardas Date: Fri Mar 7 11:36:37 2014 +0100 disable shared libs on sparc (linux/solaris) (fixes #8857) Signed-off-by: Austin Seipp >--------------------------------------------------------------- 623883f1ed0ee11cc925c4590fb09565403fd231 mk/config.mk.in | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/mk/config.mk.in b/mk/config.mk.in index f24c495..2c997de 100644 --- a/mk/config.mk.in +++ b/mk/config.mk.in @@ -98,7 +98,9 @@ endif NoSharedLibsPlatformList = arm-unknown-linux \ powerpc-unknown-linux \ x86_64-unknown-mingw32 \ - i386-unknown-mingw32 + i386-unknown-mingw32 \ + sparc-sun-solaris2 \ + sparc-unknown-linux ifeq "$(SOLARIS_BROKEN_SHLD)" "YES" NoSharedLibsPlatformList += i386-unknown-solaris2 From git at git.haskell.org Thu Mar 13 22:59:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 22:59:56 +0000 (UTC) Subject: [commit: packages/base] master: Add RULE for "map coerce = map" (#8767) (f96dc54) Message-ID: <20140313225957.1DBEF2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/base On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f96dc5470355ce52741c717b6387d7f61b6a8dc1/base >--------------------------------------------------------------- commit f96dc5470355ce52741c717b6387d7f61b6a8dc1 Author: Austin Seipp Date: Thu Mar 13 16:51:34 2014 -0500 Add RULE for "map coerce = map" (#8767) Signed-off-by: Austin Seipp >--------------------------------------------------------------- f96dc5470355ce52741c717b6387d7f61b6a8dc1 GHC/Base.lhs | 11 +++++++++++ 1 file changed, 11 insertions(+) diff --git a/GHC/Base.lhs b/GHC/Base.lhs index 0a2dd80..bb605e7 100644 --- a/GHC/Base.lhs +++ b/GHC/Base.lhs @@ -400,6 +400,17 @@ mapFB c f = \x ys -> c (f x) ys "mapList" [1] forall f. foldr (mapFB (:) f) [] = map f "mapFB" forall c f g. mapFB (mapFB c f) g = mapFB c (f.g) #-} + +-- There's also a rule for Map and Data.Coerce. See "Safe Coercions", +-- section 6.4: +-- +-- http://research.microsoft.com/en-us/um/people/simonpj/papers/ext-f/coercible.pdf +-- +-- We rewrite late so the optimiser has as many chances as possible to +-- turn up instances of map coerce. + +{-# RULES "map/coerce" map coerce = coerce #-} + \end{code} From git at git.haskell.org Thu Mar 13 23:02:05 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 23:02:05 +0000 (UTC) Subject: [commit: ghc] master: codeGen: allocate small byte arrays of statically known size inline (210ccab) Message-ID: <20140313230205.82CD02406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/210ccabc9489bfbf814939e8b45646c8d0c7ce5f/ghc >--------------------------------------------------------------- commit 210ccabc9489bfbf814939e8b45646c8d0c7ce5f Author: Johan Tibell Date: Wed Mar 12 07:20:19 2014 +0100 codeGen: allocate small byte arrays of statically known size inline This results in a 57% runtime decrease when allocating an array of 128 bytes on a 64-bit machine. Fixes #8876. >--------------------------------------------------------------- 210ccabc9489bfbf814939e8b45646c8d0c7ce5f compiler/cmm/CLabel.hs | 5 +- compiler/cmm/SMRep.lhs | 24 ++++++++- compiler/codeGen/StgCmmPrim.hs | 49 ++++++++++++++---- .../codeGen/should_run/StaticByteArraySize.hs | 52 ++++++++++++++++++++ ...ArraySize.stdout => StaticByteArraySize.stdout} | 0 testsuite/tests/codeGen/should_run/all.T | 1 + ...InlineArrayAlloc.hs => InlineByteArrayAlloc.hs} | 8 +-- testsuite/tests/perf/should_run/all.T | 7 +++ utils/deriveConstants/DeriveConstants.hs | 2 +- 9 files changed, 130 insertions(+), 18 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 210ccabc9489bfbf814939e8b45646c8d0c7ce5f From git at git.haskell.org Thu Mar 13 23:20:21 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 13 Mar 2014 23:20:21 +0000 (UTC) Subject: [commit: packages/base] master: Remove misleading comment (ebe15a1) Message-ID: <20140313232023.ED6A52406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/base On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ebe15a10191aafb2bcfd3e29f234cd72c152459c/base >--------------------------------------------------------------- commit ebe15a10191aafb2bcfd3e29f234cd72c152459c Author: Austin Seipp Date: Thu Mar 13 18:19:28 2014 -0500 Remove misleading comment We actually can't inline at phase 0 here, because there's probably a pretty good chance 'map' will get optimized away which will defeat the rule. Signed-off-by: Austin Seipp >--------------------------------------------------------------- ebe15a10191aafb2bcfd3e29f234cd72c152459c GHC/Base.lhs | 3 --- 1 file changed, 3 deletions(-) diff --git a/GHC/Base.lhs b/GHC/Base.lhs index bb605e7..1c8e144 100644 --- a/GHC/Base.lhs +++ b/GHC/Base.lhs @@ -405,9 +405,6 @@ mapFB c f = \x ys -> c (f x) ys -- section 6.4: -- -- http://research.microsoft.com/en-us/um/people/simonpj/papers/ext-f/coercible.pdf --- --- We rewrite late so the optimiser has as many chances as possible to --- turn up instances of map coerce. {-# RULES "map/coerce" map coerce = coerce #-} From git at git.haskell.org Fri Mar 14 03:35:49 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Mar 2014 03:35:49 +0000 (UTC) Subject: [commit: ghc] master: Recharacterize test according to discussion in #8851. (8ee6162) Message-ID: <20140314033549.29F632406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8ee6162e9a3377cd4c79f49b63f92046b0d5c708/ghc >--------------------------------------------------------------- commit 8ee6162e9a3377cd4c79f49b63f92046b0d5c708 Author: Richard Eisenberg Date: Thu Mar 13 15:12:27 2014 -0400 Recharacterize test according to discussion in #8851. >--------------------------------------------------------------- 8ee6162e9a3377cd4c79f49b63f92046b0d5c708 testsuite/tests/deriving/should_compile/all.T | 1 - .../deriving/{should_compile => should_fail}/T8851.hs | 0 testsuite/tests/deriving/should_fail/T8851.stderr | 12 ++++++++++++ testsuite/tests/deriving/should_fail/all.T | 1 + 4 files changed, 13 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/deriving/should_compile/all.T b/testsuite/tests/deriving/should_compile/all.T index b34290f..cc4115c 100644 --- a/testsuite/tests/deriving/should_compile/all.T +++ b/testsuite/tests/deriving/should_compile/all.T @@ -44,6 +44,5 @@ test('AutoDeriveTypeable', normal, compile, ['']) test('T8138', reqlib('primitive'), compile, ['-O2']) test('T8631', normal, compile, ['']) test('T8758', extra_clean(['T8758a.o', 'T8758a.hi']), multimod_compile, ['T8758a', '-v0']) -test('T8851', expect_broken(8851), compile, ['']) test('T8678', normal, compile, ['']) test('T8865', normal, compile, ['']) diff --git a/testsuite/tests/deriving/should_compile/T8851.hs b/testsuite/tests/deriving/should_fail/T8851.hs similarity index 100% rename from testsuite/tests/deriving/should_compile/T8851.hs rename to testsuite/tests/deriving/should_fail/T8851.hs diff --git a/testsuite/tests/deriving/should_fail/T8851.stderr b/testsuite/tests/deriving/should_fail/T8851.stderr new file mode 100644 index 0000000..348f1f1 --- /dev/null +++ b/testsuite/tests/deriving/should_fail/T8851.stderr @@ -0,0 +1,12 @@ + +T8851.hs:24:12: + Could not coerce from ?Monad Parser? to ?Monad MyParser? + because the first type argument of ?Monad? has role Nominal, + but the arguments ?Parser? and ?MyParser? differ + arising from the coercion of the method ?notFollowedBy? from type + ?forall a. (Monad Parser, Show a) => Parser a -> Parser ()? to type + ?forall a. (Monad MyParser, Show a) => MyParser a -> MyParser ()? + Possible fix: + use a standalone 'deriving instance' declaration, + so you can specify the instance context yourself + When deriving the instance for (Parsing MyParser) diff --git a/testsuite/tests/deriving/should_fail/all.T b/testsuite/tests/deriving/should_fail/all.T index 1ffa5fc..d503b6e 100644 --- a/testsuite/tests/deriving/should_fail/all.T +++ b/testsuite/tests/deriving/should_fail/all.T @@ -49,3 +49,4 @@ test('T7148a', normal, compile_fail, ['']) test('T7800', normal, multimod_compile_fail, ['T7800','']) test('T5498', normal, compile_fail, ['']) test('T6147', normal, compile_fail, ['']) +test('T8851', normal, compile_fail, ['']) From git at git.haskell.org Fri Mar 14 03:35:51 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Mar 2014 03:35:51 +0000 (UTC) Subject: [commit: ghc] master: Remove "Safe mode" check for Coercible instances (5972229) Message-ID: <20140314033552.054262406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/59722295bb8da8f01d37356fbed6aef7321a8195/ghc >--------------------------------------------------------------- commit 59722295bb8da8f01d37356fbed6aef7321a8195 Author: Richard Eisenberg Date: Thu Mar 13 14:16:37 2014 -0400 Remove "Safe mode" check for Coercible instances We assume that library authors supply correct role annotations for their types, and therefore we do not need to check for the availability of data constructors in Safe mode. See discussion in #8725. This effectively fixes #8827 and #8826. >--------------------------------------------------------------- 59722295bb8da8f01d37356fbed6aef7321a8195 compiler/typecheck/TcInteract.lhs | 21 +++++--------------- .../typecheck/should_fail/TcCoercibleFailSafe.hs | 11 ---------- .../should_fail/TcCoercibleFailSafe.stderr | 8 -------- testsuite/tests/typecheck/should_fail/all.T | 1 - 4 files changed, 5 insertions(+), 36 deletions(-) diff --git a/compiler/typecheck/TcInteract.lhs b/compiler/typecheck/TcInteract.lhs index 377cd2d..75835ad 100644 --- a/compiler/typecheck/TcInteract.lhs +++ b/compiler/typecheck/TcInteract.lhs @@ -1922,11 +1922,10 @@ getCoercibleInst loc ty1 ty2 = do -- Get some global stuff in scope, for nice pattern-guard based code in `go` rdr_env <- getGlobalRdrEnvTcS famenv <- getFamInstEnvs - safeMode <- safeLanguageOn `fmap` getDynFlags - go safeMode famenv rdr_env + go famenv rdr_env where - go :: Bool -> FamInstEnvs -> GlobalRdrEnv -> TcS LookupInstResult - go safeMode famenv rdr_env + go :: FamInstEnvs -> GlobalRdrEnv -> TcS LookupInstResult + go famenv rdr_env -- Coercible a a (see case 1 in [Coercible Instances]) | ty1 `tcEqType` ty2 = do return $ GenInst [] @@ -1946,11 +1945,8 @@ getCoercibleInst loc ty1 ty2 = do | Just (tc1,tyArgs1) <- splitTyConApp_maybe ty1, Just (tc2,tyArgs2) <- splitTyConApp_maybe ty2, tc1 == tc2, - nominalArgsAgree tc1 tyArgs1 tyArgs2, - not safeMode || all (dataConsInScope rdr_env) (tyConsOfTyCon tc1) - = do -- Mark all used data constructors as used - when safeMode $ mapM_ (markDataConsAsUsed rdr_env) (tyConsOfTyCon tc1) - -- We want evidence for all type arguments of role R + nominalArgsAgree tc1 tyArgs1 tyArgs2 + = do -- We want evidence for all type arguments of role R arg_stuff <- forM (zip3 (tyConRoles tc1) tyArgs1 tyArgs2) $ \(r,ta1,ta2) -> case r of Nominal -> do return @@ -2060,13 +2056,6 @@ air, in getCoercibleInst. The following ?instances? are present: The type constructor can be used undersaturated; then the Coercible instance is at a higher kind. This does not cause problems. - Furthermore in Safe Haskell code, we check that - * the data constructors of C are in scope and - * the data constructors of all type constructors used in the definition of - * C are in scope. - This is required as otherwise the previous check can be circumvented by - just adding a local data type around C. - 4. instance Coercible r b => Coercible (NT t1 t2 ...) b instance Coercible a r => Coercible a (NT t1 t2 ...) for a newtype constructor NT (or data family instance that resolves to a diff --git a/testsuite/tests/typecheck/should_fail/TcCoercibleFailSafe.hs b/testsuite/tests/typecheck/should_fail/TcCoercibleFailSafe.hs deleted file mode 100644 index 85f86b6..0000000 --- a/testsuite/tests/typecheck/should_fail/TcCoercibleFailSafe.hs +++ /dev/null @@ -1,11 +0,0 @@ -{-# LANGUAGE RoleAnnotations, RankNTypes, ScopedTypeVariables, Safe #-} - -import GHC.Prim (coerce, Coercible) -import Data.Ord (Down) - -newtype Age = Age Int deriving Show - -foo1 :: (Down Age -> Down Int) -foo1 = coerce - -main = return () diff --git a/testsuite/tests/typecheck/should_fail/TcCoercibleFailSafe.stderr b/testsuite/tests/typecheck/should_fail/TcCoercibleFailSafe.stderr deleted file mode 100644 index 2d7bf19..0000000 --- a/testsuite/tests/typecheck/should_fail/TcCoercibleFailSafe.stderr +++ /dev/null @@ -1,8 +0,0 @@ - -TcCoercibleFailSafe.hs:9:8: - Could not coerce from ?Down Age? to ?Down Int? - because the constructor of ?Down? is not imported - as required in SafeHaskell mode - arising from a use of ?coerce? - In the expression: coerce - In an equation for ?foo1?: foo1 = coerce diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index 9f5af09..9367aed 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -317,7 +317,6 @@ test('T7989', normal, compile_fail, ['']) test('T8142', normal, compile_fail, ['']) test('T8262', normal, compile_fail, ['']) test('TcCoercibleFail', when(compiler_lt('ghc', '7.7'), skip), compile_fail, ['']) -test('TcCoercibleFailSafe', when(compiler_lt('ghc', '7.7'), skip), compile_fail, ['']) test('TcCoercibleFail2', when(compiler_lt('ghc', '7.7'), skip), compile_fail, ['']) test('TcCoercibleFail3', when(compiler_lt('ghc', '7.7'), skip), compile_fail, ['']) test('T8306', normal, compile_fail, ['']) From git at git.haskell.org Fri Mar 14 03:35:54 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Mar 2014 03:35:54 +0000 (UTC) Subject: [commit: ghc] master: Fix #8884. (8c5ea91) Message-ID: <20140314033554.C683B2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8c5ea91d68cdc79b413e05f7dacfd052f5de8c64/ghc >--------------------------------------------------------------- commit 8c5ea91d68cdc79b413e05f7dacfd052f5de8c64 Author: Richard Eisenberg Date: Thu Mar 13 15:48:56 2014 -0400 Fix #8884. There were two unrelated errors fixed here: 1) Make sure that only the *result kind* is reified when reifying a type family. Previously, the whole kind was reified, which defies the TH spec. 2) Omit kind patterns in equations. >--------------------------------------------------------------- 8c5ea91d68cdc79b413e05f7dacfd052f5de8c64 compiler/typecheck/TcSplice.lhs | 19 +++++++++++++------ testsuite/tests/th/T7477.stderr | 2 +- testsuite/tests/th/T8884.hs | 21 +++++++++++++++++++++ testsuite/tests/th/T8884.stderr | 3 +++ testsuite/tests/th/TH_reifyDecl1.stderr | 12 ++++++------ testsuite/tests/th/all.T | 1 + 6 files changed, 45 insertions(+), 13 deletions(-) diff --git a/compiler/typecheck/TcSplice.lhs b/compiler/typecheck/TcSplice.lhs index 9129ed8..2f4687d 100644 --- a/compiler/typecheck/TcSplice.lhs +++ b/compiler/typecheck/TcSplice.lhs @@ -1194,7 +1194,8 @@ reifyThing thing = pprPanic "reifyThing" (pprTcTyThingCategory thing) ------------------------------------------- reifyAxBranch :: CoAxBranch -> TcM TH.TySynEqn reifyAxBranch (CoAxBranch { cab_lhs = args, cab_rhs = rhs }) - = do { args' <- mapM reifyType args + -- remove kind patterns (#8884) + = do { args' <- mapM reifyType (filter (not . isKind) args) ; rhs' <- reifyType rhs ; return (TH.TySynEqn args' rhs') } @@ -1210,10 +1211,15 @@ reifyTyCon tc = return (TH.PrimTyConI (reifyName tc) (tyConArity tc) (isUnLiftedTyCon tc)) | isFamilyTyCon tc - = do { let tvs = tyConTyVars tc - kind = tyConKind tc - ; kind' <- if isLiftedTypeKind kind then return Nothing - else fmap Just (reifyKind kind) + = do { let tvs = tyConTyVars tc + kind = tyConKind tc + + -- we need the *result kind* (see #8884) + (kvs, mono_kind) = splitForAllTys kind + -- tyConArity includes *kind* params + (_, res_kind) = splitKindFunTysN (tyConArity tc - length kvs) + mono_kind + ; kind' <- fmap Just (reifyKind res_kind) ; tvs' <- reifyTyVars tvs ; flav' <- reifyFamFlavour tc @@ -1315,7 +1321,8 @@ reifyFamilyInstance (FamInst { fi_flavor = flavor , fi_rhs = rhs }) = case flavor of SynFamilyInst -> - do { th_lhs <- reifyTypes lhs + -- remove kind patterns (#8884) + do { th_lhs <- reifyTypes (filter (not . isKind) lhs) ; th_rhs <- reifyType rhs ; return (TH.TySynInstD (reifyName fam) (TH.TySynEqn th_lhs th_rhs)) } diff --git a/testsuite/tests/th/T7477.stderr b/testsuite/tests/th/T7477.stderr index f6a9e0d..f94de68 100644 --- a/testsuite/tests/th/T7477.stderr +++ b/testsuite/tests/th/T7477.stderr @@ -1,3 +1,3 @@ T7477.hs:10:4: Warning: - type instance T7477.F GHC.Prim.* GHC.Types.Int = GHC.Types.Bool + type instance T7477.F GHC.Types.Int = GHC.Types.Bool diff --git a/testsuite/tests/th/T8884.hs b/testsuite/tests/th/T8884.hs new file mode 100644 index 0000000..782bf90 --- /dev/null +++ b/testsuite/tests/th/T8884.hs @@ -0,0 +1,21 @@ +{-# LANGUAGE TemplateHaskell, TypeFamilies, PolyKinds #-} + +module T8884 where + +import Language.Haskell.TH + +type family Foo a where + Foo x = x + +type family Baz (a :: k) +type instance Baz x = x + +$( do FamilyI foo@(ClosedTypeFamilyD _ tvbs1 m_kind1 eqns1) [] <- reify ''Foo + FamilyI baz@(FamilyD TypeFam _ tvbs2 m_kind2) + [inst@(TySynInstD _ eqn2)] <- reify ''Baz + runIO $ putStrLn $ pprint foo + runIO $ putStrLn $ pprint baz + runIO $ putStrLn $ pprint inst + return [ ClosedTypeFamilyD (mkName "Foo'") tvbs1 m_kind1 eqns1 + , FamilyD TypeFam (mkName "Baz'") tvbs2 m_kind2 + , TySynInstD (mkName "Baz'") eqn2 ] ) \ No newline at end of file diff --git a/testsuite/tests/th/T8884.stderr b/testsuite/tests/th/T8884.stderr new file mode 100644 index 0000000..3c45d0e --- /dev/null +++ b/testsuite/tests/th/T8884.stderr @@ -0,0 +1,3 @@ +type family T8884.Foo (a_0 :: k_1) :: k_1 where T8884.Foo x_2 = x_2 +type family T8884.Baz (a_0 :: k_1) :: * +type instance T8884.Baz x_0 = x_0 diff --git a/testsuite/tests/th/TH_reifyDecl1.stderr b/testsuite/tests/th/TH_reifyDecl1.stderr index 82a4f57..9c3b6da 100644 --- a/testsuite/tests/th/TH_reifyDecl1.stderr +++ b/testsuite/tests/th/TH_reifyDecl1.stderr @@ -21,15 +21,15 @@ class TH_reifyDecl1.C2 a_0 instance TH_reifyDecl1.C2 GHC.Types.Int class TH_reifyDecl1.C3 a_0 instance TH_reifyDecl1.C3 GHC.Types.Int -type family TH_reifyDecl1.AT1 a_0 :: * -> * +type family TH_reifyDecl1.AT1 a_0 :: * type instance TH_reifyDecl1.AT1 GHC.Types.Int = GHC.Types.Bool -data family TH_reifyDecl1.AT2 a_0 :: * -> * +data family TH_reifyDecl1.AT2 a_0 :: * data instance TH_reifyDecl1.AT2 GHC.Types.Int = TH_reifyDecl1.AT2Int -type family TH_reifyDecl1.TF1 a_0 :: * -> * -type family TH_reifyDecl1.TF2 a_0 :: * -> * +type family TH_reifyDecl1.TF1 a_0 :: * +type family TH_reifyDecl1.TF2 a_0 :: * type instance TH_reifyDecl1.TF2 GHC.Types.Bool = GHC.Types.Bool -data family TH_reifyDecl1.DF1 a_0 :: * -> * -data family TH_reifyDecl1.DF2 a_0 :: * -> * +data family TH_reifyDecl1.DF1 a_0 :: * +data family TH_reifyDecl1.DF2 a_0 :: * data instance TH_reifyDecl1.DF2 GHC.Types.Bool = TH_reifyDecl1.DBool diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index e7db161..60203ca 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -322,3 +322,4 @@ test('T8759a', normal, compile_fail, ['-v0']) test('T7021', extra_clean(['T7021a.hi', 'T7021a.o']), multimod_compile, ['T7021','-v0']) test('T8807', normal, compile, ['-v0']) +test('T8884', normal, compile, ['-v0']) \ No newline at end of file From git at git.haskell.org Fri Mar 14 03:35:57 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Mar 2014 03:35:57 +0000 (UTC) Subject: [commit: ghc] master: Fix typo in user's manual, changing "-j N" to "-jN". (337bac3) Message-ID: <20140314033557.402732406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/337bac31648a1b1261fe241286cf93cb5f09aa12/ghc >--------------------------------------------------------------- commit 337bac31648a1b1261fe241286cf93cb5f09aa12 Author: Richard Eisenberg Date: Thu Mar 13 17:20:50 2014 -0400 Fix typo in user's manual, changing "-j N" to "-jN". >--------------------------------------------------------------- 337bac31648a1b1261fe241286cf93cb5f09aa12 docs/users_guide/flags.xml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/docs/users_guide/flags.xml b/docs/users_guide/flags.xml index b054fd9..d932813 100644 --- a/docs/users_guide/flags.xml +++ b/docs/users_guide/flags.xml @@ -3020,7 +3020,7 @@ - + When compiling with --make, compile N modules in parallel. dynamic - From git at git.haskell.org Fri Mar 14 08:14:14 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Mar 2014 08:14:14 +0000 (UTC) Subject: [commit: ghc] master: Call Arity : Note about fakeBoringCalls (797da5c) Message-ID: <20140314081414.2E8182406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/797da5c5e0e13a66b55ae7fce85df4f5bee39ca8/ghc >--------------------------------------------------------------- commit 797da5c5e0e13a66b55ae7fce85df4f5bee39ca8 Author: Joachim Breitner Date: Wed Mar 12 15:48:21 2014 +0100 Call Arity : Note about fakeBoringCalls >--------------------------------------------------------------- 797da5c5e0e13a66b55ae7fce85df4f5bee39ca8 compiler/simplCore/CallArity.hs | 29 +++++++++++++++++++++-------- 1 file changed, 21 insertions(+), 8 deletions(-) diff --git a/compiler/simplCore/CallArity.hs b/compiler/simplCore/CallArity.hs index db0406d..85e555e 100644 --- a/compiler/simplCore/CallArity.hs +++ b/compiler/simplCore/CallArity.hs @@ -304,6 +304,19 @@ called, i.e. variables bound in a pattern match. So interesting are variables th * top-level or let bound * and possibly functions (typeArity > 0) +Note [Information about boring variables] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +If we decide that the variable bound in `let x = e1 in e2` is not interesting, +the analysis of `e2` will not report anything about `x`. To ensure that +`callArityBind` does still do the right thing we have to extend the result from +`e2` with a safe approximation. + +This is done using `fakeBoringCalls` and has the effect of analysing + x `seq` x `seq` e2 +instead, i.e. with `both` the result from `e2` with the most conservative +result about the uninteresting value. + Note [Recursion and fixpointing] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -348,7 +361,7 @@ callArityTopLvl exported int1 (b:bs) exported' = filter isExportedId int2 ++ exported int' = int1 `addInterestingBinds` b (ae1, bs') = callArityTopLvl exported' int' bs - ae1' = fakeBoringCalls int' b ae1 + ae1' = fakeBoringCalls int' b ae1 -- See Note [Information about boring variables] (ae2, b') = callArityBind ae1' int1 b @@ -435,7 +448,7 @@ callArityAnal arity int (Let bind e) where int_body = int `addInterestingBinds` bind (ae_body, e') = callArityAnal arity int_body e - ae_body' = fakeBoringCalls int_body bind ae_body + ae_body' = fakeBoringCalls int_body bind ae_body -- See Note [Information about boring variables] (final_ae, bind') = callArityBind ae_body' int bind -- This is a variant of callArityAnal that is additionally told whether @@ -470,14 +483,14 @@ addInterestingBinds int bind = int `delVarSetList` bindersOf bind -- Possible shadowing `extendVarSetList` interestingBinds bind --- For every boring variable in the binder, this amends the CallArityRes to --- report safe information about them (co-called with everything else, arity 0). +-- For every boring variable in the binder, add a safe approximation +-- See Note [Information about boring variables] fakeBoringCalls :: VarSet -> CoreBind -> CallArityRes -> CallArityRes -fakeBoringCalls int bind res - = addCrossCoCalls (domRes boring) (domRes res) $ (boring `lubRes` res) +fakeBoringCalls int bind res = boring `both` res where - boring = ( emptyUnVarGraph - , mkVarEnv [ (v, 0) | v <- bindersOf bind, not (v `elemVarSet` int)]) + boring = calledMultipleTimes $ + ( emptyUnVarGraph + , mkVarEnv [ (v, 0) | v <- bindersOf bind, not (v `elemVarSet` int)]) -- Used for both local and top-level binds From git at git.haskell.org Fri Mar 14 08:23:26 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Mar 2014 08:23:26 +0000 (UTC) Subject: [commit: ghc] master: Remove unused gHC_COERCIBLE (41ab584) Message-ID: <20140314082326.754B32406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/41ab58415224b7fa27cfc27846d4b56aad3e1949/ghc >--------------------------------------------------------------- commit 41ab58415224b7fa27cfc27846d4b56aad3e1949 Author: Joachim Breitner Date: Fri Mar 14 09:23:15 2014 +0100 Remove unused gHC_COERCIBLE >--------------------------------------------------------------- 41ab58415224b7fa27cfc27846d4b56aad3e1949 compiler/prelude/PrelNames.lhs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/compiler/prelude/PrelNames.lhs b/compiler/prelude/PrelNames.lhs index 0a44003..3e5a8eb 100644 --- a/compiler/prelude/PrelNames.lhs +++ b/compiler/prelude/PrelNames.lhs @@ -353,7 +353,7 @@ genericTyConNames = [ pRELUDE :: Module pRELUDE = mkBaseModule_ pRELUDE_NAME -gHC_PRIM, gHC_TYPES, gHC_GENERICS, gHC_MAGIC, gHC_COERCIBLE, +gHC_PRIM, gHC_TYPES, gHC_GENERICS, gHC_MAGIC, gHC_CLASSES, gHC_BASE, gHC_ENUM, gHC_GHCI, gHC_CSTRING, gHC_SHOW, gHC_READ, gHC_NUM, gHC_INTEGER_TYPE, gHC_LIST, gHC_TUPLE, dATA_TUPLE, dATA_EITHER, dATA_STRING, dATA_FOLDABLE, dATA_TRAVERSABLE, dATA_MONOID, @@ -370,7 +370,6 @@ gHC_TYPES = mkPrimModule (fsLit "GHC.Types") gHC_MAGIC = mkPrimModule (fsLit "GHC.Magic") gHC_CSTRING = mkPrimModule (fsLit "GHC.CString") gHC_CLASSES = mkPrimModule (fsLit "GHC.Classes") -gHC_COERCIBLE = mkPrimModule (fsLit "GHC.Coercible") gHC_BASE = mkBaseModule (fsLit "GHC.Base") gHC_ENUM = mkBaseModule (fsLit "GHC.Enum") From git at git.haskell.org Fri Mar 14 08:27:03 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Mar 2014 08:27:03 +0000 (UTC) Subject: [commit: packages/ghc-prim] master: Update Coercible docs due to Safe Haskell adjustment (db4f5e5) Message-ID: <20140314082704.0641B2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc-prim On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/db4f5e5245d5b24a8f0a06a85ded89c6124fb4c7/ghc-prim >--------------------------------------------------------------- commit db4f5e5245d5b24a8f0a06a85ded89c6124fb4c7 Author: Joachim Breitner Date: Fri Mar 14 09:26:12 2014 +0100 Update Coercible docs due to Safe Haskell adjustment This should go with [59722295bb8da8f01d37356fbed6aef7321a8195/ghc], see bug #8826. >--------------------------------------------------------------- db4f5e5245d5b24a8f0a06a85ded89c6124fb4c7 GHC/Types.hs | 4 ---- 1 file changed, 4 deletions(-) diff --git a/GHC/Types.hs b/GHC/Types.hs index 96673e1..310c04d 100644 --- a/GHC/Types.hs +++ b/GHC/Types.hs @@ -116,10 +116,6 @@ data (~) a b = Eq# ((~#) a b) -- @Coercible@ instance themself, and the @phantom@ type arguments can be -- changed arbitrarily. -- --- In SafeHaskell code, this instance is only usable if the constructors of --- every type constructor used in the definition of @D@ (including --- those of @D@ itself) are in scope. --- -- The third kind of instance exists for every @newtype NT = MkNT T@ and -- comes in two variants, namely -- From git at git.haskell.org Fri Mar 14 09:33:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Mar 2014 09:33:15 +0000 (UTC) Subject: [commit: ghc] master: testsuite: look for tests-ghc directories for libraries (c61d40e) Message-ID: <20140314093315.B72482406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c61d40e8780d5dad2767c7dfb3f9251d586926fe/ghc >--------------------------------------------------------------- commit c61d40e8780d5dad2767c7dfb3f9251d586926fe Author: Austin Seipp Date: Fri Mar 14 04:26:50 2014 -0500 testsuite: look for tests-ghc directories for libraries Who knows how long the tests for containers have been broken. They haven't bitrotted, however. Signed-off-by: Austin Seipp >--------------------------------------------------------------- c61d40e8780d5dad2767c7dfb3f9251d586926fe testsuite/tests/Makefile | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/Makefile b/testsuite/tests/Makefile index 9234bcc..3b2ce49 100644 --- a/testsuite/tests/Makefile +++ b/testsuite/tests/Makefile @@ -12,7 +12,9 @@ $(error base library does not seem to be installed) endif # Now find the "tests" directories of those libraries, where they exist -LIBRARY_TEST_PATHS := $(wildcard $(patsubst %, $(TOP)/../libraries/%/tests, $(LIBRARIES))) +LIBRARY_TEST_PATHS := $(wildcard $(patsubst %, $(TOP)/../libraries/%/tests, $(LIBRARIES))) \ + $(wildcard $(patsubst %, $(TOP)/../libraries/%/tests-ghc, $(LIBRARIES))) + # Add tests from packages RUNTEST_OPTS += $(patsubst %, --rootdir=%, $(LIBRARY_TEST_PATHS)) From git at git.haskell.org Fri Mar 14 10:05:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Mar 2014 10:05:19 +0000 (UTC) Subject: [commit: packages/containers] ghc-head: Fix a typo in GHC #if guard (68aaa66) Message-ID: <20140314100519.6B9A62406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : ghc-head Link : http://git.haskell.org/packages/containers.git/commitdiff/68aaa661dec34b6c842e5feaa39df6c11744ea64 >--------------------------------------------------------------- commit 68aaa661dec34b6c842e5feaa39df6c11744ea64 Author: Johan Tibell Date: Fri Mar 14 10:30:37 2014 +0100 Fix a typo in GHC #if guard >--------------------------------------------------------------- 68aaa661dec34b6c842e5feaa39df6c11744ea64 Data/Set/Base.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs index 720ffb5..f863d17 100644 --- a/Data/Set/Base.hs +++ b/Data/Set/Base.hs @@ -229,7 +229,7 @@ data Set a = Bin {-# UNPACK #-} !Size !a !(Set a) !(Set a) type Size = Int -#if __GLASGOW_HASKELL >= 708 +#if __GLASGOW_HASKELL__ >= 708 type role Set nominal #endif From git at git.haskell.org Fri Mar 14 10:05:21 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Mar 2014 10:05:21 +0000 (UTC) Subject: [commit: packages/containers] ghc-head: Bump version number to 0.5.5.1 (e787f05) Message-ID: <20140314100521.875672406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers On branch : ghc-head Link : http://git.haskell.org/packages/containers.git/commitdiff/e787f05e7ef7b07363bd04962af8b1ec65693888 >--------------------------------------------------------------- commit e787f05e7ef7b07363bd04962af8b1ec65693888 Author: Johan Tibell Date: Fri Mar 14 10:31:46 2014 +0100 Bump version number to 0.5.5.1 Fixed a typo in an #if guard that made Set get the wrong role annotation. >--------------------------------------------------------------- e787f05e7ef7b07363bd04962af8b1ec65693888 containers.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/containers.cabal b/containers.cabal index 1d7d8bf..8abca7a 100644 --- a/containers.cabal +++ b/containers.cabal @@ -1,5 +1,5 @@ name: containers -version: 0.5.5.0 +version: 0.5.5.1 license: BSD3 license-file: LICENSE maintainer: fox at ucw.cz From git at git.haskell.org Fri Mar 14 10:06:31 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Mar 2014 10:06:31 +0000 (UTC) Subject: [commit: packages/containers] tag 'containers-0.5.5.1-release' created Message-ID: <20140314100631.6C2702406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/containers New tag : containers-0.5.5.1-release Referencing: fcbcbffee84575f6ea3d0e9e53eb0d9537893c7d From git at git.haskell.org Fri Mar 14 10:16:57 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Mar 2014 10:16:57 +0000 (UTC) Subject: [commit: ghc] master: Update to containers-0.5.5.1 (df265b9) Message-ID: <20140314101657.7F6812406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/df265b95a2f3640425b43b17993b9ec78a287f60/ghc >--------------------------------------------------------------- commit df265b95a2f3640425b43b17993b9ec78a287f60 Author: Herbert Valerio Riedel Date: Fri Mar 14 11:13:39 2014 +0100 Update to containers-0.5.5.1 This fixes a wrong #if around role annotations (see #8718) Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- df265b95a2f3640425b43b17993b9ec78a287f60 libraries/containers | 2 +- testsuite/tests/th/TH_Roles2.stderr | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/libraries/containers b/libraries/containers index 02cc94d..e787f05 160000 --- a/libraries/containers +++ b/libraries/containers @@ -1 +1 @@ -Subproject commit 02cc94d727e0332df64deb7818fd246e3caab172 +Subproject commit e787f05e7ef7b07363bd04962af8b1ec65693888 diff --git a/testsuite/tests/th/TH_Roles2.stderr b/testsuite/tests/th/TH_Roles2.stderr index 10fb988..a4526e1 100644 --- a/testsuite/tests/th/TH_Roles2.stderr +++ b/testsuite/tests/th/TH_Roles2.stderr @@ -9,7 +9,7 @@ TYPE CONSTRUCTORS FamilyInstance: none COERCION AXIOMS Dependent modules: [] -Dependent packages: [array-0.5.0.0, base, containers-0.5.5.0, +Dependent packages: [array-0.5.0.0, base, containers-0.5.5.1, deepseq-1.3.0.2, ghc-prim, integer-gmp, pretty-1.1.1.1, template-haskell] From git at git.haskell.org Fri Mar 14 10:19:13 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Mar 2014 10:19:13 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Update to containers-0.5.5.1 (702fb1d) Message-ID: <20140314101913.C4C7D2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/702fb1ddf44256d5b03cc81164606f0b5beb31e5/ghc >--------------------------------------------------------------- commit 702fb1ddf44256d5b03cc81164606f0b5beb31e5 Author: Herbert Valerio Riedel Date: Fri Mar 14 11:13:39 2014 +0100 Update to containers-0.5.5.1 This fixes a wrong #if around role annotations (see #8718) Signed-off-by: Herbert Valerio Riedel (cherry picked from commit df265b95a2f3640425b43b17993b9ec78a287f60) >--------------------------------------------------------------- 702fb1ddf44256d5b03cc81164606f0b5beb31e5 libraries/containers | 2 +- testsuite/tests/th/TH_Roles2.stderr | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/libraries/containers b/libraries/containers index 02cc94d..e787f05 160000 --- a/libraries/containers +++ b/libraries/containers @@ -1 +1 @@ -Subproject commit 02cc94d727e0332df64deb7818fd246e3caab172 +Subproject commit e787f05e7ef7b07363bd04962af8b1ec65693888 diff --git a/testsuite/tests/th/TH_Roles2.stderr b/testsuite/tests/th/TH_Roles2.stderr index 10fb988..a4526e1 100644 --- a/testsuite/tests/th/TH_Roles2.stderr +++ b/testsuite/tests/th/TH_Roles2.stderr @@ -9,7 +9,7 @@ TYPE CONSTRUCTORS FamilyInstance: none COERCION AXIOMS Dependent modules: [] -Dependent packages: [array-0.5.0.0, base, containers-0.5.5.0, +Dependent packages: [array-0.5.0.0, base, containers-0.5.5.1, deepseq-1.3.0.2, ghc-prim, integer-gmp, pretty-1.1.1.1, template-haskell] From git at git.haskell.org Fri Mar 14 10:28:38 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Mar 2014 10:28:38 +0000 (UTC) Subject: [commit: packages/ghc-prim] master: Note [Kind-changing of (~) and Coercible] (b31737d) Message-ID: <20140314102838.23EEE2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc-prim On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b31737dfe6c1d8e973b3bc94c2bcee1a74fba29f/ghc-prim >--------------------------------------------------------------- commit b31737dfe6c1d8e973b3bc94c2bcee1a74fba29f Author: Joachim Breitner Date: Fri Mar 14 11:28:35 2014 +0100 Note [Kind-changing of (~) and Coercible] >--------------------------------------------------------------- b31737dfe6c1d8e973b3bc94c2bcee1a74fba29f GHC/Types.hs | 26 +++++++++++++++++++++++--- 1 file changed, 23 insertions(+), 3 deletions(-) diff --git a/GHC/Types.hs b/GHC/Types.hs index 310c04d..25f4176 100644 --- a/GHC/Types.hs +++ b/GHC/Types.hs @@ -81,6 +81,28 @@ or the '>>' and '>>=' operations from the 'Monad' class. newtype IO a = IO (State# RealWorld -> (# State# RealWorld, a #)) +{- +Note [Kind-changing of (~) and Coercible] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +(~) and Coercible are tricky to define. To the user, they must appear as +constraints, but we cannot define them as such in Haskell. But we also cannot +just define them only in GHC.Prim (like (->)), because we need a real module +for them, e.g. to compile the constructor's info table. + +Furthermore the type of MkCoercible cannot be written in Haskell (no syntax for +~#R). + +So we define them as regular data types in GHC.Types, but do /not/ export them. +This ensures we have a home module. We then define them with the types and +kinds that we actually want, in TysWiredIn, and export them in GHC.Prim. + +Haddock still takes the documentation from GHC.Types (and not from the fake +module created from primops.txt.pp), so we have the user-facing documentation +here. +-} + + -- | A data constructor used to box up all unlifted equalities -- -- The type constructor is special in that GHC pretends that it @@ -88,9 +110,6 @@ newtype IO a = IO (State# RealWorld -> (# State# RealWorld, a #)) data (~) a b = Eq# ((~#) a b) --- Despite this not being exported here, the documentation will --- be used by haddock, hence the user-facing blurb here, and not in primops.txt.pp: - -- | This two-parameter class has instances for types @a@ and @b@ if -- the compiler can infer that they have the same representation. This class -- does not have regular instances; instead they are created on-the-fly during @@ -135,6 +154,7 @@ data (~) a b = Eq# ((~#) a b) -- -- /Since: 4.7.0.0/ data Coercible a b = MkCoercible ((~#) a b) +-- Also see Note [Kind-changing of (~) and Coercible] -- | Alias for tagToEnum#. Returns True of its parameter is 1# and False -- if it is 0#. From git at git.haskell.org Fri Mar 14 10:29:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Mar 2014 10:29:50 +0000 (UTC) Subject: [commit: ghc] master: Reference Note [Kind-changing of (~) and Coercible] (4133ff8) Message-ID: <20140314102951.0DC912406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4133ff86cbeefedf51f5ec963a06665e35fc68dd/ghc >--------------------------------------------------------------- commit 4133ff86cbeefedf51f5ec963a06665e35fc68dd Author: Joachim Breitner Date: Fri Mar 14 11:28:48 2014 +0100 Reference Note [Kind-changing of (~) and Coercible] >--------------------------------------------------------------- 4133ff86cbeefedf51f5ec963a06665e35fc68dd compiler/prelude/TysWiredIn.lhs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/compiler/prelude/TysWiredIn.lhs b/compiler/prelude/TysWiredIn.lhs index bf1907d..9ecc581 100644 --- a/compiler/prelude/TysWiredIn.lhs +++ b/compiler/prelude/TysWiredIn.lhs @@ -174,10 +174,12 @@ mkWiredInDataConName built_in modu fs unique datacon (AConLike (RealDataCon datacon)) -- Relevant DataCon built_in +-- See Note [Kind-changing of (~) and Coercible] eqTyConName, eqBoxDataConName :: Name eqTyConName = mkWiredInTyConName BuiltInSyntax gHC_TYPES (fsLit "~") eqTyConKey eqTyCon eqBoxDataConName = mkWiredInDataConName UserSyntax gHC_TYPES (fsLit "Eq#") eqBoxDataConKey eqBoxDataCon +-- See Note [Kind-changing of (~) and Coercible] coercibleTyConName, coercibleDataConName :: Name coercibleTyConName = mkWiredInTyConName UserSyntax gHC_TYPES (fsLit "Coercible") coercibleTyConKey coercibleTyCon coercibleDataConName = mkWiredInDataConName UserSyntax gHC_TYPES (fsLit "MkCoercible") coercibleDataConKey coercibleDataCon From git at git.haskell.org Fri Mar 14 11:30:36 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Mar 2014 11:30:36 +0000 (UTC) Subject: [commit: packages/ghc-prim] master: Better Comment [Kind-changing of (~) and Coercible] (b19daeb) Message-ID: <20140314113036.3EDD62406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc-prim On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b19daeb18c2c64ef2207f70806048c5288e1333c/ghc-prim >--------------------------------------------------------------- commit b19daeb18c2c64ef2207f70806048c5288e1333c Author: Joachim Breitner Date: Fri Mar 14 12:26:14 2014 +0100 Better Comment [Kind-changing of (~) and Coercible] >--------------------------------------------------------------- b19daeb18c2c64ef2207f70806048c5288e1333c GHC/Types.hs | 12 +++++++++++- 1 file changed, 11 insertions(+), 1 deletion(-) diff --git a/GHC/Types.hs b/GHC/Types.hs index 25f4176..3023045 100644 --- a/GHC/Types.hs +++ b/GHC/Types.hs @@ -95,11 +95,21 @@ Furthermore the type of MkCoercible cannot be written in Haskell (no syntax for So we define them as regular data types in GHC.Types, but do /not/ export them. This ensures we have a home module. We then define them with the types and -kinds that we actually want, in TysWiredIn, and export them in GHC.Prim. +kinds that we actually want, in TysWiredIn. + +We also export coercibleTyCon in PrelInfo's ghcPrimExports. +(This is not needed for (~), as that is not importable and handled specially by +the parser). +Why not export it in GHC.Types? Because then ghci and haddock would, for some +reason, display it as a data type, and not as a constraint. Haddock still takes the documentation from GHC.Types (and not from the fake module created from primops.txt.pp), so we have the user-facing documentation here. + +(This this note merely documents what is implemented because it happens to +work, and should not be taken as an indication of good design. Cleanup is +appreciated). -} From git at git.haskell.org Fri Mar 14 11:30:37 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Mar 2014 11:30:37 +0000 (UTC) Subject: [commit: ghc] master: Another reference to Note [Kind-changing of (~) and Coercible] (d53ccab) Message-ID: <20140314113038.05D0C2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d53ccab6ab32df38c0c226dea51f702f20d4feb3/ghc >--------------------------------------------------------------- commit d53ccab6ab32df38c0c226dea51f702f20d4feb3 Author: Joachim Breitner Date: Fri Mar 14 12:26:26 2014 +0100 Another reference to Note [Kind-changing of (~) and Coercible] >--------------------------------------------------------------- d53ccab6ab32df38c0c226dea51f702f20d4feb3 compiler/prelude/PrelInfo.lhs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/compiler/prelude/PrelInfo.lhs b/compiler/prelude/PrelInfo.lhs index bfcea1c..ca156ee 100644 --- a/compiler/prelude/PrelInfo.lhs +++ b/compiler/prelude/PrelInfo.lhs @@ -124,6 +124,8 @@ primOpId op = primOpIds ! primOpTag op GHC.Prim "exports" all the primops and primitive types, some wired-in Ids. +See Note [Kind-changing of (~) and Coerciblea] for why we export coercibleTyCon here. + \begin{code} ghcPrimExports :: [IfaceExport] ghcPrimExports @@ -134,6 +136,7 @@ ghcPrimExports \end{code} + %************************************************************************ %* * \subsection{Built-in keys} From git at git.haskell.org Fri Mar 14 11:53:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Mar 2014 11:53:15 +0000 (UTC) Subject: [commit: packages/ghc-prim] master: Refer to the coercible paper in Coercible' docs (fc7aaf5) Message-ID: <20140314115315.E5CE62406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc-prim On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fc7aaf57a33ab07b70628c75fcf134fdf4e701e5/ghc-prim >--------------------------------------------------------------- commit fc7aaf57a33ab07b70628c75fcf134fdf4e701e5 Author: Joachim Breitner Date: Fri Mar 14 12:41:46 2014 +0100 Refer to the coercible paper in Coercible' docs Implements parts of #8888. >--------------------------------------------------------------- fc7aaf57a33ab07b70628c75fcf134fdf4e701e5 GHC/Types.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/GHC/Types.hs b/GHC/Types.hs index 3023045..a144657 100644 --- a/GHC/Types.hs +++ b/GHC/Types.hs @@ -162,6 +162,10 @@ data (~) a b = Eq# ((~#) a b) -- -- @type role Set nominal@ -- +-- For more details about this feature, please refer to +-- +-- by Joachim Breitner, Richard A. Eisenberg, Simon Peyton Jones and Stephanie Weirich. +-- -- /Since: 4.7.0.0/ data Coercible a b = MkCoercible ((~#) a b) -- Also see Note [Kind-changing of (~) and Coercible] From git at git.haskell.org Fri Mar 14 11:53:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Mar 2014 11:53:17 +0000 (UTC) Subject: [commit: ghc] master: Document Coercible in the user guide (1e36a38) Message-ID: <20140314115317.559BF2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1e36a386042248523de69ad6b02c43a6631ed5d0/ghc >--------------------------------------------------------------- commit 1e36a386042248523de69ad6b02c43a6631ed5d0 Author: Joachim Breitner Date: Fri Mar 14 12:51:37 2014 +0100 Document Coercible in the user guide as a subsection of "Equality constraints", containing references to the module's haddock and to the paper. Fixes #8888 >--------------------------------------------------------------- 1e36a386042248523de69ad6b02c43a6631ed5d0 docs/users_guide/glasgow_exts.xml | 15 +++++++++++++++ 1 file changed, 15 insertions(+) diff --git a/docs/users_guide/glasgow_exts.xml b/docs/users_guide/glasgow_exts.xml index 4217b7d..9dbd545 100644 --- a/docs/users_guide/glasgow_exts.xml +++ b/docs/users_guide/glasgow_exts.xml @@ -6729,6 +6729,21 @@ class (F a ~ b) => C a b where with the class head. Method signatures are not affected by that process. + + + The <literal>Coercible</literal> constraint + + The constraint Coercible t1 t2 is similar to t1 ~ + t2, but denotes representational equality between + t1 and t2 in the sense of Roles + (). It is exported by + Data.Coerce, + which also contains the documentation. More details and discussion can be found in + the paper + Safe Coercions". + + + From git at git.haskell.org Fri Mar 14 13:35:54 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Mar 2014 13:35:54 +0000 (UTC) Subject: [commit: ghc] wip/T8776: Honor Op_PrintExplicitForalls setting in pprIfaceForAllPart (a819a19) Message-ID: <20140314133554.93E322406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8776 Link : http://ghc.haskell.org/trac/ghc/changeset/a819a19d5956bd9712bc044b42ac64a1c437b7d2/ghc >--------------------------------------------------------------- commit a819a19d5956bd9712bc044b42ac64a1c437b7d2 Author: Dr. ERDI Gergo Date: Fri Mar 14 19:50:15 2014 +0800 Honor Op_PrintExplicitForalls setting in pprIfaceForAllPart >--------------------------------------------------------------- a819a19d5956bd9712bc044b42ac64a1c437b7d2 compiler/iface/IfaceType.lhs | 9 +++++++-- 1 file changed, 7 insertions(+), 2 deletions(-) diff --git a/compiler/iface/IfaceType.lhs b/compiler/iface/IfaceType.lhs index 8c1791a..e4a789f 100644 --- a/compiler/iface/IfaceType.lhs +++ b/compiler/iface/IfaceType.lhs @@ -31,6 +31,8 @@ module IfaceType ( ) where import Coercion +import TcType +import DynFlags import TypeRep hiding( maybeParen ) import Unique( hasKey ) import TyCon @@ -248,7 +250,7 @@ ppr_ty ctxt_prec ty@(IfaceForAllTy _ _) where (tvs, theta, tau) = splitIfaceSigmaTy ty - ------------------- +------------------- -- needs to handle type contexts and coercion contexts, hence the -- generality pprIfaceForAllPart :: Outputable a => [IfaceTvBndr] -> [a] -> SDoc -> SDoc @@ -256,7 +258,10 @@ pprIfaceForAllPart tvs ctxt doc = sep [ppr_tvs, pprIfaceContextArr ctxt, doc] where ppr_tvs | null tvs = empty - | otherwise = ptext (sLit "forall") <+> pprIfaceTvBndrs tvs <> dot + | otherwise = sdocWithDynFlags $ \ dflags -> + if gopt Opt_PrintExplicitForalls dflags + then ptext (sLit "forall") <+> pprIfaceTvBndrs tvs <> dot + else empty ------------------- ppr_tc_app :: (Int -> a -> SDoc) -> Int -> IfaceTyCon -> [a] -> SDoc From git at git.haskell.org Fri Mar 14 13:35:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Mar 2014 13:35:56 +0000 (UTC) Subject: [commit: ghc] wip/T8776: Use prefix notation in pprIfaceDecl for IfaceIds (7cc79fc) Message-ID: <20140314133556.E73E32406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8776 Link : http://ghc.haskell.org/trac/ghc/changeset/7cc79fc34bd49a339e5eb4392e5c7a2a9e21b7d4/ghc >--------------------------------------------------------------- commit 7cc79fc34bd49a339e5eb4392e5c7a2a9e21b7d4 Author: Dr. ERDI Gergo Date: Fri Mar 14 21:35:30 2014 +0800 Use prefix notation in pprIfaceDecl for IfaceIds >--------------------------------------------------------------- 7cc79fc34bd49a339e5eb4392e5c7a2a9e21b7d4 compiler/iface/IfaceSyn.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/iface/IfaceSyn.lhs b/compiler/iface/IfaceSyn.lhs index 7484b37..1283b09 100644 --- a/compiler/iface/IfaceSyn.lhs +++ b/compiler/iface/IfaceSyn.lhs @@ -1047,7 +1047,7 @@ instance Outputable IfaceDecl where pprIfaceDecl :: IfaceDecl -> SDoc pprIfaceDecl (IfaceId {ifName = var, ifType = ty, ifIdDetails = details, ifIdInfo = info}) - = sep [ ppr var <+> dcolon <+> ppr ty, + = sep [ pprPrefixOcc var <+> dcolon <+> ppr ty, nest 2 (ppr details), nest 2 (ppr info) ] From git at git.haskell.org Fri Mar 14 14:22:54 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Mar 2014 14:22:54 +0000 (UTC) Subject: [commit: ghc] wip/T8776: Reinstate pretty-printing of AnIds via pprId (#8776) (ced09a6) Message-ID: <20140314142254.817AD2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8776 Link : http://ghc.haskell.org/trac/ghc/changeset/ced09a6a2923e4f49ff345d4a28ea11a3b28c4ad/ghc >--------------------------------------------------------------- commit ced09a6a2923e4f49ff345d4a28ea11a3b28c4ad Author: Dr. ERDI Gergo Date: Fri Mar 14 22:17:45 2014 +0800 Reinstate pretty-printing of AnIds via pprId (#8776) >--------------------------------------------------------------- ced09a6a2923e4f49ff345d4a28ea11a3b28c4ad compiler/main/PprTyThing.hs | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/compiler/main/PprTyThing.hs b/compiler/main/PprTyThing.hs index fb92b5a..1fd5d0c 100644 --- a/compiler/main/PprTyThing.hs +++ b/compiler/main/PprTyThing.hs @@ -104,6 +104,7 @@ pprTyThingHdr = ppr_ty_thing Nothing -- 'TyCon' tidying happening in 'tyThingToIfaceDecl'. See #8776 for details. ppr_ty_thing :: Maybe ShowSub -> TyThing -> SDoc ppr_ty_thing mss tyThing = case tyThing of + AnId id -> pprId id ATyCon tyCon -> case mss of Nothing -> pprTyConHdr tyCon Just ss -> pprTyCon ss tyCon @@ -147,6 +148,11 @@ pprClassHdr cls where (tvs, funDeps) = classTvsFds cls +pprId :: Var -> SDoc +pprId ident + = hang (ppr_bndr ident <+> dcolon) + 2 (pprTypeForUser (idType ident)) + pprTypeForUser :: Type -> SDoc -- We do two things here. -- a) We tidy the type, regardless From git at git.haskell.org Fri Mar 14 14:26:09 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Mar 2014 14:26:09 +0000 (UTC) Subject: [commit: ghc] master: Reinstate pretty-printing of AnIds via pprId (#8776) (5200369) Message-ID: <20140314142610.21A8C2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/52003696ff7a2bbf86fbfccfe29b9f146a1ea549/ghc >--------------------------------------------------------------- commit 52003696ff7a2bbf86fbfccfe29b9f146a1ea549 Author: Dr. ERDI Gergo Date: Fri Mar 14 22:17:45 2014 +0800 Reinstate pretty-printing of AnIds via pprId (#8776) >--------------------------------------------------------------- 52003696ff7a2bbf86fbfccfe29b9f146a1ea549 compiler/main/PprTyThing.hs | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/compiler/main/PprTyThing.hs b/compiler/main/PprTyThing.hs index fb92b5a..1fd5d0c 100644 --- a/compiler/main/PprTyThing.hs +++ b/compiler/main/PprTyThing.hs @@ -104,6 +104,7 @@ pprTyThingHdr = ppr_ty_thing Nothing -- 'TyCon' tidying happening in 'tyThingToIfaceDecl'. See #8776 for details. ppr_ty_thing :: Maybe ShowSub -> TyThing -> SDoc ppr_ty_thing mss tyThing = case tyThing of + AnId id -> pprId id ATyCon tyCon -> case mss of Nothing -> pprTyConHdr tyCon Just ss -> pprTyCon ss tyCon @@ -147,6 +148,11 @@ pprClassHdr cls where (tvs, funDeps) = classTvsFds cls +pprId :: Var -> SDoc +pprId ident + = hang (ppr_bndr ident <+> dcolon) + 2 (pprTypeForUser (idType ident)) + pprTypeForUser :: Type -> SDoc -- We do two things here. -- a) We tidy the type, regardless From git at git.haskell.org Fri Mar 14 14:26:12 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Mar 2014 14:26:12 +0000 (UTC) Subject: [commit: ghc] master: Honor Op_PrintExplicitForalls setting in pprIfaceForAllPart (f3eeb93) Message-ID: <20140314142612.B42212406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f3eeb93529798b80721a9801aa1bf2ea7a1de049/ghc >--------------------------------------------------------------- commit f3eeb93529798b80721a9801aa1bf2ea7a1de049 Author: Dr. ERDI Gergo Date: Fri Mar 14 19:50:15 2014 +0800 Honor Op_PrintExplicitForalls setting in pprIfaceForAllPart >--------------------------------------------------------------- f3eeb93529798b80721a9801aa1bf2ea7a1de049 compiler/iface/IfaceType.lhs | 9 +++++++-- 1 file changed, 7 insertions(+), 2 deletions(-) diff --git a/compiler/iface/IfaceType.lhs b/compiler/iface/IfaceType.lhs index 8c1791a..e4a789f 100644 --- a/compiler/iface/IfaceType.lhs +++ b/compiler/iface/IfaceType.lhs @@ -31,6 +31,8 @@ module IfaceType ( ) where import Coercion +import TcType +import DynFlags import TypeRep hiding( maybeParen ) import Unique( hasKey ) import TyCon @@ -248,7 +250,7 @@ ppr_ty ctxt_prec ty@(IfaceForAllTy _ _) where (tvs, theta, tau) = splitIfaceSigmaTy ty - ------------------- +------------------- -- needs to handle type contexts and coercion contexts, hence the -- generality pprIfaceForAllPart :: Outputable a => [IfaceTvBndr] -> [a] -> SDoc -> SDoc @@ -256,7 +258,10 @@ pprIfaceForAllPart tvs ctxt doc = sep [ppr_tvs, pprIfaceContextArr ctxt, doc] where ppr_tvs | null tvs = empty - | otherwise = ptext (sLit "forall") <+> pprIfaceTvBndrs tvs <> dot + | otherwise = sdocWithDynFlags $ \ dflags -> + if gopt Opt_PrintExplicitForalls dflags + then ptext (sLit "forall") <+> pprIfaceTvBndrs tvs <> dot + else empty ------------------- ppr_tc_app :: (Int -> a -> SDoc) -> Int -> IfaceTyCon -> [a] -> SDoc From git at git.haskell.org Fri Mar 14 14:26:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Mar 2014 14:26:15 +0000 (UTC) Subject: [commit: ghc] master: Use prefix notation in pprIfaceDecl for IfaceIds (5908a74) Message-ID: <20140314142615.1B5F72406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5908a7427abd35264f5bafd5bf7bce3a0c9dde8e/ghc >--------------------------------------------------------------- commit 5908a7427abd35264f5bafd5bf7bce3a0c9dde8e Author: Dr. ERDI Gergo Date: Fri Mar 14 21:35:30 2014 +0800 Use prefix notation in pprIfaceDecl for IfaceIds >--------------------------------------------------------------- 5908a7427abd35264f5bafd5bf7bce3a0c9dde8e compiler/iface/IfaceSyn.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/iface/IfaceSyn.lhs b/compiler/iface/IfaceSyn.lhs index 7484b37..1283b09 100644 --- a/compiler/iface/IfaceSyn.lhs +++ b/compiler/iface/IfaceSyn.lhs @@ -1047,7 +1047,7 @@ instance Outputable IfaceDecl where pprIfaceDecl :: IfaceDecl -> SDoc pprIfaceDecl (IfaceId {ifName = var, ifType = ty, ifIdDetails = details, ifIdInfo = info}) - = sep [ ppr var <+> dcolon <+> ppr ty, + = sep [ pprPrefixOcc var <+> dcolon <+> ppr ty, nest 2 (ppr details), nest 2 (ppr info) ] From git at git.haskell.org Fri Mar 14 14:35:10 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Mar 2014 14:35:10 +0000 (UTC) Subject: [commit: ghc] master: Add test case for #8776 (de32a95) Message-ID: <20140314143510.4CA8E2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/de32a95ef21970c2db959509861b4f59d1dcbb82/ghc >--------------------------------------------------------------- commit de32a95ef21970c2db959509861b4f59d1dcbb82 Author: Dr. ERDI Gergo Date: Fri Mar 14 22:34:56 2014 +0800 Add test case for #8776 >--------------------------------------------------------------- de32a95ef21970c2db959509861b4f59d1dcbb82 testsuite/tests/ghci/scripts/T8776.hs | 6 ++++++ testsuite/tests/ghci/scripts/T8776.script | 2 ++ testsuite/tests/ghci/scripts/T8776.stdout | 1 + testsuite/tests/ghci/scripts/all.T | 2 ++ 4 files changed, 11 insertions(+) diff --git a/testsuite/tests/ghci/scripts/T8776.hs b/testsuite/tests/ghci/scripts/T8776.hs new file mode 100644 index 0000000..55e329c --- /dev/null +++ b/testsuite/tests/ghci/scripts/T8776.hs @@ -0,0 +1,6 @@ +{-# LANGUAGE PatternSynonyms, GADTs #-} +data A x y = (Num x, Eq y) => B + +data R = R{ rX :: Int } + +pattern P = B diff --git a/testsuite/tests/ghci/scripts/T8776.script b/testsuite/tests/ghci/scripts/T8776.script new file mode 100644 index 0000000..baaca9f --- /dev/null +++ b/testsuite/tests/ghci/scripts/T8776.script @@ -0,0 +1,2 @@ +:load T8776.hs +:i P diff --git a/testsuite/tests/ghci/scripts/T8776.stdout b/testsuite/tests/ghci/scripts/T8776.stdout new file mode 100644 index 0000000..9c9e89a --- /dev/null +++ b/testsuite/tests/ghci/scripts/T8776.stdout @@ -0,0 +1 @@ +pattern (Num t, Eq t1) => P :: (A t t1) -- Defined at T8776.hs:6:9 diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T index e9fe6e8..06c0716 100755 --- a/testsuite/tests/ghci/scripts/all.T +++ b/testsuite/tests/ghci/scripts/all.T @@ -166,3 +166,5 @@ test('T8579', normal, ghci_script, ['T8579.script']) test('T8649', normal, ghci_script, ['T8649.script']) test('T8674', normal, ghci_script, ['T8674.script']) test('T8696', normal, ghci_script, ['T8696.script']) +test('T8776', normal, ghci_script, ['T8776.script']) + From git at git.haskell.org Fri Mar 14 17:27:09 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Mar 2014 17:27:09 +0000 (UTC) Subject: [commit: ghc] master: Call Arity: Never eta-expand thunks in recursive groups (306d255) Message-ID: <20140314172709.EC86A2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/306d255de6c33a2430822524bc81d07ec5c1e456/ghc >--------------------------------------------------------------- commit 306d255de6c33a2430822524bc81d07ec5c1e456 Author: Joachim Breitner Date: Fri Mar 14 18:25:07 2014 +0100 Call Arity: Never eta-expand thunks in recursive groups Even if the recursion is a nice tail-call only recusion, we'd stil be calling the thunk multiple times and eta-expansion would be wrong. Includes a [Note]. (Also shows the disadvantage of unit tests: They had the same bug.) >--------------------------------------------------------------- 306d255de6c33a2430822524bc81d07ec5c1e456 compiler/simplCore/CallArity.hs | 73 +++++++++++++------- testsuite/tests/callarity/unittest/CallArity1.hs | 15 +--- .../tests/callarity/unittest/CallArity1.stderr | 16 +---- 3 files changed, 51 insertions(+), 53 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 306d255de6c33a2430822524bc81d07ec5c1e456 From git at git.haskell.org Fri Mar 14 18:17:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Mar 2014 18:17:19 +0000 (UTC) Subject: [commit: ghc] master: Call Arity test case: Check what happens with unboxed lets (aab6b9b) Message-ID: <20140314181719.82B522406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/aab6b9bdc00dee375feb0b52907ba01bade607fa/ghc >--------------------------------------------------------------- commit aab6b9bdc00dee375feb0b52907ba01bade607fa Author: Joachim Breitner Date: Fri Mar 14 19:16:58 2014 +0100 Call Arity test case: Check what happens with unboxed lets >--------------------------------------------------------------- aab6b9bdc00dee375feb0b52907ba01bade607fa .../should_run}/Makefile | 0 testsuite/tests/callarity/should_run/StrictLet.hs | 32 ++++++++++++++++++++ .../tests/callarity/should_run/StrictLet.stderr | 1 + testsuite/tests/callarity/should_run/all.T | 1 + 4 files changed, 34 insertions(+) diff --git a/testsuite/tests/annotations/should_compile/Makefile b/testsuite/tests/callarity/should_run/Makefile similarity index 100% copy from testsuite/tests/annotations/should_compile/Makefile copy to testsuite/tests/callarity/should_run/Makefile diff --git a/testsuite/tests/callarity/should_run/StrictLet.hs b/testsuite/tests/callarity/should_run/StrictLet.hs new file mode 100644 index 0000000..bae0183 --- /dev/null +++ b/testsuite/tests/callarity/should_run/StrictLet.hs @@ -0,0 +1,32 @@ +{-# LANGUAGE MagicHash #-} + +{- +If the (unboxed, hence strict) "let thunk =" would survive to the CallArity +stage, it might yield wrong results (eta-expanding thunk and hence "cond" would +be called multiple times). + +It does not actually happen (CallArity sees a "case"), so this test just +safe-guards against future changes here. +-} + +import Debug.Trace +import GHC.Exts +import System.Environment + +cond :: Int# -> Bool +cond x = trace ("cond called with " ++ show (I# x)) True +{-# NOINLINE cond #-} + + +bar (I# x) = + let go n = let x = thunk n + in case n of + 100# -> I# x + _ -> go (n +# 1#) + in go x + where thunk = if cond x then \x -> (x +# 1#) else \x -> (x -# 1#) + + +main = do + args <- getArgs + bar (length args) `seq` return () diff --git a/testsuite/tests/callarity/should_run/StrictLet.stderr b/testsuite/tests/callarity/should_run/StrictLet.stderr new file mode 100644 index 0000000..4387bc0 --- /dev/null +++ b/testsuite/tests/callarity/should_run/StrictLet.stderr @@ -0,0 +1 @@ +cond called with 0 diff --git a/testsuite/tests/callarity/should_run/all.T b/testsuite/tests/callarity/should_run/all.T new file mode 100644 index 0000000..571448c --- /dev/null +++ b/testsuite/tests/callarity/should_run/all.T @@ -0,0 +1 @@ +test('StrictLet', [], compile_and_run, ['']) From git at git.haskell.org Fri Mar 14 19:04:34 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 14 Mar 2014 19:04:34 +0000 (UTC) Subject: [commit: ghc] master: Remove code reporting issues with Safe Haskell and coerce. (7602bd4) Message-ID: <20140314190434.8D68C2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7602bd4de901e4304a3a45dca08fc630d1bb5bf2/ghc >--------------------------------------------------------------- commit 7602bd4de901e4304a3a45dca08fc630d1bb5bf2 Author: Richard Eisenberg Date: Fri Mar 14 15:03:21 2014 -0400 Remove code reporting issues with Safe Haskell and coerce. This is a followup to the fix for #8827, and should be merged with that change. >--------------------------------------------------------------- 7602bd4de901e4304a3a45dca08fc630d1bb5bf2 compiler/typecheck/TcErrors.lhs | 24 ++++-------------------- 1 file changed, 4 insertions(+), 20 deletions(-) diff --git a/compiler/typecheck/TcErrors.lhs b/compiler/typecheck/TcErrors.lhs index 4b1bc68..df241c9 100644 --- a/compiler/typecheck/TcErrors.lhs +++ b/compiler/typecheck/TcErrors.lhs @@ -996,9 +996,8 @@ mk_dict_err ctxt (ct, (matches, unifiers, safe_haskell)) = do { let (is_ambig, ambig_msg) = mkAmbigMsg ct ; (ctxt, binds_msg) <- relevantBindings True ctxt ct ; traceTc "mk_dict_err" (ppr ct $$ ppr is_ambig $$ ambig_msg) - ; safe_mod <- safeLanguageOn `fmap` getDynFlags ; rdr_env <- getGlobalRdrEnv - ; return (ctxt, cannot_resolve_msg safe_mod rdr_env is_ambig binds_msg ambig_msg) } + ; return (ctxt, cannot_resolve_msg rdr_env is_ambig binds_msg ambig_msg) } | not safe_haskell -- Some matches => overlap errors = return (ctxt, overlap_msg) @@ -1013,8 +1012,8 @@ mk_dict_err ctxt (ct, (matches, unifiers, safe_haskell)) givens = getUserGivens ctxt all_tyvars = all isTyVarTy tys - cannot_resolve_msg safe_mod rdr_env has_ambig_tvs binds_msg ambig_msg - = vcat [ addArising orig (no_inst_msg $$ coercible_explanation safe_mod rdr_env) + cannot_resolve_msg rdr_env has_ambig_tvs binds_msg ambig_msg + = vcat [ addArising orig (no_inst_msg $$ coercible_explanation rdr_env) , vcat (pp_givens givens) , ppWhen (has_ambig_tvs && not (null unifiers && null givens)) (vcat [ ambig_msg, binds_msg, potential_msg ]) @@ -1139,27 +1138,12 @@ mk_dict_err ctxt (ct, (matches, unifiers, safe_haskell)) -- This function tries to reconstruct why a "Coercible ty1 ty2" constraint -- is left over. Therefore its logic has to stay in sync with -- getCoericbleInst in TcInteract. See Note [Coercible Instances] - coercible_explanation safe_mod rdr_env + coercible_explanation rdr_env | clas /= coercibleClass = empty | Just (tc1,tyArgs1) <- splitTyConApp_maybe ty1, Just (tc2,tyArgs2) <- splitTyConApp_maybe ty2, tc1 == tc2 = nest 2 $ vcat $ - -- Only for safe haskell: First complain if tc is abstract, only if - -- not check if the type constructors therein are abstract - (if safe_mod - then case tyConAbstractMsg rdr_env tc1 empty of - Just msg -> - [ msg $$ ptext (sLit "as required in SafeHaskell mode") ] - Nothing -> - [ msg - | tc <- tyConsOfTyCon tc1 - , Just msg <- return $ - tyConAbstractMsg rdr_env tc $ - parens $ ptext (sLit "used within") <+> quotes (ppr tc1) - ] - else [] - ) ++ [ fsep [ hsep [ ptext $ sLit "because the", speakNth n, ptext $ sLit "type argument"] , hsep [ ptext $ sLit "of", quotes (ppr tc1), ptext $ sLit "has role Nominal,"] , ptext $ sLit "but the arguments" From git at git.haskell.org Sat Mar 15 08:04:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 15 Mar 2014 08:04:47 +0000 (UTC) Subject: [commit: haddock] master: Add Fuuzetsu maintainers field in cabal file (76bafc9) Message-ID: <20140315080447.334562406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : master Link : http://git.haskell.org/haddock.git/commitdiff/76bafc9e873ea0a75c2ad40b74310cecad89e245 >--------------------------------------------------------------- commit 76bafc9e873ea0a75c2ad40b74310cecad89e245 Author: Simon Hengel Date: Sat Mar 15 09:02:47 2014 +0100 Add Fuuzetsu maintainers field in cabal file >--------------------------------------------------------------- 76bafc9e873ea0a75c2ad40b74310cecad89e245 haddock.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/haddock.cabal b/haddock.cabal index 7b852a9..0df89be 100644 --- a/haddock.cabal +++ b/haddock.cabal @@ -6,7 +6,7 @@ description: Haddock is a documentation-generation tool for Haskell license: BSD3 license-file: LICENSE author: Simon Marlow, David Waern -maintainer: Simon Hengel +maintainer: Simon Hengel , Mateusz Kowalczyk homepage: http://www.haskell.org/haddock/ bug-reports: http://trac.haskell.org/haddock copyright: (c) Simon Marlow, David Waern From git at git.haskell.org Sat Mar 15 08:47:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 15 Mar 2014 08:47:52 +0000 (UTC) Subject: [commit: haddock] tag 'haddock-2.15-start' created Message-ID: <20140315084752.195942406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock New tag : haddock-2.15-start Referencing: bc784d2732c07db9b1bed4c31d492a84465e566c From git at git.haskell.org Sat Mar 15 08:58:51 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 15 Mar 2014 08:58:51 +0000 (UTC) Subject: [commit: haddock] v2.14: Add Fuuzetsu maintainers field in cabal file (620e062) Message-ID: <20140315085851.86EE52406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : v2.14 Link : http://git.haskell.org/haddock.git/commitdiff/620e062c812740ed10eb018da61476c12d8026bf >--------------------------------------------------------------- commit 620e062c812740ed10eb018da61476c12d8026bf Author: Simon Hengel Date: Sat Mar 15 09:02:47 2014 +0100 Add Fuuzetsu maintainers field in cabal file >--------------------------------------------------------------- 620e062c812740ed10eb018da61476c12d8026bf haddock.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/haddock.cabal b/haddock.cabal index 0cd6747..84e5b9d 100644 --- a/haddock.cabal +++ b/haddock.cabal @@ -6,7 +6,7 @@ description: Haddock is a documentation-generation tool for Haskell license: BSD3 license-file: LICENSE author: Simon Marlow, David Waern -maintainer: Simon Hengel +maintainer: Simon Hengel , Mateusz Kowalczyk homepage: http://www.haskell.org/haddock/ bug-reports: http://trac.haskell.org/haddock copyright: (c) Simon Marlow, David Waern From git at git.haskell.org Sat Mar 15 16:18:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 15 Mar 2014 16:18:56 +0000 (UTC) Subject: [commit: nofib] master: nofib-analyse: Support comparing multiple runs in the summary table (a557442) Message-ID: <20140315161856.47CA52406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/nofib On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a557442ee381d8225d30b82245acaf5eeba917be/nofib >--------------------------------------------------------------- commit a557442ee381d8225d30b82245acaf5eeba917be Author: Joachim Breitner Date: Fri Mar 14 23:09:31 2014 +0100 nofib-analyse: Support comparing multiple runs in the summary table and adjust the table layout to have at least one space padding, even with long input file names. >--------------------------------------------------------------- a557442ee381d8225d30b82245acaf5eeba917be nofib-analyse/Main.hs | 61 +++++++++++++++++++++++++++++------------------- nofib-analyse/Makefile | 2 +- 2 files changed, 38 insertions(+), 25 deletions(-) diff --git a/nofib-analyse/Main.hs b/nofib-analyse/Main.hs index fa78ebe..ad043f5 100644 --- a/nofib-analyse/Main.hs +++ b/nofib-analyse/Main.hs @@ -216,7 +216,7 @@ per_prog_result_tab = gcwork_spec, balance_spec, instrs_spec, mreads_spec, mwrite_spec, cmiss_spec, totmem_spec] -- A single summary table, giving comparison figures for a number of --- aspects, each in its own column. Only works when comparing two runs. +-- aspects, each in its own column. Only works when comparing at least two runs. normal_summary_specs :: [PerProgTableSpec] normal_summary_specs = [ size_spec, alloc_spec, runtime_spec, elapsedtime_spec, totmem_spec ] @@ -437,9 +437,9 @@ latexOutput results (Just table_name) _ _ _ norm inc_baseline [] -> error ("can't find table named: " ++ table_name) (spec:_) -> latexProgTable results spec norm inc_baseline "\n" -latexOutput results Nothing _ summary_spec summary_rows _ _ = - (if (length results == 2) - then ascii_summary_table True results summary_spec summary_rows +latexOutput results Nothing column_headings summary_spec summary_rows _ _ = + (if (length results >= 2) + then ascii_summary_table True results column_headings summary_spec summary_rows . str "\n\n" else id) "" @@ -494,9 +494,9 @@ asciiPage :: [ResultTable] -> [String] -> [PerProgTableSpec] -> Maybe [String] asciiPage results args summary_spec summary_rows norm = ( str reportTitle . str "\n\n" - -- only show the summary table if we're comparing two runs - . (if (length results == 2) - then ascii_summary_table False results summary_spec summary_rows . str "\n\n" + -- only show the summary table if we're comparing at least two runs + . (if (length results >= 2) + then ascii_summary_table False results args summary_spec summary_rows . str "\n\n" else id) . interleave "\n\n" (map (asciiGenProgTable results args norm) per_prog_result_tab) . str "\n" @@ -520,7 +520,7 @@ ascii_header w ss = str "\n-------------------------------------------------------------------------------\n" . str (rjustify 15 "Program") . str (space 5) - . foldr (.) id (map (str . rjustify w) ss) + . foldr (.) id (intersperse (str (space 1)) (map (str . rjustify w) ss)) . str "\n-------------------------------------------------------------------------------\n" ascii_show_results @@ -557,27 +557,33 @@ ascii_show_results (r:rs) ss f stat result_ok norm ascii_summary_table :: Bool -- generate a LaTeX table? -> [ResultTable] + -> [String] -> [PerProgTableSpec] -> Maybe [String] -> ShowS -ascii_summary_table _ [] _ _ +ascii_summary_table _ [] _ _ _ = error "ascii_summary_table: Can't happen?" -ascii_summary_table _ [_] _ _ +ascii_summary_table _ [_] _ _ _ = error "ascii_summary_table: Can't happen?" -ascii_summary_table latex (r1:r2:_) specs mb_restrict +ascii_summary_table latex (rbase:rs) (_:names) specs mb_restrict | latex = makeLatexTable (rows ++ TableLine : av_rows) | otherwise = - makeTable (table_layout (length specs) w) - (TableLine : TableRow header_row : - TableLine : rows ++ - TableLine : av_rows) + makeTable (table_layout (length specs * length rs) w) $ + [ TableLine + , TableRow header_row ] ++ + [ TableRow header_row2 | length rs > 1] ++ + [ TableLine ] ++ + rows ++ + [ TableLine ] ++ + av_rows where header_row = BoxString "Program" : map BoxString headings + header_row2 = BoxString "" : map BoxString headings2 - (headings, columns, av_cols) = unzip3 (map calc_col specs) + (headings, headings2, columns, av_cols) = unzip4 (concatMap calc_col_group specs) av_heads = [BoxString "Min", BoxString "Max", BoxString "Geometric Mean"] - baseline = Map.toList r1 - progs = map BoxString (Map.keys r1) + baseline = Map.toList rbase + progs = map BoxString (Map.keys rbase) rows0 = map TableRow (zipWith (:) progs (transpose columns)) rows1 = restrictRows mb_restrict rows0 @@ -586,13 +592,17 @@ ascii_summary_table latex (r1:r2:_) specs mb_restrict | otherwise = rows1 av_rows = map TableRow (zipWith (:) av_heads (transpose av_cols)) - w = 10 + w = sUMMARY_FIELD_WIDTH + + calc_col_group :: PerProgTableSpec -> [(String, String, [BoxValue], [BoxValue])] + calc_col_group spec = [calc_col spec r n | (r,n) <- zip rs names] - calc_col (SpecP _ heading _ getr gets ok) + calc_col :: PerProgTableSpec -> ResultTable -> String -> (String, String, [BoxValue], [BoxValue]) + calc_col (SpecP _ heading _ getr gets ok) r n -- throw away the baseline result - = (heading, column, [column_min, column_max, column_mean]) + = (heading, n, column, [column_min, column_max, column_mean]) where (_, boxes) = unzip (map calc_one_result baseline) - calc_one_result = calc_result [r2] getr gets ok convert_to_percentage + calc_one_result = calc_result [r] getr gets ok convert_to_percentage column = map (\(_:b:_) -> b) boxes (_, column_mean, _) = calc_gmsd column (column_min, column_max) = calc_minmax column @@ -617,7 +627,7 @@ mungeForLaTeX = map transrow transchar c s = c:s table_layout :: Int -> Int -> Layout -table_layout n w boxes = foldr (.) id $ zipWith ($) fns boxes +table_layout n w boxes = foldr (.) id $ intersperse (str (space 1)) $ zipWith ($) fns boxes where fns = (str . rjustify 15 . show ) : (\s -> str (space 5) . str (rjustify w (show s))) : replicate (n-1) (str . rjustify w . show) @@ -681,7 +691,7 @@ show_per_prog_results_width :: Int -> (String, [BoxValue]) -> ShowS show_per_prog_results_width w (prog,results) = str (rjustify 15 prog) . str (space 5) - . foldr (.) id (map (str . rjustify w . showBox) results) + . foldr (.) id (intersperse (str (space 1)) (map (str . rjustify w . showBox) results)) -- ----------------------------------------------------------------------------- -- CSV output @@ -963,4 +973,7 @@ interleave s = foldr1 (\a b -> a . str s . b) fIELD_WIDTH :: Int fIELD_WIDTH = 16 +sUMMARY_FIELD_WIDTH :: Int +sUMMARY_FIELD_WIDTH = 9 + ----------------------------------------------------------------------------- diff --git a/nofib-analyse/Makefile b/nofib-analyse/Makefile index 6fbd622..5691121 100644 --- a/nofib-analyse/Makefile +++ b/nofib-analyse/Makefile @@ -3,7 +3,7 @@ include $(TOP)/mk/boilerplate.mk PROG = nofib-analyse -$(PROG): +$(PROG): *.hs $(BOOT_HC) -O -cpp --make Main -o $(PROG) all :: $(PROG) From git at git.haskell.org Sat Mar 15 16:18:58 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 15 Mar 2014 16:18:58 +0000 (UTC) Subject: [commit: nofib] master: nofib-analyize: Include % in LaTeX output (d224bbb) Message-ID: <20140315161858.3A8FE2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/nofib On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d224bbb3576f57923be1685c903c7bdbf9b34be3/nofib >--------------------------------------------------------------- commit d224bbb3576f57923be1685c903c7bdbf9b34be3 Author: Joachim Breitner Date: Sat Mar 15 16:36:14 2014 +0100 nofib-analyize: Include % in LaTeX output I see no reason why this should be different from the text output, especially as it is important to distinguish absolute from relative values in the runtime column. It is also easier to remove the % (using search-and-replace) than to add it. >--------------------------------------------------------------- d224bbb3576f57923be1685c903c7bdbf9b34be3 nofib-analyse/Main.hs | 27 ++++++++------------------- 1 file changed, 8 insertions(+), 19 deletions(-) diff --git a/nofib-analyse/Main.hs b/nofib-analyse/Main.hs index ad043f5..a1340d9 100644 --- a/nofib-analyse/Main.hs +++ b/nofib-analyse/Main.hs @@ -586,10 +586,7 @@ ascii_summary_table latex (rbase:rs) (_:names) specs mb_restrict progs = map BoxString (Map.keys rbase) rows0 = map TableRow (zipWith (:) progs (transpose columns)) - rows1 = restrictRows mb_restrict rows0 - - rows | latex = mungeForLaTeX rows1 - | otherwise = rows1 + rows = restrictRows mb_restrict rows0 av_rows = map TableRow (zipWith (:) av_heads (transpose av_cols)) w = sUMMARY_FIELD_WIDTH @@ -614,18 +611,6 @@ restrictRows (Just these) rows = filter keep_it rows keep_it TableLine = True keep_it _ = False -mungeForLaTeX :: [TableRow] -> [TableRow] -mungeForLaTeX = map transrow - where - transrow (TableRow boxes) = TableRow (map transbox boxes) - transrow row = row - - transbox (BoxString s) = BoxString (foldr transchar "" s) - transbox box = box - - transchar '_' s = '\\':'_':s - transchar c s = c:s - table_layout :: Int -> Int -> Layout table_layout n w boxes = foldr (.) id $ intersperse (str (space 1)) $ zipWith ($) fns boxes where fns = (str . rjustify 15 . show ) : @@ -949,10 +934,14 @@ latexTableLayout boxes = foldr (.) id . intersperse (str " & ") . map abox $ boxes where abox (RunFailed NotDone) = id - abox s = str (foldr transchar "" (show s)) + abox s = str (mungeForLaTeX (show s)) - transchar '%' s = s -- leave out the percentage signs - transchar c s = c : s +mungeForLaTeX :: String -> String +mungeForLaTeX = foldr transchar "" + where + transchar '_' s = '\\':'_':s + transchar '%' s = '\\':'%':s + transchar c s = c:s -- ----------------------------------------------------------------------------- -- General Utils From git at git.haskell.org Sat Mar 15 18:24:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 15 Mar 2014 18:24:52 +0000 (UTC) Subject: [commit: haddock] master: Hide minimal definition for only-method classes (48f4567) Message-ID: <20140315182453.634DB2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : master Link : http://git.haskell.org/haddock.git/commitdiff/48f45676f7c6c79b249b51dde9a6791393860676 >--------------------------------------------------------------- commit 48f45676f7c6c79b249b51dde9a6791393860676 Author: Niklas Haas Date: Sat Mar 15 15:15:44 2014 +0100 Hide minimal definition for only-method classes Previously this was not covered by the All xs check since here it is not actually an All, rather a single Var n. This also adds the previously missing html-test/src/Minimal.hs. >--------------------------------------------------------------- 48f45676f7c6c79b249b51dde9a6791393860676 html-test/ref/DeprecatedClass.html | 16 --------------- html-test/ref/Hash.html | 8 -------- html-test/ref/Test.html | 8 -------- html-test/ref/Ticket61.html | 8 -------- html-test/src/Minimal.hs | 40 ++++++++++++++++++++++++++++++++++++ src/Haddock/Backends/Xhtml/Decl.hs | 7 ++++++- 6 files changed, 46 insertions(+), 41 deletions(-) diff --git a/html-test/ref/DeprecatedClass.html b/html-test/ref/DeprecatedClass.html index 76c0c17..c8799bf 100644 --- a/html-test/ref/DeprecatedClass.html +++ b/html-test/ref/DeprecatedClass.html @@ -95,14 +95,6 @@ window.onload = function () {pageLoad();setSynopsis("mini_DeprecatedClass.html") >

    some class

    Minimal complete definition

    foo

    Methods

    Deprecated: SomeOtherClass

    Minimal complete definition

    bar

    Methods

    A class of types which can be hashed.

    Minimal complete definition

    hash

    Methods

    a where

    Minimal complete definition

    ff

    Methods

    a where

    Minimal complete definition

    f

    Methods

    noHtml + -- Minimal complete definition = the only shown method + Var (L _ n) : _ | [getName n] == + [getName n' | L _ (TypeSig ns _) <- lsigs, L _ n' <- ns] + -> noHtml + -- Minimal complete definition = nothing And [] : _ -> subMinimal $ toHtml "Nothing" From git at git.haskell.org Sat Mar 15 18:24:54 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 15 Mar 2014 18:24:54 +0000 (UTC) Subject: [commit: haddock] master: Fix issue #281 (82ab2c0) Message-ID: <20140315182454.29A912406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : master Link : http://git.haskell.org/haddock.git/commitdiff/82ab2c09c19641e0ea89965c9af291043798486d >--------------------------------------------------------------- commit 82ab2c09c19641e0ea89965c9af291043798486d Author: Niklas Haas Date: Sat Mar 15 15:17:18 2014 +0100 Fix issue #281 This is a regression from the data family instances change. Data instances are now distinguished from regular lists by usage of the new class "inst", and the style has been updated to only apply to those. I've also updated the appropriate test case to test this a bit better, including GADT instances with GADT-style records. >--------------------------------------------------------------- 82ab2c09c19641e0ea89965c9af291043798486d html-test/ref/TypeFamilies.html | 304 ++++++++++++++++++++++-------- html-test/src/TypeFamilies.hs | 16 +- resources/html/Ocean.std-theme/ocean.css | 7 +- src/Haddock/Backends/Xhtml/Decl.hs | 16 +- src/Haddock/Backends/Xhtml/Layout.hs | 8 +- 5 files changed, 251 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 82ab2c09c19641e0ea89965c9af291043798486d From git at git.haskell.org Sat Mar 15 18:25:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 15 Mar 2014 18:25:15 +0000 (UTC) Subject: [commit: haddock] v2.14: Hide minimal definition for only-method classes (cac5384) Message-ID: <20140315182515.DC4EB2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : v2.14 Link : http://git.haskell.org/haddock.git/commitdiff/cac5384ccd77630fa0e00633bc14f67c306bca24 >--------------------------------------------------------------- commit cac5384ccd77630fa0e00633bc14f67c306bca24 Author: Niklas Haas Date: Sat Mar 15 15:15:44 2014 +0100 Hide minimal definition for only-method classes Previously this was not covered by the All xs check since here it is not actually an All, rather a single Var n. This also adds the previously missing html-test/src/Minimal.hs. >--------------------------------------------------------------- cac5384ccd77630fa0e00633bc14f67c306bca24 html-test/ref/DeprecatedClass.html | 16 --------------- html-test/ref/Hash.html | 8 -------- html-test/ref/Test.html | 8 -------- html-test/ref/Ticket61.html | 8 -------- html-test/src/Minimal.hs | 40 ++++++++++++++++++++++++++++++++++++ src/Haddock/Backends/Xhtml/Decl.hs | 7 ++++++- 6 files changed, 46 insertions(+), 41 deletions(-) diff --git a/html-test/ref/DeprecatedClass.html b/html-test/ref/DeprecatedClass.html index 162e421..66f3b93 100644 --- a/html-test/ref/DeprecatedClass.html +++ b/html-test/ref/DeprecatedClass.html @@ -95,14 +95,6 @@ window.onload = function () {pageLoad();setSynopsis("mini_DeprecatedClass.html") >

    some class

    Minimal complete definition

    foo

    Methods

    Deprecated: SomeOtherClass

    Minimal complete definition

    bar

    Methods

    A class of types which can be hashed.

    Minimal complete definition

    hash

    Methods

    a where

    Minimal complete definition

    ff

    Methods

    a where

    Minimal complete definition

    f

    Methods

    noHtml + -- Minimal complete definition = the only shown method + Var (L _ n) : _ | [getName n] == + [getName n' | L _ (TypeSig ns _) <- lsigs, L _ n' <- ns] + -> noHtml + -- Minimal complete definition = nothing And [] : _ -> subMinimal $ toHtml "Nothing" From git at git.haskell.org Sat Mar 15 18:25:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 15 Mar 2014 18:25:17 +0000 (UTC) Subject: [commit: haddock] v2.14: Fix issue #281 (40d2b41) Message-ID: <20140315182517.E03F92406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : v2.14 Link : http://git.haskell.org/haddock.git/commitdiff/40d2b4190c541ec7bb6a92e7c75cff02ef01d82b >--------------------------------------------------------------- commit 40d2b4190c541ec7bb6a92e7c75cff02ef01d82b Author: Niklas Haas Date: Sat Mar 15 15:17:18 2014 +0100 Fix issue #281 This is a regression from the data family instances change. Data instances are now distinguished from regular lists by usage of the new class "inst", and the style has been updated to only apply to those. I've also updated the appropriate test case to test this a bit better, including GADT instances with GADT-style records. >--------------------------------------------------------------- 40d2b4190c541ec7bb6a92e7c75cff02ef01d82b html-test/ref/TypeFamilies.html | 304 ++++++++++++++++++++++-------- html-test/src/TypeFamilies.hs | 16 +- resources/html/Ocean.std-theme/ocean.css | 7 +- src/Haddock/Backends/Xhtml/Decl.hs | 16 +- src/Haddock/Backends/Xhtml/Layout.hs | 8 +- 5 files changed, 251 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 40d2b4190c541ec7bb6a92e7c75cff02ef01d82b From git at git.haskell.org Sun Mar 16 16:13:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 16 Mar 2014 16:13:43 +0000 (UTC) Subject: [commit: ghc] branch 'ghc-head' created Message-ID: <20140316161343.DF1D12406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : ghc-head Referencing: 014223745186fc0ca6afb9938227df9ce7d28b38 From git at git.haskell.org Sun Mar 16 16:13:46 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 16 Mar 2014 16:13:46 +0000 (UTC) Subject: [commit: ghc] master, master: Test case: :info Coercible in GHCi (0142237) Message-ID: <20140316161346.9BD5C2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branches: master,master Link : http://ghc.haskell.org/trac/ghc/changeset/014223745186fc0ca6afb9938227df9ce7d28b38/ghc >--------------------------------------------------------------- commit 014223745186fc0ca6afb9938227df9ce7d28b38 Author: Joachim Breitner Date: Sun Mar 16 17:12:58 2014 +0100 Test case: :info Coercible in GHCi This prepares against future breakage, especially if #8894 is tackled. >--------------------------------------------------------------- 014223745186fc0ca6afb9938227df9ce7d28b38 testsuite/tests/ghci/scripts/all.T | 1 + testsuite/tests/ghci/scripts/ghci059.script | 6 ++++++ 2 files changed, 7 insertions(+) diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T index 06c0716..6812c9d 100755 --- a/testsuite/tests/ghci/scripts/all.T +++ b/testsuite/tests/ghci/scripts/all.T @@ -167,4 +167,5 @@ test('T8649', normal, ghci_script, ['T8649.script']) test('T8674', normal, ghci_script, ['T8674.script']) test('T8696', normal, ghci_script, ['T8696.script']) test('T8776', normal, ghci_script, ['T8776.script']) +test('ghci059', normal, ghci_script, ['ghci059.script']) diff --git a/testsuite/tests/ghci/scripts/ghci059.script b/testsuite/tests/ghci/scripts/ghci059.script new file mode 100644 index 0000000..a78be19 --- /dev/null +++ b/testsuite/tests/ghci/scripts/ghci059.script @@ -0,0 +1,6 @@ +# At one point, :info Coercible would not report it as a constraint, but as a +# data type. So this test case ensures that this is broken later. + +:m + Data.Coerce +:info Coercible +:info coerce From git at git.haskell.org Sun Mar 16 16:41:27 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 16 Mar 2014 16:41:27 +0000 (UTC) Subject: [commit: ghc] master, master: Fix comment for ghci script files (db497cd) Message-ID: <20140316164127.6C9902406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branches: master,master Link : http://ghc.haskell.org/trac/ghc/changeset/db497cd1bef818e5b2ae3028a48538f2cba95157/ghc >--------------------------------------------------------------- commit db497cd1bef818e5b2ae3028a48538f2cba95157 Author: Joachim Breitner Date: Sun Mar 16 17:40:51 2014 +0100 Fix comment for ghci script files (Unchecked comment-only commits should better use the right commenting style...) >--------------------------------------------------------------- db497cd1bef818e5b2ae3028a48538f2cba95157 testsuite/tests/ghci/scripts/ghci059.script | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/ghci/scripts/ghci059.script b/testsuite/tests/ghci/scripts/ghci059.script index a78be19..936277e 100644 --- a/testsuite/tests/ghci/scripts/ghci059.script +++ b/testsuite/tests/ghci/scripts/ghci059.script @@ -1,5 +1,5 @@ -# At one point, :info Coercible would not report it as a constraint, but as a -# data type. So this test case ensures that this is broken later. +-- At one point, :info Coercible would not report it as a constraint, but as a +-- data type. So this test case ensures that this is broken later. :m + Data.Coerce :info Coercible From git at git.haskell.org Sun Mar 16 17:54:08 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 16 Mar 2014 17:54:08 +0000 (UTC) Subject: [commit: packages/base] master: Import Coercible from GHC.Types (172dc4b) Message-ID: <20140316175409.C76542406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/base On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/172dc4b451579512024eb6d8d70da1671b32e05b/base >--------------------------------------------------------------- commit 172dc4b451579512024eb6d8d70da1671b32e05b Author: Joachim Breitner Date: Sun Mar 16 18:35:00 2014 +0100 Import Coercible from GHC.Types >--------------------------------------------------------------- 172dc4b451579512024eb6d8d70da1671b32e05b Data/Coerce.hs | 3 ++- Data/Data.hs | 2 +- GHC/Exts.hs | 4 ++-- 3 files changed, 5 insertions(+), 4 deletions(-) diff --git a/Data/Coerce.hs b/Data/Coerce.hs index 2065159..b00144b 100644 --- a/Data/Coerce.hs +++ b/Data/Coerce.hs @@ -24,4 +24,5 @@ module Data.Coerce ( -- * Safe coercions coerce, Coercible, ) where -import GHC.Prim (coerce, Coercible) +import GHC.Prim (coerce) +import GHC.Types (Coercible) diff --git a/Data/Data.hs b/Data/Data.hs index 24f72d4..a12a6d7 100644 --- a/Data/Data.hs +++ b/Data/Data.hs @@ -116,10 +116,10 @@ import Control.Monad -- Imports for the instances import Data.Int -- So we can give Data instance for Int8, ... import Data.Type.Coercion +import Data.Coerce import Data.Word -- So we can give Data instance for Word8, ... import GHC.Real( Ratio(..) ) -- So we can give Data instance for Ratio --import GHC.IOBase -- So we can give Data instance for IO, Handle -import GHC.Prim import GHC.Ptr -- So we can give Data instance for Ptr import GHC.ForeignPtr -- So we can give Data instance for ForeignPtr --import GHC.Stable -- So we can give Data instance for StablePtr diff --git a/GHC/Exts.hs b/GHC/Exts.hs index efdf868..05e7281 100755 --- a/GHC/Exts.hs +++ b/GHC/Exts.hs @@ -73,8 +73,8 @@ module GHC.Exts import Prelude -import GHC.Prim hiding (coerce, Coercible) -import GHC.Base hiding (coerce, Coercible) -- implicitly comes from GHC.Prim +import GHC.Prim hiding (coerce) +import GHC.Base hiding (coerce) -- implicitly comes from GHC.Prim import GHC.Word import GHC.Int import GHC.Ptr From git at git.haskell.org Sun Mar 16 17:54:16 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 16 Mar 2014 17:54:16 +0000 (UTC) Subject: [commit: packages/ghc-prim] master: Export Coercible in GHC.Types (#8894) (aea32bc) Message-ID: <20140316175416.B9D6E2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc-prim On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/aea32bc5ca0511b79136b9a7294022ef708d8d3c/ghc-prim >--------------------------------------------------------------- commit aea32bc5ca0511b79136b9a7294022ef708d8d3c Author: Joachim Breitner Date: Sun Mar 16 18:34:46 2014 +0100 Export Coercible in GHC.Types (#8894) >--------------------------------------------------------------- aea32bc5ca0511b79136b9a7294022ef708d8d3c GHC/Types.hs | 22 ++++------------------ 1 file changed, 4 insertions(+), 18 deletions(-) diff --git a/GHC/Types.hs b/GHC/Types.hs index a144657..44351d8 100644 --- a/GHC/Types.hs +++ b/GHC/Types.hs @@ -20,7 +20,8 @@ module GHC.Types ( Float(..), Double(..), Ordering(..), IO(..), isTrue#, - SPEC(..) + SPEC(..), + Coercible, ) where import GHC.Prim @@ -93,23 +94,8 @@ for them, e.g. to compile the constructor's info table. Furthermore the type of MkCoercible cannot be written in Haskell (no syntax for ~#R). -So we define them as regular data types in GHC.Types, but do /not/ export them. -This ensures we have a home module. We then define them with the types and -kinds that we actually want, in TysWiredIn. - -We also export coercibleTyCon in PrelInfo's ghcPrimExports. -(This is not needed for (~), as that is not importable and handled specially by -the parser). -Why not export it in GHC.Types? Because then ghci and haddock would, for some -reason, display it as a data type, and not as a constraint. - -Haddock still takes the documentation from GHC.Types (and not from the fake -module created from primops.txt.pp), so we have the user-facing documentation -here. - -(This this note merely documents what is implemented because it happens to -work, and should not be taken as an indication of good design. Cleanup is -appreciated). +So we define them as regular data types in GHC.Types, and do magic in GHC to +change the kind and type, in tysWiredIn. -} From git at git.haskell.org Sun Mar 16 17:54:35 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 16 Mar 2014 17:54:35 +0000 (UTC) Subject: [commit: ghc] master, master: Coercible is now exported from GHC.Types (#8894) (d59170b) Message-ID: <20140316175435.42F7F2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branches: master,master Link : http://ghc.haskell.org/trac/ghc/changeset/d59170b6deaee480640889e8a7eef5a863242562/ghc >--------------------------------------------------------------- commit d59170b6deaee480640889e8a7eef5a863242562 Author: Joachim Breitner Date: Sun Mar 16 18:35:28 2014 +0100 Coercible is now exported from GHC.Types (#8894) so do not export it in GHC.Prim, and also have the pseudo-code for GHC.Prim import GHC.Types, so that haddock is happy. >--------------------------------------------------------------- d59170b6deaee480640889e8a7eef5a863242562 compiler/prelude/PrelInfo.lhs | 4 +--- compiler/prelude/primops.txt.pp | 2 -- utils/genprimopcode/Main.hs | 1 + 3 files changed, 2 insertions(+), 5 deletions(-) diff --git a/compiler/prelude/PrelInfo.lhs b/compiler/prelude/PrelInfo.lhs index ca156ee..014e0e7 100644 --- a/compiler/prelude/PrelInfo.lhs +++ b/compiler/prelude/PrelInfo.lhs @@ -124,15 +124,13 @@ primOpId op = primOpIds ! primOpTag op GHC.Prim "exports" all the primops and primitive types, some wired-in Ids. -See Note [Kind-changing of (~) and Coerciblea] for why we export coercibleTyCon here. - \begin{code} ghcPrimExports :: [IfaceExport] ghcPrimExports = map (Avail . idName) ghcPrimIds ++ map (Avail . idName . primOpId) allThePrimOps ++ [ AvailTC n [n] - | tc <- funTyCon : coercibleTyCon : primTyCons, let n = tyConName tc ] + | tc <- funTyCon : primTyCons, let n = tyConName tc ] \end{code} diff --git a/compiler/prelude/primops.txt.pp b/compiler/prelude/primops.txt.pp index 63aef0f..49fef35 100644 --- a/compiler/prelude/primops.txt.pp +++ b/compiler/prelude/primops.txt.pp @@ -2380,8 +2380,6 @@ pseudoop "coerce" concrete types. } -primclass Coercible a b - ------------------------------------------------------------------------ section "SIMD Vectors" {Operations on SIMD vectors.} diff --git a/utils/genprimopcode/Main.hs b/utils/genprimopcode/Main.hs index d60081f..05d42fa 100644 --- a/utils/genprimopcode/Main.hs +++ b/utils/genprimopcode/Main.hs @@ -252,6 +252,7 @@ gen_hs_source (Info defaults entries) = ++ "{-\n" ++ unlines (map opt defaults) ++ "-}\n" + ++ "import GHC.Types (Coercible)\n" ++ unlines (concatMap ent entries') ++ "\n\n\n" where entries' = concatMap desugarVectorSpec entries From git at git.haskell.org Sun Mar 16 17:54:38 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 16 Mar 2014 17:54:38 +0000 (UTC) Subject: [commit: ghc] master, master: Remove support for "primclass" (5d59265) Message-ID: <20140316175438.88B0A2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branches: master,master Link : http://ghc.haskell.org/trac/ghc/changeset/5d59265acf6c61840e386842c506241f9e48f1ae/ghc >--------------------------------------------------------------- commit 5d59265acf6c61840e386842c506241f9e48f1ae Author: Joachim Breitner Date: Sun Mar 16 18:39:27 2014 +0100 Remove support for "primclass" This partly reverts commit e239753c349f925b576b72dc3445934cba8bcd50. Since Coercible is exported via GHC.Types, so "primclass" is no longer needed. The support for => in primops.pp is still required for coerce. >--------------------------------------------------------------- 5d59265acf6c61840e386842c506241f9e48f1ae utils/genprimopcode/Lexer.x | 1 - utils/genprimopcode/Main.hs | 12 ------------ utils/genprimopcode/Parser.y | 6 ------ utils/genprimopcode/ParserM.hs | 1 - utils/genprimopcode/Syntax.hs | 3 --- 5 files changed, 23 deletions(-) diff --git a/utils/genprimopcode/Lexer.x b/utils/genprimopcode/Lexer.x index a796b8a..527a03f 100644 --- a/utils/genprimopcode/Lexer.x +++ b/utils/genprimopcode/Lexer.x @@ -48,7 +48,6 @@ words :- <0> "primop" { mkT TPrimop } <0> "pseudoop" { mkT TPseudoop } <0> "primtype" { mkT TPrimtype } - <0> "primclass" { mkT TPrimclass } <0> "with" { mkT TWith } <0> "defaults" { mkT TDefaults } <0> "True" { mkT TTrue } diff --git a/utils/genprimopcode/Main.hs b/utils/genprimopcode/Main.hs index 05d42fa..c9d0d9c 100644 --- a/utils/genprimopcode/Main.hs +++ b/utils/genprimopcode/Main.hs @@ -269,8 +269,6 @@ gen_hs_source (Info defaults entries) = hdr (PseudoOpSpec { name = n }) = wrapOp n ++ "," hdr (PrimTypeSpec { ty = TyApp (TyCon n) _ }) = wrapTy n ++ "," hdr (PrimTypeSpec {}) = error $ "Illegal type spec" - hdr (PrimClassSpec { cls = TyApp (TyCon n) _ }) = wrapTy n ++ "," - hdr (PrimClassSpec {}) = error "Illegal class spec" hdr (PrimVecTypeSpec { ty = TyApp (VecTyCon n _) _ }) = wrapTy n ++ "," hdr (PrimVecTypeSpec {}) = error $ "Illegal type spec" @@ -278,7 +276,6 @@ gen_hs_source (Info defaults entries) = ent o@(PrimOpSpec {}) = spec o ent o@(PrimVecOpSpec {}) = spec o ent o@(PrimTypeSpec {}) = spec o - ent o@(PrimClassSpec {}) = spec o ent o@(PrimVecTypeSpec {}) = spec o ent o@(PseudoOpSpec {}) = spec o @@ -302,8 +299,6 @@ gen_hs_source (Info defaults entries) = wrapOp n ++ " = let x = x in x" ] PrimTypeSpec { ty = t } -> [ "data " ++ pprTy t ] - PrimClassSpec { cls = t } -> - [ "class " ++ pprTy t ] PrimVecTypeSpec { ty = t } -> [ "data " ++ pprTy t ] Section { } -> [] @@ -497,13 +492,6 @@ gen_latex_doc (Info defaults entries) ++ d ++ "}{" ++ mk_options o ++ "}\n" - mk_entry (PrimClassSpec {cls=t,desc=d,opts=o}) = - "\\primclassspec{" - ++ latex_encode (mk_source_ty t) ++ "}{" - ++ latex_encode (mk_core_ty t) ++ "}{" - ++ d ++ "}{" - ++ mk_options o - ++ "}\n" mk_entry (PrimVecTypeSpec {}) = "" mk_entry (PseudoOpSpec {name=n,ty=t,desc=d,opts=o}) = diff --git a/utils/genprimopcode/Parser.y b/utils/genprimopcode/Parser.y index ef6e27e..424efe6 100644 --- a/utils/genprimopcode/Parser.y +++ b/utils/genprimopcode/Parser.y @@ -40,7 +40,6 @@ import Syntax primop { TPrimop } pseudoop { TPseudoop } primtype { TPrimtype } - primclass { TPrimclass } with { TWith } defaults { TDefaults } true { TTrue } @@ -99,7 +98,6 @@ pEntries : pEntry pEntries { $1 : $2 } pEntry :: { Entry } pEntry : pPrimOpSpec { $1 } | pPrimTypeSpec { $1 } - | pPrimClassSpec { $1 } | pPseudoOpSpec { $1 } | pSection { $1 } @@ -120,10 +118,6 @@ pPrimTypeSpec :: { Entry } pPrimTypeSpec : primtype pType pDesc pWithOptions { PrimTypeSpec { ty = $2, desc = $3, opts = $4 } } -pPrimClassSpec :: { Entry } -pPrimClassSpec : primclass pType pDesc pWithOptions - { PrimClassSpec { cls = $2, desc = $3, opts = $4 } } - pPseudoOpSpec :: { Entry } pPseudoOpSpec : pseudoop string pType pDesc pWithOptions { PseudoOpSpec { name = $2, ty = $3, desc = $4, opts = $5 } } diff --git a/utils/genprimopcode/ParserM.hs b/utils/genprimopcode/ParserM.hs index 0a69db6..4dedfa3 100644 --- a/utils/genprimopcode/ParserM.hs +++ b/utils/genprimopcode/ParserM.hs @@ -83,7 +83,6 @@ data Token = TEOF | TPrimop | TPseudoop | TPrimtype - | TPrimclass | TWith | TDefaults | TTrue diff --git a/utils/genprimopcode/Syntax.hs b/utils/genprimopcode/Syntax.hs index d0c380c..68b20ad 100644 --- a/utils/genprimopcode/Syntax.hs +++ b/utils/genprimopcode/Syntax.hs @@ -35,9 +35,6 @@ data Entry | PrimTypeSpec { ty :: Ty, -- name in prog text desc :: String, -- description opts :: [Option] } -- default overrides - | PrimClassSpec { cls :: Ty, -- name in prog text - desc :: String, -- description - opts :: [Option] } -- default overrides | PrimVecTypeSpec { ty :: Ty, -- name in prog text prefix :: String, -- prefix for generated names veclen :: Int, -- vector length From git at git.haskell.org Mon Mar 17 08:51:18 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 17 Mar 2014 08:51:18 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T4404' created Message-ID: <20140317085120.2597D2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T4404 Referencing: 41dc5190d5ffec988834fa055f407157c1e1022b From git at git.haskell.org Mon Mar 17 08:51:20 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 17 Mar 2014 08:51:20 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T7704' created Message-ID: <20140317085120.B74782406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T7704 Referencing: b5541c97b0eb00b84772e786b86704ddf8b204b4 From git at git.haskell.org Mon Mar 17 08:51:22 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 17 Mar 2014 08:51:22 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T5084' created Message-ID: <20140317085122.ABCD82406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T5084 Referencing: 33208bb4b072b01c71ca24ca505ed3d11fbd7764 From git at git.haskell.org Mon Mar 17 08:51:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 17 Mar 2014 08:51:24 +0000 (UTC) Subject: [commit: ghc] branch 'T8776' deleted Message-ID: <20140317085124.D47942406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: T8776 From git at git.haskell.org Mon Mar 17 08:51:26 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 17 Mar 2014 08:51:26 +0000 (UTC) Subject: [commit: ghc] branch 'patch-5084' deleted Message-ID: <20140317085126.ABA862406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: patch-5084 From git at git.haskell.org Mon Mar 17 08:51:28 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 17 Mar 2014 08:51:28 +0000 (UTC) Subject: [commit: ghc] branch 'patch-7704' deleted Message-ID: <20140317085128.B7D4F2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: patch-7704 From git at git.haskell.org Mon Mar 17 08:51:30 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 17 Mar 2014 08:51:30 +0000 (UTC) Subject: [commit: ghc] branch 'patch-4404' deleted Message-ID: <20140317085130.AEF3D2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: patch-4404 From git at git.haskell.org Mon Mar 17 08:51:32 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 17 Mar 2014 08:51:32 +0000 (UTC) Subject: [commit: ghc] branch 'ghc-head' deleted Message-ID: <20140317085132.B7C9E2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: ghc-head From git at git.haskell.org Mon Mar 17 08:51:35 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 17 Mar 2014 08:51:35 +0000 (UTC) Subject: [commit: ghc] master: Unflatten the constraints of an inferred types (Trac #8889) (7a7af1f) Message-ID: <20140317085135.9051A2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7a7af1ffc48f605cf365faf8fcef31ef4f13822b/ghc >--------------------------------------------------------------- commit 7a7af1ffc48f605cf365faf8fcef31ef4f13822b Author: Simon Peyton Jones Date: Fri Mar 14 22:51:20 2014 +0000 Unflatten the constraints of an inferred types (Trac #8889) There was even a comment to warn about this possiblity, and it finally showed up in practice! This patch fixes it quite nicely, with commens to explain. >--------------------------------------------------------------- 7a7af1ffc48f605cf365faf8fcef31ef4f13822b compiler/typecheck/TcMType.lhs | 2 +- compiler/typecheck/TcSimplify.lhs | 44 +++++++++++++++++++++++-------------- 2 files changed, 29 insertions(+), 17 deletions(-) diff --git a/compiler/typecheck/TcMType.lhs b/compiler/typecheck/TcMType.lhs index 2bed04c..b9f3d25 100644 --- a/compiler/typecheck/TcMType.lhs +++ b/compiler/typecheck/TcMType.lhs @@ -56,7 +56,7 @@ module TcMType ( zonkTcTyVarBndr, zonkTcType, zonkTcTypes, zonkTcThetaType, zonkTcKind, defaultKindVarToStar, - zonkEvVar, zonkWC, zonkId, zonkCt, zonkCts, zonkSkolemInfo, + zonkEvVar, zonkWC, zonkFlats, zonkId, zonkCt, zonkCts, zonkSkolemInfo, tcGetGlobalTyVars, ) where diff --git a/compiler/typecheck/TcSimplify.lhs b/compiler/typecheck/TcSimplify.lhs index 0fdd2ba..af57729 100644 --- a/compiler/typecheck/TcSimplify.lhs +++ b/compiler/typecheck/TcSimplify.lhs @@ -253,39 +253,50 @@ simplifyInfer _top_lvl apply_mr name_taus wanteds ; ev_binds_var <- newTcEvBinds ; wanted_transformed_incl_derivs <- solveWantedsTcMWithEvBinds ev_binds_var wanteds solve_wanteds - -- Post: wanted_transformed are zonked + -- Post: wanted_transformed_incl_derivs are zonked -- Step 4) Candidates for quantification are an approximation of wanted_transformed -- NB: Already the fixpoint of any unifications that may have happened -- NB: We do not do any defaulting when inferring a type, this can lead -- to less polymorphic types, see Note [Default while Inferring] - -- Step 5) Minimize the quantification candidates - -- Step 6) Final candidates for quantification - -- We discard bindings, insolubles etc, because all we are - -- care aout it - ; tc_lcl_env <- TcRnMonad.getLclEnv ; let untch = tcl_untch tc_lcl_env wanted_transformed = dropDerivedWC wanted_transformed_incl_derivs ; quant_pred_candidates -- Fully zonked <- if insolubleWC wanted_transformed_incl_derivs then return [] -- See Note [Quantification with errors] - -- NB: must include derived errors - else do { gbl_tvs <- tcGetGlobalTyVars - ; let quant_cand = approximateWC wanted_transformed + -- 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)) - ; ((flats, _insols), _extra_binds) <- runTcS $ + ; gbl_tvs <- tcGetGlobalTyVars + ; null_ev_binds_var <- newTcEvBinds + -- Miminise quant_cand. We are not interested in any evidence + -- produced, because we are going to simplify wanted_transformed + -- again later. All we want here is the predicates over which to + -- quantify. + -- + -- If any meta-tyvar unifications take place (unlikely), we'll + -- pick that up later. + + ; (flats, _insols) <- runTcSWithEvBinds null_ev_binds_var $ do { mapM_ (promoteAndDefaultTyVar untch gbl_tvs) meta_tvs -- See Note [Promote _and_ default when inferring] ; _implics <- solveInteract quant_cand ; getInertUnsolved } - ; return (map ctPred $ filter isWantedCt (bagToList flats)) } - -- NB: Dimitrios is slightly worried that we will get - -- family equalities (F Int ~ alpha) in the quantification - -- candidates, as we have performed no further unflattening - -- at this point. Nothing bad, but inferred contexts might - -- look complicated. + + ; flats' <- zonkFlats null_ev_binds_var untch $ + filterBag isWantedCt flats + -- The quant_cand were already fully zonked, so this zonkFlats + -- really only unflattens the flattening that solveInteract + -- may have done (Trac #8889). + -- E.g. quant_cand = F a, where F :: * -> Constraint + -- We'll flatten to (alpha, F a ~ alpha) + -- fail to make any further progress and must unflatten again + + ; return (map ctPred $ bagToList flats') } -- NB: quant_pred_candidates is already the fixpoint of any -- unifications that may have happened @@ -326,6 +337,7 @@ simplifyInfer _top_lvl apply_mr name_taus wanteds { -- Step 7) Emit an implication let minimal_flat_preds = mkMinimalBySCs bound + -- See Note [Minimize by Superclasses] skol_info = InferSkol [ (name, mkSigmaTy [] minimal_flat_preds ty) | (name, ty) <- name_taus ] -- Don't add the quantified variables here, because From git at git.haskell.org Mon Mar 17 08:51:38 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 17 Mar 2014 08:51:38 +0000 (UTC) Subject: [commit: ghc] master: Revert ad15c2, which causes Windows seg-faults (Trac #8834) (a79613a) Message-ID: <20140317085138.7EC7F2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a79613a75c7da0d3d225850382f0f578a07113b5/ghc >--------------------------------------------------------------- commit a79613a75c7da0d3d225850382f0f578a07113b5 Author: Simon Peyton Jones Date: Fri Mar 14 22:55:26 2014 +0000 Revert ad15c2, which causes Windows seg-faults (Trac #8834) We don't yet understand WHY commit ad15c2, which is to do with CmmSink, causes seg-faults on Windows, but it certainly seems to. So reverting it is a stop-gap, but we need to un-block the 7.8 release. Many thanks to awson for identifying the offending commit. >--------------------------------------------------------------- a79613a75c7da0d3d225850382f0f578a07113b5 compiler/cmm/CmmSink.hs | 85 ++++++++++++----------------------------------- 1 file changed, 21 insertions(+), 64 deletions(-) diff --git a/compiler/cmm/CmmSink.hs b/compiler/cmm/CmmSink.hs index c404a2e..635b002 100644 --- a/compiler/cmm/CmmSink.hs +++ b/compiler/cmm/CmmSink.hs @@ -3,6 +3,8 @@ module CmmSink ( cmmSink ) where +import CodeGen.Platform (callerSaves) + import Cmm import CmmOpt import BlockId @@ -236,9 +238,11 @@ some tool like perf or VTune and make decisions what to inline based on that. -- global) and literals. -- isTrivial :: CmmExpr -> Bool -isTrivial (CmmReg _) = True -isTrivial (CmmLit _) = True -isTrivial _ = False +isTrivial (CmmReg (CmmLocal _)) = True +-- isTrivial (CmmLit _) = True -- Disabled because it used to make thing worse. + -- Needs further investigation +isTrivial _ = False + -- -- annotate each node with the set of registers live *after* the node @@ -501,8 +505,7 @@ regsUsedIn ls e = wrapRecExpf f e False -- nor the NCG can do it. See Note [Register parameter passing] -- See also StgCmmForeign:load_args_into_temps. okToInline :: DynFlags -> CmmExpr -> CmmNode e x -> Bool -okToInline dflags expr node@(CmmUnsafeForeignCall{}) = - not (globalRegistersConflict dflags expr node) +okToInline dflags expr CmmUnsafeForeignCall{} = not (anyCallerSavesRegs dflags expr) okToInline _ _ _ = True -- ----------------------------------------------------------------------------- @@ -515,23 +518,23 @@ okToInline _ _ _ = True conflicts :: DynFlags -> Assignment -> CmmNode O x -> Bool conflicts dflags (r, rhs, addr) node - -- (1) node defines registers used by rhs of assignment. This catches - -- assignmnets and all three kinds of calls. See Note [Sinking and calls] - | globalRegistersConflict dflags rhs node = True - | localRegistersConflict dflags rhs node = True - - -- (2) node uses register defined by assignment + -- (1) an assignment to a register conflicts with a use of the register + | CmmAssign reg _ <- node, reg `regUsedIn` rhs = True | foldRegsUsed dflags (\b r' -> r == r' || b) False node = True - -- (3) a store to an address conflicts with a read of the same memory + -- (2) a store to an address conflicts with a read of the same memory | CmmStore addr' e <- node , memConflicts addr (loadAddr dflags addr' (cmmExprWidth dflags e)) = True - -- (4) an assignment to Hp/Sp conflicts with a heap/stack read respectively + -- (3) an assignment to Hp/Sp conflicts with a heap/stack read respectively | HeapMem <- addr, CmmAssign (CmmGlobal Hp) _ <- node = True | StackMem <- addr, CmmAssign (CmmGlobal Sp) _ <- node = True | SpMem{} <- addr, CmmAssign (CmmGlobal Sp) _ <- node = True + -- (4) assignments that read caller-saves GlobalRegs conflict with a + -- foreign call. See Note [Unsafe foreign calls clobber caller-save registers] + | CmmUnsafeForeignCall{} <- node, anyCallerSavesRegs dflags rhs = True + -- (5) foreign calls clobber heap: see Note [Foreign calls clobber heap] | CmmUnsafeForeignCall{} <- node, memConflicts addr AnyMem = True @@ -541,57 +544,11 @@ conflicts dflags (r, rhs, addr) node -- (7) otherwise, no conflict | otherwise = False --- Returns True if node defines any global registers that are used in the --- Cmm expression -globalRegistersConflict :: DynFlags -> CmmExpr -> CmmNode e x -> Bool -globalRegistersConflict dflags expr node = - foldRegsDefd dflags (\b r -> b || (CmmGlobal r) `regUsedIn` expr) False node - --- Returns True if node defines any local registers that are used in the --- Cmm expression -localRegistersConflict :: DynFlags -> CmmExpr -> CmmNode e x -> Bool -localRegistersConflict dflags expr node = - foldRegsDefd dflags (\b r -> b || (CmmLocal r) `regUsedIn` expr) False node - --- Note [Sinking and calls] --- ~~~~~~~~~~~~~~~~~~~~~~~~ --- --- We have three kinds of calls: normal (CmmCall), safe foreign (CmmForeignCall) --- and unsafe foreign (CmmUnsafeForeignCall). We perform sinking pass after --- stack layout (see Note [Sinking after stack layout]) which leads to two --- invariants related to calls: --- --- a) during stack layout phase all safe foreign calls are turned into --- unsafe foreign calls (see Note [Lower safe foreign calls]). This --- means that we will never encounter CmmForeignCall node when running --- sinking after stack layout --- --- b) stack layout saves all variables live across a call on the stack --- just before making a call (remember we are not sinking assignments to --- stack): --- --- L1: --- x = R1 --- P64[Sp - 16] = L2 --- P64[Sp - 8] = x --- Sp = Sp - 16 --- call f() returns L2 --- L2: --- --- We will attempt to sink { x = R1 } but we will detect conflict with --- { P64[Sp - 8] = x } and hence we will drop { x = R1 } without even --- checking whether it conflicts with { call f() }. In this way we will --- never need to check any assignment conflicts with CmmCall. Remember --- that we still need to check for potential memory conflicts. --- --- So the result is that we only need to worry about CmmUnsafeForeignCall nodes --- when checking conflicts (see Note [Unsafe foreign calls clobber caller-save registers]). --- This assumption holds only when we do sinking after stack layout. If we run --- it before stack layout we need to check for possible conflicts with all three --- kinds of calls. Our `conflicts` function does that by using a generic --- foldRegsDefd and foldRegsUsed functions defined in DefinerOfRegs and --- UserOfRegs typeclasses. --- +anyCallerSavesRegs :: DynFlags -> CmmExpr -> Bool +anyCallerSavesRegs dflags e = wrapRecExpf f e False + where f (CmmReg (CmmGlobal r)) _ + | callerSaves (targetPlatform dflags) r = True + f _ z = z -- An abstraction of memory read or written. data AbsMem From git at git.haskell.org Mon Mar 17 13:43:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 17 Mar 2014 13:43:47 +0000 (UTC) Subject: [commit: ghc] master: Fix validation issue due to Coercible move (#8894) (7511d5b) Message-ID: <20140317134347.2D04D2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7511d5bf708f38bbdf5733f42dc8a025c76cc684/ghc >--------------------------------------------------------------- commit 7511d5bf708f38bbdf5733f42dc8a025c76cc684 Author: Joachim Breitner Date: Mon Mar 17 14:43:31 2014 +0100 Fix validation issue due to Coercible move (#8894) >--------------------------------------------------------------- 7511d5bf708f38bbdf5733f42dc8a025c76cc684 testsuite/tests/typecheck/should_fail/TcCoercibleFail.hs | 2 +- testsuite/tests/typecheck/should_fail/TcCoercibleFail2.hs | 2 +- testsuite/tests/typecheck/should_fail/TcCoercibleFail3.hs | 2 +- testsuite/tests/typecheck/should_run/TcCoercible.hs | 2 +- 4 files changed, 4 insertions(+), 4 deletions(-) diff --git a/testsuite/tests/typecheck/should_fail/TcCoercibleFail.hs b/testsuite/tests/typecheck/should_fail/TcCoercibleFail.hs index 1ad76d4..0431eee 100644 --- a/testsuite/tests/typecheck/should_fail/TcCoercibleFail.hs +++ b/testsuite/tests/typecheck/should_fail/TcCoercibleFail.hs @@ -1,6 +1,6 @@ {-# LANGUAGE RoleAnnotations, RankNTypes, ScopedTypeVariables #-} -import GHC.Prim (coerce, Coercible) +import Data.Coerce (coerce, Coercible) import Data.Ord (Down) newtype Age = Age Int deriving Show diff --git a/testsuite/tests/typecheck/should_fail/TcCoercibleFail2.hs b/testsuite/tests/typecheck/should_fail/TcCoercibleFail2.hs index 13a3234..8d89b52 100644 --- a/testsuite/tests/typecheck/should_fail/TcCoercibleFail2.hs +++ b/testsuite/tests/typecheck/should_fail/TcCoercibleFail2.hs @@ -1,4 +1,4 @@ -import GHC.Prim (Coercible) +import Data.Coerce (Coercible) instance Coercible () () diff --git a/testsuite/tests/typecheck/should_fail/TcCoercibleFail3.hs b/testsuite/tests/typecheck/should_fail/TcCoercibleFail3.hs index 4caf1c2..eb9b725 100644 --- a/testsuite/tests/typecheck/should_fail/TcCoercibleFail3.hs +++ b/testsuite/tests/typecheck/should_fail/TcCoercibleFail3.hs @@ -1,6 +1,6 @@ {-# LANGUAGE RoleAnnotations, RankNTypes, ScopedTypeVariables #-} -import GHC.Prim (coerce, Coercible) +import Data.Coerce (coerce, Coercible) newtype List a = List [a] data T f = T (f Int) diff --git a/testsuite/tests/typecheck/should_run/TcCoercible.hs b/testsuite/tests/typecheck/should_run/TcCoercible.hs index e3b29af..7bb8e48 100644 --- a/testsuite/tests/typecheck/should_run/TcCoercible.hs +++ b/testsuite/tests/typecheck/should_run/TcCoercible.hs @@ -1,6 +1,6 @@ {-# LANGUAGE RoleAnnotations, StandaloneDeriving, FlexibleContexts, UndecidableInstances, GADTs, TypeFamilies #-} -import GHC.Prim (Coercible, coerce) +import Data.Coerce (Coercible, coerce) import Data.Monoid (mempty, First(First), Last()) newtype Age = Age Int deriving Show From git at git.haskell.org Mon Mar 17 13:51:16 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 17 Mar 2014 13:51:16 +0000 (UTC) Subject: [commit: ghc] master: Comments only (2b3feaa) Message-ID: <20140317135116.4514D2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2b3feaa5e6da5f071ffe0325a81a32fd395739b6/ghc >--------------------------------------------------------------- commit 2b3feaa5e6da5f071ffe0325a81a32fd395739b6 Author: Simon Peyton Jones Date: Fri Mar 14 13:50:14 2014 +0000 Comments only >--------------------------------------------------------------- 2b3feaa5e6da5f071ffe0325a81a32fd395739b6 compiler/types/Type.lhs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/compiler/types/Type.lhs b/compiler/types/Type.lhs index b8edc3e..88054ce 100644 --- a/compiler/types/Type.lhs +++ b/compiler/types/Type.lhs @@ -1365,7 +1365,7 @@ emptyTvSubst :: TvSubst emptyTvSubst = TvSubst emptyInScopeSet emptyTvSubstEnv isEmptyTvSubst :: TvSubst -> Bool - -- See Note [Extending the TvSubstEnv] + -- See Note [Extending the TvSubstEnv] in TypeRep isEmptyTvSubst (TvSubst _ tenv) = isEmptyVarEnv tenv mkTvSubst :: InScopeSet -> TvSubstEnv -> TvSubst @@ -1559,7 +1559,7 @@ subst_ty subst ty substTyVar :: TvSubst -> TyVar -> Type substTyVar (TvSubst _ tenv) tv | Just ty <- lookupVarEnv tenv tv = ty -- See Note [Apply Once] - | otherwise = ASSERT( isTyVar tv ) TyVarTy tv + | otherwise = ASSERT( isTyVar tv ) TyVarTy tv -- in TypeRep -- We do not require that the tyvar is in scope -- Reason: we do quite a bit of (substTyWith [tv] [ty] tau) -- and it's a nuisance to bring all the free vars of tau into @@ -1570,7 +1570,7 @@ substTyVars :: TvSubst -> [TyVar] -> [Type] substTyVars subst tvs = map (substTyVar subst) tvs lookupTyVar :: TvSubst -> TyVar -> Maybe Type - -- See Note [Extending the TvSubst] + -- See Note [Extending the TvSubst] in TypeRep lookupTyVar (TvSubst _ tenv) tv = lookupVarEnv tenv tv substTyVarBndr :: TvSubst -> TyVar -> (TvSubst, TyVar) @@ -1589,7 +1589,7 @@ substTyVarBndr subst@(TvSubst in_scope tenv) old_var no_change = no_kind_change && (new_var == old_var) -- no_change means that the new_var is identical in -- all respects to the old_var (same unique, same kind) - -- See Note [Extending the TvSubst] + -- See Note [Extending the TvSubst] in TypeRep -- -- In that case we don't need to extend the substitution -- to map old to new. But instead we must zap any From git at git.haskell.org Mon Mar 17 13:51:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 17 Mar 2014 13:51:19 +0000 (UTC) Subject: [commit: ghc] master: More debug info (f4d15cb) Message-ID: <20140317135119.A11E12406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f4d15cb97a0d480d39ef4272192ca731fb732c6d/ghc >--------------------------------------------------------------- commit f4d15cb97a0d480d39ef4272192ca731fb732c6d Author: Simon Peyton Jones Date: Fri Mar 14 13:50:29 2014 +0000 More debug info >--------------------------------------------------------------- f4d15cb97a0d480d39ef4272192ca731fb732c6d compiler/typecheck/TcDeriv.lhs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcDeriv.lhs b/compiler/typecheck/TcDeriv.lhs index 03004c9..a89adda 100644 --- a/compiler/typecheck/TcDeriv.lhs +++ b/compiler/typecheck/TcDeriv.lhs @@ -652,6 +652,7 @@ deriveStandalone (L loc (DerivDecl deriv_ty)) ------------------------------------------------------------------ deriveTyData :: [TyVar] -> TyCon -> [Type] -- LHS of data or data instance + -- Can be a data instance, hence [Type] args -> LHsType Name -- The deriving predicate -> TcM EarlyDerivSpec -- The deriving clause of a data or newtype declaration @@ -692,10 +693,11 @@ deriveTyData tvs tc tc_args (L loc deriv_pred) final_cls_tys = substTys subst cls_tys univ_tvs = mkVarSet deriv_tvs `unionVarSet` tyVarsOfTypes final_tc_args - ; traceTc "derivTyData1" (vcat [ pprTvBndrs tvs, ppr tc, ppr tc_args + ; traceTc "derivTyData1" (vcat [ pprTvBndrs tvs, ppr tc, ppr tc_args, ppr deriv_pred , pprTvBndrs (varSetElems $ tyVarsOfTypes tc_args) , ppr n_args_to_keep, ppr n_args_to_drop - , ppr inst_ty_kind, ppr cls_arg_kind, ppr mb_match ]) + , ppr inst_ty_kind, ppr cls_arg_kind, ppr mb_match + , ppr final_tc_args, ppr final_cls_tys ]) -- Check that the result really is well-kinded ; checkTc (n_args_to_keep >= 0 && isJust mb_match) From git at git.haskell.org Mon Mar 17 13:51:22 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 17 Mar 2014 13:51:22 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #8889 (0e2155d) Message-ID: <20140317135122.926D02406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0e2155ddb10f4ccf53e50064756cbc3ce7dd8832/ghc >--------------------------------------------------------------- commit 0e2155ddb10f4ccf53e50064756cbc3ce7dd8832 Author: Simon Peyton Jones Date: Mon Mar 17 13:50:54 2014 +0000 Test Trac #8889 >--------------------------------------------------------------- 0e2155ddb10f4ccf53e50064756cbc3ce7dd8832 testsuite/tests/indexed-types/should_compile/T8889.hs | 12 ++++++++++++ testsuite/tests/indexed-types/should_compile/T8889.stderr | 6 ++++++ testsuite/tests/indexed-types/should_compile/all.T | 1 + 3 files changed, 19 insertions(+) diff --git a/testsuite/tests/indexed-types/should_compile/T8889.hs b/testsuite/tests/indexed-types/should_compile/T8889.hs new file mode 100644 index 0000000..45c88a6 --- /dev/null +++ b/testsuite/tests/indexed-types/should_compile/T8889.hs @@ -0,0 +1,12 @@ +{-# LANGUAGE TypeFamilies, ConstraintKinds #-} +{-# OPTIONS_GHC -fwarn-missing-signatures #-} -- Report f's inferred type + +module T8889 where + +import GHC.Exts + +class C f where + type C_fmap f a :: Constraint + foo :: C_fmap f a => (a -> b) -> f a -> f b + +f x = foo x diff --git a/testsuite/tests/indexed-types/should_compile/T8889.stderr b/testsuite/tests/indexed-types/should_compile/T8889.stderr new file mode 100644 index 0000000..77e05d7 --- /dev/null +++ b/testsuite/tests/indexed-types/should_compile/T8889.stderr @@ -0,0 +1,6 @@ + +T8889.hs:12:1: Warning: + Top-level binding with no type signature: + f :: forall (f :: * -> *) a b. + (C_fmap f a, C f) => + (a -> b) -> f a -> f b diff --git a/testsuite/tests/indexed-types/should_compile/all.T b/testsuite/tests/indexed-types/should_compile/all.T index f722ea3..5c156ec 100644 --- a/testsuite/tests/indexed-types/should_compile/all.T +++ b/testsuite/tests/indexed-types/should_compile/all.T @@ -239,3 +239,4 @@ test('ClosedFam1', extra_clean(['ClosedFam1.o-boot', 'ClosedFam1.hi-boot']), test('ClosedFam2', extra_clean(['ClosedFam2.o-boot', 'ClosedFam2.hi-boot']), multimod_compile, ['ClosedFam2', '-v0']) test('T8651', normal, compile, ['']) +test('T8889', normal, compile, ['']) From git at git.haskell.org Mon Mar 17 14:35:23 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 17 Mar 2014 14:35:23 +0000 (UTC) Subject: [commit: ghc] master: Test case: ghci059: Forgot stdout file (a5ab610) Message-ID: <20140317143523.AFFFB2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a5ab610f8d7ea5ddbcfe2c27fa18fceb02923ee2/ghc >--------------------------------------------------------------- commit a5ab610f8d7ea5ddbcfe2c27fa18fceb02923ee2 Author: Joachim Breitner Date: Mon Mar 17 15:34:54 2014 +0100 Test case: ghci059: Forgot stdout file >--------------------------------------------------------------- a5ab610f8d7ea5ddbcfe2c27fa18fceb02923ee2 testsuite/tests/ghci/scripts/ghci059.stdout | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/testsuite/tests/ghci/scripts/ghci059.stdout b/testsuite/tests/ghci/scripts/ghci059.stdout new file mode 100644 index 0000000..6b2c8f8 --- /dev/null +++ b/testsuite/tests/ghci/scripts/ghci059.stdout @@ -0,0 +1,4 @@ +type role Coercible representational representational +class Coercible (a :: k) (b :: k) + -- Defined in ?GHC.Types? +coerce :: Coercible a b => a -> b -- Defined in ?GHC.Prim? From git at git.haskell.org Mon Mar 17 15:36:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 17 Mar 2014 15:36:11 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: add missing files (#8124) (7d4540f) Message-ID: <20140317153611.EB2D82406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/7d4540f23df4cb32eaba94c3d574df2a0850b8f4/ghc >--------------------------------------------------------------- commit 7d4540f23df4cb32eaba94c3d574df2a0850b8f4 Author: Simon Marlow Date: Sat Mar 1 07:14:47 2014 +0000 add missing files (#8124) (cherry picked from commit 3fba87599378afbcf425a0fc2a5a61d21e3719d4) >--------------------------------------------------------------- 7d4540f23df4cb32eaba94c3d574df2a0850b8f4 testsuite/tests/rts/T8124.hs | 6 ++++++ testsuite/tests/rts/T8124_c.c | 42 +++++++++++++++++++++++++++++++++++++++++ 2 files changed, 48 insertions(+) diff --git a/testsuite/tests/rts/T8124.hs b/testsuite/tests/rts/T8124.hs new file mode 100644 index 0000000..c914b03 --- /dev/null +++ b/testsuite/tests/rts/T8124.hs @@ -0,0 +1,6 @@ +module T8124 where + +f :: Int -> Int +f x = x + 1 + +foreign export ccall "f" f :: Int -> Int diff --git a/testsuite/tests/rts/T8124_c.c b/testsuite/tests/rts/T8124_c.c new file mode 100644 index 0000000..e7e8739 --- /dev/null +++ b/testsuite/tests/rts/T8124_c.c @@ -0,0 +1,42 @@ +#include +#include "T8124_stub.h" +#include "HsFFI.h" +#include + +void *thread(void *param) +{ + f(3); + hs_thread_done(); + pthread_exit(NULL); +} + +int main (int argc, char *argv[]) +{ + hs_init(&argc,&argv); + + // check that we can call hs_thread_done() without having made any + // Haskell calls: + hs_thread_done(); + + // check that we can call hs_thread_done() and then make another Haskell + // call: + int i; + for (i=0; i < 1000; i++) { + f(3); + hs_thread_done(); + } + + // check that we can call hs_thread_done() twice: + hs_thread_done(); + hs_thread_done(); + + // check that hs_thread_done() from child threads works: + pthread_t pid; + for (i=0; i < 1000; i++) { + pthread_create(&pid, NULL, thread, NULL); + pthread_join(pid, NULL); + } + + hs_exit(); + exit(0); +} From git at git.haskell.org Mon Mar 17 15:36:14 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 17 Mar 2014 15:36:14 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: fix copy/pasto (1fdb951) Message-ID: <20140317153615.21F352406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/1fdb9517e99314ddd4139a9f7f0d71f32a13b337/ghc >--------------------------------------------------------------- commit 1fdb9517e99314ddd4139a9f7f0d71f32a13b337 Author: Simon Marlow Date: Sat Mar 1 07:16:44 2014 +0000 fix copy/pasto (cherry picked from commit 176205cf0b89f76d904d381bdcd61e8685116bb7) >--------------------------------------------------------------- 1fdb9517e99314ddd4139a9f7f0d71f32a13b337 testsuite/tests/rts/Makefile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/rts/Makefile b/testsuite/tests/rts/Makefile index 7f9e073..180fe9b 100644 --- a/testsuite/tests/rts/Makefile +++ b/testsuite/tests/rts/Makefile @@ -85,7 +85,7 @@ T6006_setup : '$(TEST_HC)' $(TEST_HC_OPTS) -c T6006.hs T8124_setup : - '$(TEST_HC)' $(TEST_HC_OPTS) -c T6006.hs + '$(TEST_HC)' $(TEST_HC_OPTS) -c T8124.hs ifeq "$(TARGETPLATFORM)" "i386-unknown-mingw32" T7037_CONST = const From git at git.haskell.org Mon Mar 17 15:36:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 17 Mar 2014 15:36:17 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Run testcase for 8124 only with threaded ways (e5c8d5b) Message-ID: <20140317153617.68F0E2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/e5c8d5bc38dd4d3e42911ff3285f830f1b6df856/ghc >--------------------------------------------------------------- commit e5c8d5bc38dd4d3e42911ff3285f830f1b6df856 Author: Joachim Breitner Date: Fri Mar 7 16:05:39 2014 +0100 Run testcase for 8124 only with threaded ways (cherry picked from commit 0014fb3dbf4a2096489a4800adf2d79a83a12274) >--------------------------------------------------------------- e5c8d5bc38dd4d3e42911ff3285f830f1b6df856 testsuite/tests/rts/all.T | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/rts/all.T b/testsuite/tests/rts/all.T index d36cc21..f7c4986 100644 --- a/testsuite/tests/rts/all.T +++ b/testsuite/tests/rts/all.T @@ -200,7 +200,7 @@ test('T8209', [ only_ways(threaded_ways), ignore_output ], test('T8242', [ only_ways(threaded_ways), ignore_output ], compile_and_run, ['']) -test('T8124', [ omit_ways(prof_ways + ['ghci']), +test('T8124', [ only_ways(threaded_ways), omit_ways(['ghci']), extra_clean(['T8124_c.o']), pre_cmd('$MAKE -s --no-print-directory T8124_setup') ], # The T8124_setup hack is to ensure that we generate From git at git.haskell.org Mon Mar 17 15:36:21 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 17 Mar 2014 15:36:21 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Make SetLevels do substitution properly (fixes Trac #8714) (9a168d6) Message-ID: <20140317153621.6D19F2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/9a168d6097e9d08f4e1d399d10a6690d479e6a40/ghc >--------------------------------------------------------------- commit 9a168d6097e9d08f4e1d399d10a6690d479e6a40 Author: Simon Peyton Jones Date: Tue Mar 11 11:13:31 2014 +0000 Make SetLevels do substitution properly (fixes Trac #8714) Nowadays SetLevels floats case expressions as well as let-bindings, and case expressions bind type variables. We need to clone all such floated binders, to avoid accidental name capture. But I'd forgotten to substitute for the cloned type variables, causing #8714. (In the olden days only Ids were cloned, from let-bindings.) This patch fixes the bug and does quite a bit of clean-up refactoring as well, by putting the context level in the LvlEnv. There is no effect on performance, except that nofib 'rewrite' improves allocations by 3%. On investigation I think it was a fluke to do with loop-cutting in big letrec nests. But at least it's a fluke in the right direction. Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- Min -0.4% -3.0% -19.4% -19.4% -26.7% Max -0.0% +0.0% +17.9% +17.9% 0.0% Geometric Mean -0.1% -0.0% -0.7% -0.7% -0.4% (cherry picked from commit ef44a429af4a630a153b5774d0e19dbcad8328d5) >--------------------------------------------------------------- 9a168d6097e9d08f4e1d399d10a6690d479e6a40 compiler/coreSyn/CoreSubst.lhs | 2 +- compiler/coreSyn/CoreSyn.lhs | 21 +- compiler/simplCore/SetLevels.lhs | 602 ++++++++++----------- testsuite/tests/simplCore/should_compile/T8714.hs | 9 + testsuite/tests/simplCore/should_compile/all.T | 1 + 5 files changed, 312 insertions(+), 323 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 9a168d6097e9d08f4e1d399d10a6690d479e6a40 From git at git.haskell.org Mon Mar 17 15:36:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 17 Mar 2014 15:36:24 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Fix last-minute typo in SetLevels commit ef44a4 (76ba0d6) Message-ID: <20140317153624.3E2922406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/76ba0d6d4748d9cc00c6486aae8dcb2a8cd6a1c1/ghc >--------------------------------------------------------------- commit 76ba0d6d4748d9cc00c6486aae8dcb2a8cd6a1c1 Author: Simon Peyton Jones Date: Tue Mar 11 12:47:57 2014 +0000 Fix last-minute typo in SetLevels commit ef44a4 Sorry about that... (cherry picked from commit 41f803105999ffe51a40d3c72d5994520496b7ea) >--------------------------------------------------------------- 76ba0d6d4748d9cc00c6486aae8dcb2a8cd6a1c1 compiler/simplCore/SetLevels.lhs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/compiler/simplCore/SetLevels.lhs b/compiler/simplCore/SetLevels.lhs index cc72164..6edadb8 100644 --- a/compiler/simplCore/SetLevels.lhs +++ b/compiler/simplCore/SetLevels.lhs @@ -479,7 +479,8 @@ lvlMFE strict_ctxt env ann_expr@(fvs, _) ; return (Let (NonRec (TB var (FloatMe dest_lvl)) expr') (mkVarApps (Var var) abs_vars)) } where - is_bot = exprIsBottom (deAnnotate ann_expr) -- Note [Bottoming floats] + expr = deAnnotate ann_expr + is_bot = exprIsBottom expr -- Note [Bottoming floats] dest_lvl = destLevel env fvs (isFunction ann_expr) is_bot abs_vars = abstractVars dest_lvl env fvs From git at git.haskell.org Mon Mar 17 15:36:27 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 17 Mar 2014 15:36:27 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: fix SHELL makefile variable to be set by the configure script (fixes #8783) (af88b5b) Message-ID: <20140317153627.4A4422406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/af88b5b7ded1904e687de3d2057eb1fa0ff3dfbd/ghc >--------------------------------------------------------------- commit af88b5b7ded1904e687de3d2057eb1fa0ff3dfbd Author: Karel Gardas Date: Wed Mar 12 16:14:49 2014 +0100 fix SHELL makefile variable to be set by the configure script (fixes #8783) The patch provided by Christian Maeder Signed-off-by: Karel Gardas Signed-off-by: Austin Seipp (cherry picked from commit a0bcbb54481297f9ff329766529a8343c4853e3f) >--------------------------------------------------------------- af88b5b7ded1904e687de3d2057eb1fa0ff3dfbd 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 b805a14..f24c495 100644 --- a/mk/config.mk.in +++ b/mk/config.mk.in @@ -652,7 +652,7 @@ PIC = pic RANLIB_CMD = @RANLIB_CMD@ REAL_RANLIB_CMD = @REAL_RANLIB_CMD@ SED = @SedCmd@ -SHELL = /bin/sh +SHELL = @SHELL@ HaveDtrace = @HaveDtrace@ USE_DTRACE = $(HaveDtrace) From git at git.haskell.org Mon Mar 17 15:36:30 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 17 Mar 2014 15:36:30 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Remove "Safe mode" check for Coercible instances (c00406c) Message-ID: <20140317153630.BA33F2406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/c00406c0b565823946b0874bd18e568bfce2282c/ghc >--------------------------------------------------------------- commit c00406c0b565823946b0874bd18e568bfce2282c Author: Richard Eisenberg Date: Thu Mar 13 14:16:37 2014 -0400 Remove "Safe mode" check for Coercible instances We assume that library authors supply correct role annotations for their types, and therefore we do not need to check for the availability of data constructors in Safe mode. See discussion in #8725. This effectively fixes #8827 and #8826. (cherry picked from commit 59722295bb8da8f01d37356fbed6aef7321a8195) >--------------------------------------------------------------- c00406c0b565823946b0874bd18e568bfce2282c compiler/typecheck/TcInteract.lhs | 21 +++++--------------- .../typecheck/should_fail/TcCoercibleFailSafe.hs | 11 ---------- .../should_fail/TcCoercibleFailSafe.stderr | 8 -------- testsuite/tests/typecheck/should_fail/all.T | 1 - 4 files changed, 5 insertions(+), 36 deletions(-) diff --git a/compiler/typecheck/TcInteract.lhs b/compiler/typecheck/TcInteract.lhs index 377cd2d..75835ad 100644 --- a/compiler/typecheck/TcInteract.lhs +++ b/compiler/typecheck/TcInteract.lhs @@ -1922,11 +1922,10 @@ getCoercibleInst loc ty1 ty2 = do -- Get some global stuff in scope, for nice pattern-guard based code in `go` rdr_env <- getGlobalRdrEnvTcS famenv <- getFamInstEnvs - safeMode <- safeLanguageOn `fmap` getDynFlags - go safeMode famenv rdr_env + go famenv rdr_env where - go :: Bool -> FamInstEnvs -> GlobalRdrEnv -> TcS LookupInstResult - go safeMode famenv rdr_env + go :: FamInstEnvs -> GlobalRdrEnv -> TcS LookupInstResult + go famenv rdr_env -- Coercible a a (see case 1 in [Coercible Instances]) | ty1 `tcEqType` ty2 = do return $ GenInst [] @@ -1946,11 +1945,8 @@ getCoercibleInst loc ty1 ty2 = do | Just (tc1,tyArgs1) <- splitTyConApp_maybe ty1, Just (tc2,tyArgs2) <- splitTyConApp_maybe ty2, tc1 == tc2, - nominalArgsAgree tc1 tyArgs1 tyArgs2, - not safeMode || all (dataConsInScope rdr_env) (tyConsOfTyCon tc1) - = do -- Mark all used data constructors as used - when safeMode $ mapM_ (markDataConsAsUsed rdr_env) (tyConsOfTyCon tc1) - -- We want evidence for all type arguments of role R + nominalArgsAgree tc1 tyArgs1 tyArgs2 + = do -- We want evidence for all type arguments of role R arg_stuff <- forM (zip3 (tyConRoles tc1) tyArgs1 tyArgs2) $ \(r,ta1,ta2) -> case r of Nominal -> do return @@ -2060,13 +2056,6 @@ air, in getCoercibleInst. The following ?instances? are present: The type constructor can be used undersaturated; then the Coercible instance is at a higher kind. This does not cause problems. - Furthermore in Safe Haskell code, we check that - * the data constructors of C are in scope and - * the data constructors of all type constructors used in the definition of - * C are in scope. - This is required as otherwise the previous check can be circumvented by - just adding a local data type around C. - 4. instance Coercible r b => Coercible (NT t1 t2 ...) b instance Coercible a r => Coercible a (NT t1 t2 ...) for a newtype constructor NT (or data family instance that resolves to a diff --git a/testsuite/tests/typecheck/should_fail/TcCoercibleFailSafe.hs b/testsuite/tests/typecheck/should_fail/TcCoercibleFailSafe.hs deleted file mode 100644 index 85f86b6..0000000 --- a/testsuite/tests/typecheck/should_fail/TcCoercibleFailSafe.hs +++ /dev/null @@ -1,11 +0,0 @@ -{-# LANGUAGE RoleAnnotations, RankNTypes, ScopedTypeVariables, Safe #-} - -import GHC.Prim (coerce, Coercible) -import Data.Ord (Down) - -newtype Age = Age Int deriving Show - -foo1 :: (Down Age -> Down Int) -foo1 = coerce - -main = return () diff --git a/testsuite/tests/typecheck/should_fail/TcCoercibleFailSafe.stderr b/testsuite/tests/typecheck/should_fail/TcCoercibleFailSafe.stderr deleted file mode 100644 index 2d7bf19..0000000 --- a/testsuite/tests/typecheck/should_fail/TcCoercibleFailSafe.stderr +++ /dev/null @@ -1,8 +0,0 @@ - -TcCoercibleFailSafe.hs:9:8: - Could not coerce from ?Down Age? to ?Down Int? - because the constructor of ?Down? is not imported - as required in SafeHaskell mode - arising from a use of ?coerce? - In the expression: coerce - In an equation for ?foo1?: foo1 = coerce diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index faef063..092a7da 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -317,7 +317,6 @@ test('T7989', normal, compile_fail, ['']) test('T8142', normal, compile_fail, ['']) test('T8262', normal, compile_fail, ['']) test('TcCoercibleFail', when(compiler_lt('ghc', '7.7'), skip), compile_fail, ['']) -test('TcCoercibleFailSafe', when(compiler_lt('ghc', '7.7'), skip), compile_fail, ['']) test('TcCoercibleFail2', when(compiler_lt('ghc', '7.7'), skip), compile_fail, ['']) test('TcCoercibleFail3', when(compiler_lt('ghc', '7.7'), skip), compile_fail, ['']) test('T8306', normal, compile_fail, ['']) From git at git.haskell.org Mon Mar 17 15:36:33 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 17 Mar 2014 15:36:33 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Remove code reporting issues with Safe Haskell and coerce. (358b3c0) Message-ID: <20140317153633.7F1692406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/358b3c05dc95f66c61beda2b1b40c2669968b0c5/ghc >--------------------------------------------------------------- commit 358b3c05dc95f66c61beda2b1b40c2669968b0c5 Author: Richard Eisenberg Date: Fri Mar 14 15:03:21 2014 -0400 Remove code reporting issues with Safe Haskell and coerce. This is a followup to the fix for #8827, and should be merged with that change. (cherry picked from commit 7602bd4de901e4304a3a45dca08fc630d1bb5bf2) >--------------------------------------------------------------- 358b3c05dc95f66c61beda2b1b40c2669968b0c5 compiler/typecheck/TcErrors.lhs | 24 ++++-------------------- 1 file changed, 4 insertions(+), 20 deletions(-) diff --git a/compiler/typecheck/TcErrors.lhs b/compiler/typecheck/TcErrors.lhs index f105cdd..6afc424 100644 --- a/compiler/typecheck/TcErrors.lhs +++ b/compiler/typecheck/TcErrors.lhs @@ -995,9 +995,8 @@ mk_dict_err ctxt (ct, (matches, unifiers, safe_haskell)) = do { let (is_ambig, ambig_msg) = mkAmbigMsg ct ; (ctxt, binds_msg) <- relevantBindings True ctxt ct ; traceTc "mk_dict_err" (ppr ct $$ ppr is_ambig $$ ambig_msg) - ; safe_mod <- safeLanguageOn `fmap` getDynFlags ; rdr_env <- getGlobalRdrEnv - ; return (ctxt, cannot_resolve_msg safe_mod rdr_env is_ambig binds_msg ambig_msg) } + ; return (ctxt, cannot_resolve_msg rdr_env is_ambig binds_msg ambig_msg) } | not safe_haskell -- Some matches => overlap errors = return (ctxt, overlap_msg) @@ -1012,8 +1011,8 @@ mk_dict_err ctxt (ct, (matches, unifiers, safe_haskell)) givens = getUserGivens ctxt all_tyvars = all isTyVarTy tys - cannot_resolve_msg safe_mod rdr_env has_ambig_tvs binds_msg ambig_msg - = vcat [ addArising orig (no_inst_msg $$ coercible_explanation safe_mod rdr_env) + cannot_resolve_msg rdr_env has_ambig_tvs binds_msg ambig_msg + = vcat [ addArising orig (no_inst_msg $$ coercible_explanation rdr_env) , vcat (pp_givens givens) , ppWhen (has_ambig_tvs && not (null unifiers && null givens)) (vcat [ ambig_msg, binds_msg, potential_msg ]) @@ -1138,27 +1137,12 @@ mk_dict_err ctxt (ct, (matches, unifiers, safe_haskell)) -- This function tries to reconstruct why a "Coercible ty1 ty2" constraint -- is left over. Therefore its logic has to stay in sync with -- getCoericbleInst in TcInteract. See Note [Coercible Instances] - coercible_explanation safe_mod rdr_env + coercible_explanation rdr_env | clas /= coercibleClass = empty | Just (tc1,tyArgs1) <- splitTyConApp_maybe ty1, Just (tc2,tyArgs2) <- splitTyConApp_maybe ty2, tc1 == tc2 = nest 2 $ vcat $ - -- Only for safe haskell: First complain if tc is abstract, only if - -- not check if the type constructors therein are abstract - (if safe_mod - then case tyConAbstractMsg rdr_env tc1 empty of - Just msg -> - [ msg $$ ptext (sLit "as required in SafeHaskell mode") ] - Nothing -> - [ msg - | tc <- tyConsOfTyCon tc1 - , Just msg <- return $ - tyConAbstractMsg rdr_env tc $ - parens $ ptext (sLit "used within") <+> quotes (ppr tc1) - ] - else [] - ) ++ [ fsep [ hsep [ ptext $ sLit "because the", speakNth n, ptext $ sLit "type argument"] , hsep [ ptext $ sLit "of", quotes (ppr tc1), ptext $ sLit "has role Nominal,"] , ptext $ sLit "but the arguments" From git at git.haskell.org Mon Mar 17 15:36:36 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 17 Mar 2014 15:36:36 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Fix incorrect blocksize calculation on Win64 (e2dc029) Message-ID: <20140317153636.9B8F92406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/e2dc02942ba918fab0fca26596882ba2990b8833/ghc >--------------------------------------------------------------- commit e2dc02942ba918fab0fca26596882ba2990b8833 Author: Kyrill Briantsev Date: Wed Mar 12 14:31:21 2014 -0500 Fix incorrect blocksize calculation on Win64 Fixes #8839 Signed-off-by: Austin Seipp (cherry picked from commit b7e5d722c6811f34253d8202540dd9b0ec1b6766) >--------------------------------------------------------------- e2dc02942ba918fab0fca26596882ba2990b8833 includes/rts/storage/Block.h | 14 ++++++++++++-- 1 file changed, 12 insertions(+), 2 deletions(-) diff --git a/includes/rts/storage/Block.h b/includes/rts/storage/Block.h index 5567bf4..29c081b 100644 --- a/includes/rts/storage/Block.h +++ b/includes/rts/storage/Block.h @@ -9,16 +9,26 @@ #ifndef RTS_STORAGE_BLOCK_H #define RTS_STORAGE_BLOCK_H +#include "ghcconfig.h" + /* The actual block and megablock-size constants are defined in * includes/Constants.h, all constants here are derived from these. */ /* Block related constants (BLOCK_SHIFT is defined in Constants.h) */ +#if SIZEOF_LONG == SIZEOF_VOID_P +#define UNIT 1UL +#elif SIZEOF_LONG_LONG == SIZEOF_VOID_P +#define UNIT 1ULL +#else +#error "Size of pointer is suspicious." +#endif + #ifdef CMINUSMINUS #define BLOCK_SIZE (1< Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/e20210668262a0abe3843aa654957420ba5437ef/ghc >--------------------------------------------------------------- commit e20210668262a0abe3843aa654957420ba5437ef Author: Joachim Breitner Date: Fri Mar 14 12:51:37 2014 +0100 Document Coercible in the user guide as a subsection of "Equality constraints", containing references to the module's haddock and to the paper. Fixes #8888 (cherry picked from commit 1e36a386042248523de69ad6b02c43a6631ed5d0) >--------------------------------------------------------------- e20210668262a0abe3843aa654957420ba5437ef docs/users_guide/glasgow_exts.xml | 15 +++++++++++++++ 1 file changed, 15 insertions(+) diff --git a/docs/users_guide/glasgow_exts.xml b/docs/users_guide/glasgow_exts.xml index 9910d2b..4707807 100644 --- a/docs/users_guide/glasgow_exts.xml +++ b/docs/users_guide/glasgow_exts.xml @@ -6708,6 +6708,21 @@ class (F a ~ b) => C a b where with the class head. Method signatures are not affected by that process. + + + The <literal>Coercible</literal> constraint + + The constraint Coercible t1 t2 is similar to t1 ~ + t2, but denotes representational equality between + t1 and t2 in the sense of Roles + (). It is exported by + Data.Coerce, + which also contains the documentation. More details and discussion can be found in + the paper + Safe Coercions". + + + From git at git.haskell.org Mon Mar 17 15:36:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 17 Mar 2014 15:36:43 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Fix #8884. (a78d602) Message-ID: <20140317153643.6890F2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/a78d60201e126f2533752041538a67385b2a081d/ghc >--------------------------------------------------------------- commit a78d60201e126f2533752041538a67385b2a081d Author: Richard Eisenberg Date: Thu Mar 13 15:48:56 2014 -0400 Fix #8884. There were two unrelated errors fixed here: 1) Make sure that only the *result kind* is reified when reifying a type family. Previously, the whole kind was reified, which defies the TH spec. 2) Omit kind patterns in equations. (cherry picked from commit 8c5ea91d68cdc79b413e05f7dacfd052f5de8c64) Conflicts: testsuite/tests/th/all.T >--------------------------------------------------------------- a78d60201e126f2533752041538a67385b2a081d compiler/typecheck/TcSplice.lhs | 19 +++++++++++++------ testsuite/tests/th/T7477.stderr | 2 +- testsuite/tests/th/T8884.hs | 21 +++++++++++++++++++++ testsuite/tests/th/T8884.stderr | 3 +++ testsuite/tests/th/TH_reifyDecl1.stderr | 12 ++++++------ testsuite/tests/th/all.T | 1 + 6 files changed, 45 insertions(+), 13 deletions(-) diff --git a/compiler/typecheck/TcSplice.lhs b/compiler/typecheck/TcSplice.lhs index 0a47da1..4dbf2d3 100644 --- a/compiler/typecheck/TcSplice.lhs +++ b/compiler/typecheck/TcSplice.lhs @@ -1194,7 +1194,8 @@ reifyThing thing = pprPanic "reifyThing" (pprTcTyThingCategory thing) ------------------------------------------- reifyAxBranch :: CoAxBranch -> TcM TH.TySynEqn reifyAxBranch (CoAxBranch { cab_lhs = args, cab_rhs = rhs }) - = do { args' <- mapM reifyType args + -- remove kind patterns (#8884) + = do { args' <- mapM reifyType (filter (not . isKind) args) ; rhs' <- reifyType rhs ; return (TH.TySynEqn args' rhs') } @@ -1210,10 +1211,15 @@ reifyTyCon tc = return (TH.PrimTyConI (reifyName tc) (tyConArity tc) (isUnLiftedTyCon tc)) | isFamilyTyCon tc - = do { let tvs = tyConTyVars tc - kind = tyConKind tc - ; kind' <- if isLiftedTypeKind kind then return Nothing - else fmap Just (reifyKind kind) + = do { let tvs = tyConTyVars tc + kind = tyConKind tc + + -- we need the *result kind* (see #8884) + (kvs, mono_kind) = splitForAllTys kind + -- tyConArity includes *kind* params + (_, res_kind) = splitKindFunTysN (tyConArity tc - length kvs) + mono_kind + ; kind' <- fmap Just (reifyKind res_kind) ; tvs' <- reifyTyVars tvs ; flav' <- reifyFamFlavour tc @@ -1315,7 +1321,8 @@ reifyFamilyInstance (FamInst { fi_flavor = flavor , fi_rhs = rhs }) = case flavor of SynFamilyInst -> - do { th_lhs <- reifyTypes lhs + -- remove kind patterns (#8884) + do { th_lhs <- reifyTypes (filter (not . isKind) lhs) ; th_rhs <- reifyType rhs ; return (TH.TySynInstD (reifyName fam) (TH.TySynEqn th_lhs th_rhs)) } diff --git a/testsuite/tests/th/T7477.stderr b/testsuite/tests/th/T7477.stderr index f6a9e0d..f94de68 100644 --- a/testsuite/tests/th/T7477.stderr +++ b/testsuite/tests/th/T7477.stderr @@ -1,3 +1,3 @@ T7477.hs:10:4: Warning: - type instance T7477.F GHC.Prim.* GHC.Types.Int = GHC.Types.Bool + type instance T7477.F GHC.Types.Int = GHC.Types.Bool diff --git a/testsuite/tests/th/T8884.hs b/testsuite/tests/th/T8884.hs new file mode 100644 index 0000000..782bf90 --- /dev/null +++ b/testsuite/tests/th/T8884.hs @@ -0,0 +1,21 @@ +{-# LANGUAGE TemplateHaskell, TypeFamilies, PolyKinds #-} + +module T8884 where + +import Language.Haskell.TH + +type family Foo a where + Foo x = x + +type family Baz (a :: k) +type instance Baz x = x + +$( do FamilyI foo@(ClosedTypeFamilyD _ tvbs1 m_kind1 eqns1) [] <- reify ''Foo + FamilyI baz@(FamilyD TypeFam _ tvbs2 m_kind2) + [inst@(TySynInstD _ eqn2)] <- reify ''Baz + runIO $ putStrLn $ pprint foo + runIO $ putStrLn $ pprint baz + runIO $ putStrLn $ pprint inst + return [ ClosedTypeFamilyD (mkName "Foo'") tvbs1 m_kind1 eqns1 + , FamilyD TypeFam (mkName "Baz'") tvbs2 m_kind2 + , TySynInstD (mkName "Baz'") eqn2 ] ) \ No newline at end of file diff --git a/testsuite/tests/th/T8884.stderr b/testsuite/tests/th/T8884.stderr new file mode 100644 index 0000000..3c45d0e --- /dev/null +++ b/testsuite/tests/th/T8884.stderr @@ -0,0 +1,3 @@ +type family T8884.Foo (a_0 :: k_1) :: k_1 where T8884.Foo x_2 = x_2 +type family T8884.Baz (a_0 :: k_1) :: * +type instance T8884.Baz x_0 = x_0 diff --git a/testsuite/tests/th/TH_reifyDecl1.stderr b/testsuite/tests/th/TH_reifyDecl1.stderr index 82a4f57..9c3b6da 100644 --- a/testsuite/tests/th/TH_reifyDecl1.stderr +++ b/testsuite/tests/th/TH_reifyDecl1.stderr @@ -21,15 +21,15 @@ class TH_reifyDecl1.C2 a_0 instance TH_reifyDecl1.C2 GHC.Types.Int class TH_reifyDecl1.C3 a_0 instance TH_reifyDecl1.C3 GHC.Types.Int -type family TH_reifyDecl1.AT1 a_0 :: * -> * +type family TH_reifyDecl1.AT1 a_0 :: * type instance TH_reifyDecl1.AT1 GHC.Types.Int = GHC.Types.Bool -data family TH_reifyDecl1.AT2 a_0 :: * -> * +data family TH_reifyDecl1.AT2 a_0 :: * data instance TH_reifyDecl1.AT2 GHC.Types.Int = TH_reifyDecl1.AT2Int -type family TH_reifyDecl1.TF1 a_0 :: * -> * -type family TH_reifyDecl1.TF2 a_0 :: * -> * +type family TH_reifyDecl1.TF1 a_0 :: * +type family TH_reifyDecl1.TF2 a_0 :: * type instance TH_reifyDecl1.TF2 GHC.Types.Bool = GHC.Types.Bool -data family TH_reifyDecl1.DF1 a_0 :: * -> * -data family TH_reifyDecl1.DF2 a_0 :: * -> * +data family TH_reifyDecl1.DF1 a_0 :: * +data family TH_reifyDecl1.DF2 a_0 :: * data instance TH_reifyDecl1.DF2 GHC.Types.Bool = TH_reifyDecl1.DBool diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 3e88970..c39fc6d 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -319,3 +319,4 @@ test('T8633', normal, compile_and_run, ['']) test('T8625', normal, ghci_script, ['T8625.script']) test('T8759', normal, compile_fail, ['-v0']) test('T8759a', normal, compile_fail, ['-v0']) +test('T8884', normal, compile, ['-v0']) From git at git.haskell.org Mon Mar 17 15:36:46 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 17 Mar 2014 15:36:46 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Export runTcInteractive from TcRnDriver, and from GHC (Trac #8878) (24e7387) Message-ID: <20140317153646.ADBE72406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/24e738787feaf024f47251196763f6d6b23565b8/ghc >--------------------------------------------------------------- commit 24e738787feaf024f47251196763f6d6b23565b8 Author: Simon Peyton Jones Date: Thu Mar 13 12:13:49 2014 +0000 Export runTcInteractive from TcRnDriver, and from GHC (Trac #8878) (cherry picked from commit 60bbc0af79ddfe977d93e271b57c2bc25d3fcde6) >--------------------------------------------------------------- 24e738787feaf024f47251196763f6d6b23565b8 compiler/main/GHC.hs | 2 ++ compiler/typecheck/TcRnDriver.lhs | 1 + 2 files changed, 3 insertions(+) diff --git a/compiler/main/GHC.hs b/compiler/main/GHC.hs index 553d1a9..5fe384e 100644 --- a/compiler/main/GHC.hs +++ b/compiler/main/GHC.hs @@ -102,6 +102,7 @@ module GHC ( parseName, RunResult(..), runStmt, runStmtWithLocation, runDecls, runDeclsWithLocation, + runTcInteractive, -- Desired by some clients (Trac #8878) parseImportDecl, SingleStep(..), resume, Resume(resumeStmt, resumeThreadId, resumeBreakInfo, resumeSpan, @@ -257,6 +258,7 @@ module GHC ( import ByteCodeInstr import BreakArray import InteractiveEval +import TcRnDriver ( runTcInteractive ) #endif import HscMain diff --git a/compiler/typecheck/TcRnDriver.lhs b/compiler/typecheck/TcRnDriver.lhs index dad2c67..90d7151 100644 --- a/compiler/typecheck/TcRnDriver.lhs +++ b/compiler/typecheck/TcRnDriver.lhs @@ -13,6 +13,7 @@ module TcRnDriver ( getModuleInterface, tcRnDeclsi, isGHCiMonad, + runTcInteractive, -- Used by GHC API clients (Trac #8878) #endif tcRnLookupName, tcRnGetInfo, From git at git.haskell.org Mon Mar 17 15:36:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 17 Mar 2014 15:36:50 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Unify, rather than match, in GND processing (fixes Trac #8865) (08fede0) Message-ID: <20140317153650.D03392406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/08fede0fe0ff3af4b59b965b172403af0146a460/ghc >--------------------------------------------------------------- commit 08fede0fe0ff3af4b59b965b172403af0146a460 Author: Simon Peyton Jones Date: Mon Mar 10 11:10:21 2014 +0000 Unify, rather than match, in GND processing (fixes Trac #8865) Yet another small way in which polymorphic kinds needs a bit of care See Note [Unify kinds in deriving] in TcDeriv (cherry picked from commit f521a26cb741409011137115d17232df901c3c94) Conflicts: testsuite/tests/deriving/should_compile/all.T >--------------------------------------------------------------- 08fede0fe0ff3af4b59b965b172403af0146a460 compiler/ghci/RtClosureInspect.hs | 3 +- compiler/typecheck/TcDeriv.lhs | 49 ++++++++++++++-------- compiler/types/Unify.lhs | 21 ++++++---- testsuite/tests/deriving/should_compile/T8865.hs | 11 +++++ testsuite/tests/deriving/should_compile/all.T | 1 + 5 files changed, 59 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 08fede0fe0ff3af4b59b965b172403af0146a460 From git at git.haskell.org Mon Mar 17 15:36:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 17 Mar 2014 15:36:52 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Fix incorrect maxStkSize calculation (#8858) (880d813) Message-ID: <20140317153653.37A7D2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/880d81339a6bbc2d147fe72c1ea59070dd6a9b30/ghc >--------------------------------------------------------------- commit 880d81339a6bbc2d147fe72c1ea59070dd6a9b30 Author: Kyrill Briantsev Date: Thu Mar 13 17:00:17 2014 -0500 Fix incorrect maxStkSize calculation (#8858) Signed-off-by: Austin Seipp (cherry picked from commit b99ace39cb2484bfc2d648b55a1a43ed78e4b9a0) >--------------------------------------------------------------- 880d81339a6bbc2d147fe72c1ea59070dd6a9b30 rts/RtsFlags.c | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/rts/RtsFlags.c b/rts/RtsFlags.c index 573e701..af1b204 100644 --- a/rts/RtsFlags.c +++ b/rts/RtsFlags.c @@ -97,12 +97,12 @@ void initRtsFlagsDefaults(void) StgWord64 maxStkSize = 8 * getPhysicalMemorySize() / 10; // if getPhysicalMemorySize fails just move along with an 8MB limit if (maxStkSize == 0) - maxStkSize = (8 * 1024 * 1024) / sizeof(W_); + maxStkSize = 8 * 1024 * 1024; RtsFlags.GcFlags.statsFile = NULL; RtsFlags.GcFlags.giveStats = NO_GC_STATS; - RtsFlags.GcFlags.maxStkSize = maxStkSize; + RtsFlags.GcFlags.maxStkSize = maxStkSize / sizeof(W_); RtsFlags.GcFlags.initialStkSize = 1024 / sizeof(W_); RtsFlags.GcFlags.stkChunkSize = (32 * 1024) / sizeof(W_); RtsFlags.GcFlags.stkChunkBufferSize = (1 * 1024) / sizeof(W_); From git at git.haskell.org Mon Mar 17 15:36:55 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 17 Mar 2014 15:36:55 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: disable shared libs on sparc (linux/solaris) (fixes #8857) (aa8549f) Message-ID: <20140317153655.80BE92406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/aa8549ff4eff1ca28011e530b096f81934bc5d1b/ghc >--------------------------------------------------------------- commit aa8549ff4eff1ca28011e530b096f81934bc5d1b Author: Karel Gardas Date: Fri Mar 7 11:36:37 2014 +0100 disable shared libs on sparc (linux/solaris) (fixes #8857) Signed-off-by: Austin Seipp (cherry picked from commit 623883f1ed0ee11cc925c4590fb09565403fd231) >--------------------------------------------------------------- aa8549ff4eff1ca28011e530b096f81934bc5d1b mk/config.mk.in | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/mk/config.mk.in b/mk/config.mk.in index f24c495..2c997de 100644 --- a/mk/config.mk.in +++ b/mk/config.mk.in @@ -98,7 +98,9 @@ endif NoSharedLibsPlatformList = arm-unknown-linux \ powerpc-unknown-linux \ x86_64-unknown-mingw32 \ - i386-unknown-mingw32 + i386-unknown-mingw32 \ + sparc-sun-solaris2 \ + sparc-unknown-linux ifeq "$(SOLARIS_BROKEN_SHLD)" "YES" NoSharedLibsPlatformList += i386-unknown-solaris2 From git at git.haskell.org Mon Mar 17 15:36:58 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 17 Mar 2014 15:36:58 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: DriverPipeline: Ensure -globalopt is passed to LLVM opt (c8418d1) Message-ID: <20140317153658.0EBD22406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/c8418d1888441f64941d84bac657b6f64445ed70/ghc >--------------------------------------------------------------- commit c8418d1888441f64941d84bac657b6f64445ed70 Author: Ben Gamari Date: Thu Mar 6 21:20:02 2014 +0100 DriverPipeline: Ensure -globalopt is passed to LLVM opt While -O1 and -O2 both include -globalopt, the order in which the passes are run means that aliases aren't resolved which then causes llc to fall over. See GHC bug #8855. Signed-off-by: Austin Seipp (cherry picked from commit b84b5da4430aacd5bf8422b06a861cd0584f99cf) >--------------------------------------------------------------- c8418d1888441f64941d84bac657b6f64445ed70 compiler/main/DriverPipeline.hs | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs index f6d9e03..564edd2 100644 --- a/compiler/main/DriverPipeline.hs +++ b/compiler/main/DriverPipeline.hs @@ -1337,7 +1337,7 @@ runPhase (RealPhase LlvmOpt) input_fn dflags -- passes only, so if the user is passing us extra options we assume -- they know what they are doing and don't get in the way. optFlag = if null (getOpts dflags opt_lo) - then map SysTools.Option $ words (llvmOpts !! opt_lvl) + then map SysTools.Option $ words (llvmOpts ver !! opt_lvl) else [] tbaa | ver < 29 = "" -- no tbaa in 2.8 and earlier | gopt Opt_LlvmTBAA dflags = "--enable-tbaa=true" @@ -1357,7 +1357,11 @@ runPhase (RealPhase LlvmOpt) input_fn dflags where -- we always (unless -optlo specified) run Opt since we rely on it to -- fix up some pretty big deficiencies in the code we generate - llvmOpts = ["-mem2reg -globalopt", "-O1", "-O2"] + llvmOpts ver = [ "-mem2reg -globalopt" + , if ver >= 34 then "-O1 -globalopt" else "-O1" + -- LLVM 3.4 -O1 doesn't eliminate aliases reliably (bug #8855) + , "-O2" + ] ----------------------------------------------------------------------------- -- LlvmLlc phase From git at git.haskell.org Mon Mar 17 15:37:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 17 Mar 2014 15:37:01 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Test #8851. (adbc8c1) Message-ID: <20140317153701.A130C2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/adbc8c1893c3906cdabbcef2890d0cb3c26da86f/ghc >--------------------------------------------------------------- commit adbc8c1893c3906cdabbcef2890d0cb3c26da86f Author: Richard Eisenberg Date: Thu Mar 6 23:44:57 2014 -0500 Test #8851. (cherry picked from commit 1ac91146dc3431742eafd33ed4afc552ca17fb64) Conflicts: testsuite/tests/deriving/should_compile/all.T >--------------------------------------------------------------- adbc8c1893c3906cdabbcef2890d0cb3c26da86f testsuite/tests/deriving/should_compile/T8851.hs | 24 ++++++++++++++++++++++ testsuite/tests/deriving/should_compile/all.T | 1 + 2 files changed, 25 insertions(+) diff --git a/testsuite/tests/deriving/should_compile/T8851.hs b/testsuite/tests/deriving/should_compile/T8851.hs new file mode 100644 index 0000000..84f0ad4 --- /dev/null +++ b/testsuite/tests/deriving/should_compile/T8851.hs @@ -0,0 +1,24 @@ +{-# LANGUAGE GeneralizedNewtypeDeriving #-} + +module T8851 where + +import Control.Applicative + +class Parsing m where + notFollowedBy :: (Monad m, Show a) => m a -> m () + +data Parser a +instance Parsing Parser where + notFollowedBy = undefined + +instance Functor Parser where + fmap = undefined +instance Applicative Parser where + pure = undefined + (<*>) = undefined +instance Monad Parser where + return = undefined + (>>=) = undefined + +newtype MyParser a = MkMP (Parser a) + deriving Parsing \ No newline at end of file diff --git a/testsuite/tests/deriving/should_compile/all.T b/testsuite/tests/deriving/should_compile/all.T index 257a9b2..4c1f545 100644 --- a/testsuite/tests/deriving/should_compile/all.T +++ b/testsuite/tests/deriving/should_compile/all.T @@ -45,3 +45,4 @@ test('T8138', reqlib('primitive'), compile, ['-O2']) test('T8631', normal, compile, ['']) test('T8758', extra_clean(['T8758a.o', 'T8758a.hi']), multimod_compile, ['T8758a', '-v0']) test('T8865', normal, compile, ['']) +test('T8851', expect_broken(8851), compile, ['']) From git at git.haskell.org Mon Mar 17 15:37:03 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 17 Mar 2014 15:37:03 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Improve documentation of standalone deriving (c.f. Trac #8851) (0908f06) Message-ID: <20140317153703.F05E22406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/0908f0629a622b259120cbdaac4f7039359f2fb6/ghc >--------------------------------------------------------------- commit 0908f0629a622b259120cbdaac4f7039359f2fb6 Author: Simon Peyton Jones Date: Mon Mar 10 11:08:37 2014 +0000 Improve documentation of standalone deriving (c.f. Trac #8851) (cherry picked from commit 9d14262299fe721e49eb0efadebca9d095c834b3) >--------------------------------------------------------------- 0908f0629a622b259120cbdaac4f7039359f2fb6 docs/users_guide/glasgow_exts.xml | 28 +++++++++++++++++++++------- 1 file changed, 21 insertions(+), 7 deletions(-) diff --git a/docs/users_guide/glasgow_exts.xml b/docs/users_guide/glasgow_exts.xml index 4707807..5ca544f 100644 --- a/docs/users_guide/glasgow_exts.xml +++ b/docs/users_guide/glasgow_exts.xml @@ -3752,8 +3752,16 @@ GHC now allows stand-alone deriving declarations, enabled by The syntax is identical to that of an ordinary instance declaration apart from (a) the keyword deriving, and (b) the absence of the where part. -Note the following points: + + +However, standalone deriving differs from a deriving clause in a number +of important ways: +The standalone deriving declaration does not need to be in the +same module as the data type declaration. (But be aware of the dangers of +orphan instances (). + + You must supply an explicit context (in the example the context is (Eq a)), exactly as you would in an ordinary instance declaration. @@ -3762,12 +3770,6 @@ attached to a data type declaration, the context is inferred.) -A deriving instance declaration -must obey the same rules concerning form and termination as ordinary instance declarations, -controlled by the same flags; see . - - - Unlike a deriving declaration attached to a data declaration, the instance can be more specific than the data type (assuming you also use @@ -3789,6 +3791,8 @@ declaration attached to a data declaration, GHC does not restrict the form of the data type. Instead, GHC simply generates the appropriate boilerplate code for the specified class, and typechecks it. If there is a type error, it is your problem. (GHC will show you the offending code if it has a type error.) + + The merit of this is that you can derive instances for GADTs and other exotic data types, providing only that the boilerplate code does indeed typecheck. For example: @@ -3804,6 +3808,16 @@ because T is a GADT, but you can generat the instance declaration using stand-alone deriving. + + + +In other ways, however, a standalone deriving obeys the same rules as ordinary deriving: + + +A deriving instance declaration +must obey the same rules concerning form and termination as ordinary instance declarations, +controlled by the same flags; see . + The stand-alone syntax is generalised for newtypes in exactly the same From git at git.haskell.org Mon Mar 17 15:37:06 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 17 Mar 2014 15:37:06 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Recharacterize test according to discussion in #8851. (917e374) Message-ID: <20140317153706.724582406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/917e3743a91f7479bbd54963d17d3621cfd064ff/ghc >--------------------------------------------------------------- commit 917e3743a91f7479bbd54963d17d3621cfd064ff Author: Richard Eisenberg Date: Thu Mar 13 15:12:27 2014 -0400 Recharacterize test according to discussion in #8851. (cherry picked from commit 8ee6162e9a3377cd4c79f49b63f92046b0d5c708) Conflicts: testsuite/tests/deriving/should_compile/all.T >--------------------------------------------------------------- 917e3743a91f7479bbd54963d17d3621cfd064ff testsuite/tests/deriving/should_compile/all.T | 1 - .../deriving/{should_compile => should_fail}/T8851.hs | 0 testsuite/tests/deriving/should_fail/T8851.stderr | 12 ++++++++++++ testsuite/tests/deriving/should_fail/all.T | 1 + 4 files changed, 13 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/deriving/should_compile/all.T b/testsuite/tests/deriving/should_compile/all.T index 4c1f545..257a9b2 100644 --- a/testsuite/tests/deriving/should_compile/all.T +++ b/testsuite/tests/deriving/should_compile/all.T @@ -45,4 +45,3 @@ test('T8138', reqlib('primitive'), compile, ['-O2']) test('T8631', normal, compile, ['']) test('T8758', extra_clean(['T8758a.o', 'T8758a.hi']), multimod_compile, ['T8758a', '-v0']) test('T8865', normal, compile, ['']) -test('T8851', expect_broken(8851), compile, ['']) diff --git a/testsuite/tests/deriving/should_compile/T8851.hs b/testsuite/tests/deriving/should_fail/T8851.hs similarity index 100% rename from testsuite/tests/deriving/should_compile/T8851.hs rename to testsuite/tests/deriving/should_fail/T8851.hs diff --git a/testsuite/tests/deriving/should_fail/T8851.stderr b/testsuite/tests/deriving/should_fail/T8851.stderr new file mode 100644 index 0000000..348f1f1 --- /dev/null +++ b/testsuite/tests/deriving/should_fail/T8851.stderr @@ -0,0 +1,12 @@ + +T8851.hs:24:12: + Could not coerce from ?Monad Parser? to ?Monad MyParser? + because the first type argument of ?Monad? has role Nominal, + but the arguments ?Parser? and ?MyParser? differ + arising from the coercion of the method ?notFollowedBy? from type + ?forall a. (Monad Parser, Show a) => Parser a -> Parser ()? to type + ?forall a. (Monad MyParser, Show a) => MyParser a -> MyParser ()? + Possible fix: + use a standalone 'deriving instance' declaration, + so you can specify the instance context yourself + When deriving the instance for (Parsing MyParser) diff --git a/testsuite/tests/deriving/should_fail/all.T b/testsuite/tests/deriving/should_fail/all.T index 1ffa5fc..d503b6e 100644 --- a/testsuite/tests/deriving/should_fail/all.T +++ b/testsuite/tests/deriving/should_fail/all.T @@ -49,3 +49,4 @@ test('T7148a', normal, compile_fail, ['']) test('T7800', normal, multimod_compile_fail, ['T7800','']) test('T5498', normal, compile_fail, ['']) test('T6147', normal, compile_fail, ['']) +test('T8851', normal, compile_fail, ['']) From git at git.haskell.org Mon Mar 17 15:37:08 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 17 Mar 2014 15:37:08 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Attach the right location to pattern synonym error message (fixes Trac #8841) (50af107) Message-ID: <20140317153708.E43892406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/50af1072cf63f520c8a8b0ba225b2fec1dc6deb1/ghc >--------------------------------------------------------------- commit 50af1072cf63f520c8a8b0ba225b2fec1dc6deb1 Author: Simon Peyton Jones Date: Thu Mar 6 11:32:55 2014 +0000 Attach the right location to pattern synonym error message (fixes Trac #8841) (cherry picked from commit 96daafc3305a691590b88c1175a8f45e5d327471) >--------------------------------------------------------------- 50af1072cf63f520c8a8b0ba225b2fec1dc6deb1 compiler/typecheck/TcPatSyn.lhs | 9 ++++----- 1 file changed, 4 insertions(+), 5 deletions(-) diff --git a/compiler/typecheck/TcPatSyn.lhs b/compiler/typecheck/TcPatSyn.lhs index a126f0f..703e59d 100644 --- a/compiler/typecheck/TcPatSyn.lhs +++ b/compiler/typecheck/TcPatSyn.lhs @@ -186,7 +186,7 @@ tcPatSynWrapper lname lpat dir args univ_tvs ex_tvs theta pat_ty (Unidirectional, _) -> return Nothing (ImplicitBidirectional, Nothing) -> - cannotInvertPatSynErr (unLoc lpat) + cannotInvertPatSynErr lpat (ImplicitBidirectional, Just lexpr) -> fmap Just $ tc_pat_syn_wrapper_from_expr lname lexpr args univ_tvs ex_tvs theta pat_ty } @@ -281,10 +281,9 @@ asPatInPatSynErr pat hang (ptext (sLit "Pattern synonym definition cannot contain as-patterns (@):")) 2 (ppr pat) --- TODO: Highlight sub-pattern that causes the problem -cannotInvertPatSynErr :: OutputableBndr name => Pat name -> TcM a -cannotInvertPatSynErr pat - = failWithTc $ +cannotInvertPatSynErr :: OutputableBndr name => LPat name -> TcM a +cannotInvertPatSynErr (L loc pat) + = setSrcSpan loc $ failWithTc $ hang (ptext (sLit "Right-hand side of bidirectional pattern synonym cannot be used as an expression")) 2 (ppr pat) From git at git.haskell.org Mon Mar 17 15:37:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 17 Mar 2014 15:37:11 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Test for Trac #8841 now works (0c3a1ea) Message-ID: <20140317153712.3D6AF2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/0c3a1eacb9313c5d7cd8d8802079ad4e78605be0/ghc >--------------------------------------------------------------- commit 0c3a1eacb9313c5d7cd8d8802079ad4e78605be0 Author: Simon Peyton Jones Date: Thu Mar 6 12:13:05 2014 +0000 Test for Trac #8841 now works (cherry picked from commit bf9bf602399eca30ca522ae5bae52d4f3ec1ab88) >--------------------------------------------------------------- 0c3a1eacb9313c5d7cd8d8802079ad4e78605be0 testsuite/tests/patsyn/should_fail/unidir.stderr | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/patsyn/should_fail/unidir.stderr b/testsuite/tests/patsyn/should_fail/unidir.stderr index ea019bc..b116115 100644 --- a/testsuite/tests/patsyn/should_fail/unidir.stderr +++ b/testsuite/tests/patsyn/should_fail/unidir.stderr @@ -1,4 +1,4 @@ -unidir.hs:1:1: +unidir.hs:4:18: Right-hand side of bidirectional pattern synonym cannot be used as an expression x : _ From git at git.haskell.org Mon Mar 17 15:37:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 17 Mar 2014 15:37:24 +0000 (UTC) Subject: [commit: packages/ghc-prim] ghc-7.8: Update Coercible docs due to Safe Haskell adjustment (a011e6d) Message-ID: <20140317153724.C56F92406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc-prim On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/a011e6d0ce68e243751d396f39715040b2962bde/ghc-prim >--------------------------------------------------------------- commit a011e6d0ce68e243751d396f39715040b2962bde Author: Joachim Breitner Date: Fri Mar 14 09:26:12 2014 +0100 Update Coercible docs due to Safe Haskell adjustment This should go with [59722295bb8da8f01d37356fbed6aef7321a8195/ghc], see bug #8826. (cherry picked from commit db4f5e5245d5b24a8f0a06a85ded89c6124fb4c7) >--------------------------------------------------------------- a011e6d0ce68e243751d396f39715040b2962bde GHC/Types.hs | 4 ---- 1 file changed, 4 deletions(-) diff --git a/GHC/Types.hs b/GHC/Types.hs index 96673e1..310c04d 100644 --- a/GHC/Types.hs +++ b/GHC/Types.hs @@ -116,10 +116,6 @@ data (~) a b = Eq# ((~#) a b) -- @Coercible@ instance themself, and the @phantom@ type arguments can be -- changed arbitrarily. -- --- In SafeHaskell code, this instance is only usable if the constructors of --- every type constructor used in the definition of @D@ (including --- those of @D@ itself) are in scope. --- -- The third kind of instance exists for every @newtype NT = MkNT T@ and -- comes in two variants, namely -- From git at git.haskell.org Mon Mar 17 15:37:26 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 17 Mar 2014 15:37:26 +0000 (UTC) Subject: [commit: packages/ghc-prim] ghc-7.8: Refer to the coercible paper in Coercible' docs (ac633f2) Message-ID: <20140317153726.E7DCE2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc-prim On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/ac633f2b92841bbba7c7cb0b9e85b5092a7c80fb/ghc-prim >--------------------------------------------------------------- commit ac633f2b92841bbba7c7cb0b9e85b5092a7c80fb Author: Joachim Breitner Date: Fri Mar 14 12:41:46 2014 +0100 Refer to the coercible paper in Coercible' docs Implements parts of #8888. (cherry picked from commit fc7aaf57a33ab07b70628c75fcf134fdf4e701e5) >--------------------------------------------------------------- ac633f2b92841bbba7c7cb0b9e85b5092a7c80fb GHC/Types.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/GHC/Types.hs b/GHC/Types.hs index 310c04d..a582677 100644 --- a/GHC/Types.hs +++ b/GHC/Types.hs @@ -133,6 +133,10 @@ data (~) a b = Eq# ((~#) a b) -- -- @type role Set nominal@ -- +-- For more details about this feature, please refer to +-- +-- by Joachim Breitner, Richard A. Eisenberg, Simon Peyton Jones and Stephanie Weirich. +-- -- /Since: 4.7.0.0/ data Coercible a b = MkCoercible ((~#) a b) From git at git.haskell.org Tue Mar 18 00:45:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Mar 2014 00:45:56 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: config.mk.in: ARM now supports dynamic linking with the LLVM backend (abb86ad) Message-ID: <20140318004556.A01ED2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/abb86adf7f749b3d44887d28bc96b43c5a1e0631/ghc >--------------------------------------------------------------- commit abb86adf7f749b3d44887d28bc96b43c5a1e0631 Author: Ben Gamari Date: Thu Mar 6 21:22:28 2014 +0100 config.mk.in: ARM now supports dynamic linking with the LLVM backend Signed-off-by: Austin Seipp (cherry picked from commit d574fcbba09fd6c9d10a79e19daf5f15bb0a6cde) >--------------------------------------------------------------- abb86adf7f749b3d44887d28bc96b43c5a1e0631 mk/config.mk.in | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/mk/config.mk.in b/mk/config.mk.in index 2c997de..fef1fb8 100644 --- a/mk/config.mk.in +++ b/mk/config.mk.in @@ -95,8 +95,7 @@ TargetElf = YES endif # Some platforms don't support shared libraries -NoSharedLibsPlatformList = arm-unknown-linux \ - powerpc-unknown-linux \ +NoSharedLibsPlatformList = powerpc-unknown-linux \ x86_64-unknown-mingw32 \ i386-unknown-mingw32 \ sparc-sun-solaris2 \ From git at git.haskell.org Tue Mar 18 06:22:46 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Mar 2014 06:22:46 +0000 (UTC) Subject: [commit: ghc] master: Add some documentation about type-level literals. (3099e40) Message-ID: <20140318062246.371772406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3099e40d2737172c746a6456ddcd34b54e120aa0/ghc >--------------------------------------------------------------- commit 3099e40d2737172c746a6456ddcd34b54e120aa0 Author: Iavor S. Diatchki Date: Mon Mar 17 23:19:16 2014 -0700 Add some documentation about type-level literals. I moved the "promoted literals" sub-section into a separate section, as many folks were not finding the docs. I also added some additional paragraphs describing the current state of the feature. >--------------------------------------------------------------- 3099e40d2737172c746a6456ddcd34b54e120aa0 docs/users_guide/glasgow_exts.xml | 178 ++++++++++++++++++++++++++++--------- 1 file changed, 135 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 3099e40d2737172c746a6456ddcd34b54e120aa0 From git at git.haskell.org Tue Mar 18 10:16:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Mar 2014 10:16:01 +0000 (UTC) Subject: [commit: packages/Win32] ghc-head: add support from GetFileAttributesEx (low level only) (66437bf) Message-ID: <20140318101601.97B852406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/Win32 On branch : ghc-head Link : http://git.haskell.org/packages/Win32.git/commitdiff/66437bfa67a6e63e092f9dc8b96c586311c5c58b >--------------------------------------------------------------- commit 66437bfa67a6e63e092f9dc8b96c586311c5c58b Author: Marios Titas Date: Thu Jun 6 19:48:09 2013 -0400 add support from GetFileAttributesEx (low level only) >--------------------------------------------------------------- 66437bfa67a6e63e092f9dc8b96c586311c5c58b System/Win32/File.hsc | 44 ++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 44 insertions(+) diff --git a/System/Win32/File.hsc b/System/Win32/File.hsc index b0e0ad2..b419875 100644 --- a/System/Win32/File.hsc +++ b/System/Win32/File.hsc @@ -207,6 +207,16 @@ type FileType = DWORD ---------------------------------------------------------------- +newtype GET_FILEEX_INFO_LEVELS = GET_FILEEX_INFO_LEVELS (#type GET_FILEEX_INFO_LEVELS) + deriving (Eq, Ord) + +#{enum GET_FILEEX_INFO_LEVELS, GET_FILEEX_INFO_LEVELS + , getFileExInfoStandard = GetFileExInfoStandard + , getFileExMaxInfoLevel = GetFileExMaxInfoLevel + } + +---------------------------------------------------------------- + type LPSECURITY_ATTRIBUTES = Ptr () type MbLPSECURITY_ATTRIBUTES = Maybe LPSECURITY_ATTRIBUTES @@ -256,6 +266,37 @@ instance Storable BY_HANDLE_FILE_INFORMATION where (dwordsToDdword (fshi,fslo)) link (dwordsToDdword (idhi,idlo)) ---------------------------------------------------------------- + +data WIN32_FILE_ATTRIBUTE_DATA = WIN32_FILE_ATTRIBUTE_DATA + { fadFileAttributes :: DWORD + , fadCreationTime , fadLastAccessTime , fadLastWriteTime :: FILETIME + , fadFileSize :: DDWORD + } deriving (Show) + +instance Storable WIN32_FILE_ATTRIBUTE_DATA where + sizeOf = const (#size WIN32_FILE_ATTRIBUTE_DATA) + alignment = sizeOf + poke buf ad = do + (#poke WIN32_FILE_ATTRIBUTE_DATA, dwFileAttributes) buf (fadFileAttributes ad) + (#poke WIN32_FILE_ATTRIBUTE_DATA, ftCreationTime) buf (fadCreationTime ad) + (#poke WIN32_FILE_ATTRIBUTE_DATA, ftLastAccessTime) buf (fadLastAccessTime ad) + (#poke WIN32_FILE_ATTRIBUTE_DATA, ftLastWriteTime) buf (fadLastWriteTime ad) + (#poke WIN32_FILE_ATTRIBUTE_DATA, nFileSizeHigh) buf sizeHi + (#poke WIN32_FILE_ATTRIBUTE_DATA, nFileSizeLow) buf sizeLo + where + (sizeHi,sizeLo) = ddwordToDwords $ fadFileSize ad + + peek buf = do + attr <- (#peek WIN32_FILE_ATTRIBUTE_DATA, dwFileAttributes) buf + ctim <- (#peek WIN32_FILE_ATTRIBUTE_DATA, ftCreationTime) buf + lati <- (#peek WIN32_FILE_ATTRIBUTE_DATA, ftLastAccessTime) buf + lwti <- (#peek WIN32_FILE_ATTRIBUTE_DATA, ftLastWriteTime) buf + fshi <- (#peek WIN32_FILE_ATTRIBUTE_DATA, nFileSizeHigh) buf + fslo <- (#peek WIN32_FILE_ATTRIBUTE_DATA, nFileSizeLow) buf + return $ WIN32_FILE_ATTRIBUTE_DATA attr ctim lati lwti + (dwordsToDdword (fshi,fslo)) + +---------------------------------------------------------------- -- File operations ---------------------------------------------------------------- @@ -421,6 +462,9 @@ getFileAttributes name = foreign import WINDOWS_CCONV unsafe "windows.h GetFileAttributesW" c_GetFileAttributes :: LPCTSTR -> IO FileAttributeOrFlag +foreign import WINDOWS_CCONV unsafe "windows.h GetFileAttributesExW" + c_GetFileAttributesEx :: LPCTSTR -> GET_FILEEX_INFO_LEVELS -> Ptr a -> IO BOOL + getFileInformationByHandle :: HANDLE -> IO BY_HANDLE_FILE_INFORMATION getFileInformationByHandle h = alloca $ \res -> do failIfFalseWithRetry_ "GetFileInformationByHandle" $ c_GetFileInformationByHandle h res From git at git.haskell.org Tue Mar 18 10:16:03 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Mar 2014 10:16:03 +0000 (UTC) Subject: [commit: packages/Win32] ghc-head: wrap GetFileAttributesEx with a high level function (263c97f) Message-ID: <20140318101603.90E032406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/Win32 On branch : ghc-head Link : http://git.haskell.org/packages/Win32.git/commitdiff/263c97f33d360ec9d54fc21996e5d2759f3af0c6 >--------------------------------------------------------------- commit 263c97f33d360ec9d54fc21996e5d2759f3af0c6 Author: Marios Titas Date: Thu Jun 6 19:50:06 2013 -0400 wrap GetFileAttributesEx with a high level function >--------------------------------------------------------------- 263c97f33d360ec9d54fc21996e5d2759f3af0c6 System/Win32/File.hsc | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/System/Win32/File.hsc b/System/Win32/File.hsc index b419875..d17c042 100644 --- a/System/Win32/File.hsc +++ b/System/Win32/File.hsc @@ -462,6 +462,12 @@ getFileAttributes name = foreign import WINDOWS_CCONV unsafe "windows.h GetFileAttributesW" c_GetFileAttributes :: LPCTSTR -> IO FileAttributeOrFlag +getFileAttributesExStandard :: String -> IO WIN32_FILE_ATTRIBUTE_DATA +getFileAttributesExStandard name = alloca $ \res -> do + withTString name $ \ c_name -> + failIfFalseWithRetry_ "getFileAttributesExStandard" $ + c_GetFileAttributesEx c_name getFileExInfoStandard res + peek res foreign import WINDOWS_CCONV unsafe "windows.h GetFileAttributesExW" c_GetFileAttributesEx :: LPCTSTR -> GET_FILEEX_INFO_LEVELS -> Ptr a -> IO BOOL From git at git.haskell.org Tue Mar 18 10:16:05 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Mar 2014 10:16:05 +0000 (UTC) Subject: [commit: packages/Win32] ghc-head: Use regCreateKey to be more robust when registry entry does not exist. (8862fb6) Message-ID: <20140318101605.895E42406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/Win32 On branch : ghc-head Link : http://git.haskell.org/packages/Win32.git/commitdiff/8862fb620e5af0183259ae3e642e582cc8157334 >--------------------------------------------------------------- commit 8862fb620e5af0183259ae3e642e582cc8157334 Author: Edward Z. Yang Date: Wed Sep 4 19:40:07 2013 -0700 Use regCreateKey to be more robust when registry entry does not exist. Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- 8862fb620e5af0183259ae3e642e582cc8157334 tests/registry001.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/tests/registry001.hs b/tests/registry001.hs index 9a789d2..f65c5cd 100644 --- a/tests/registry001.hs +++ b/tests/registry001.hs @@ -7,9 +7,9 @@ name = "test_registry001" -- Create, read, and delete a value (test for bug #3241) main = do - k1 <- regOpenKey hKEY_CURRENT_USER "Software" - k2 <- regOpenKey k1 "Haskell" - k3 <- regOpenKey k2 "GHC" + k1 <- regCreateKey hKEY_CURRENT_USER "Software" + k2 <- regCreateKey k1 "Haskell" + k3 <- regCreateKey k2 "GHC" flip finally (regDeleteValue k3 name) $ do regSetStringValue k3 name x r <- regQueryValue k3 (Just name) From git at git.haskell.org Tue Mar 18 10:16:07 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Mar 2014 10:16:07 +0000 (UTC) Subject: [commit: packages/Win32] ghc-head: Replace PROCESSENTRY32 -> PROCESSENTRY32W (b5392c3) Message-ID: <20140318101607.9DA2A2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/Win32 On branch : ghc-head Link : http://git.haskell.org/packages/Win32.git/commitdiff/b5392c3d3bd761990d54fd0c37e3f259578d896c >--------------------------------------------------------------- commit b5392c3d3bd761990d54fd0c37e3f259578d896c Author: Adrian Keet Date: Wed Nov 6 00:13:43 2013 -0800 Replace PROCESSENTRY32 -> PROCESSENTRY32W >--------------------------------------------------------------- b5392c3d3bd761990d54fd0c37e3f259578d896c System/Win32/Process.hsc | 14 +++++++------- 1 file changed, 7 insertions(+), 7 deletions(-) diff --git a/System/Win32/Process.hsc b/System/Win32/Process.hsc index e2f4ddf..cffc482 100644 --- a/System/Win32/Process.hsc +++ b/System/Win32/Process.hsc @@ -105,16 +105,16 @@ withTh32Snap f p = bracket (createToolhelp32Snapshot f p) (closeHandle) peekProcessEntry32 :: Ptr ProcessEntry32 -> IO ProcessEntry32 peekProcessEntry32 buf = liftM5 (,,,,) - ((#peek PROCESSENTRY32, th32ProcessID) buf) - ((#peek PROCESSENTRY32, cntThreads) buf) - ((#peek PROCESSENTRY32, th32ParentProcessID) buf) - ((#peek PROCESSENTRY32, pcPriClassBase) buf) - (peekTString $ (#ptr PROCESSENTRY32, szExeFile) buf) + ((#peek PROCESSENTRY32W, th32ProcessID) buf) + ((#peek PROCESSENTRY32W, cntThreads) buf) + ((#peek PROCESSENTRY32W, th32ParentProcessID) buf) + ((#peek PROCESSENTRY32W, pcPriClassBase) buf) + (peekTString $ (#ptr PROCESSENTRY32W, szExeFile) buf) -- | Enumerate processes using Process32First and Process32Next th32SnapEnumProcesses :: Th32SnapHandle -> IO [ProcessEntry32] -th32SnapEnumProcesses h = allocaBytes (#size PROCESSENTRY32) $ \pe -> do - (#poke PROCESSENTRY32, dwSize) pe ((#size PROCESSENTRY32)::DWORD) +th32SnapEnumProcesses h = allocaBytes (#size PROCESSENTRY32W) $ \pe -> do + (#poke PROCESSENTRY32W, dwSize) pe ((#size PROCESSENTRY32W)::DWORD) ok <- c_Process32First h pe readAndNext ok pe [] where From git at git.haskell.org Tue Mar 18 10:16:09 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Mar 2014 10:16:09 +0000 (UTC) Subject: [commit: packages/Win32] ghc-head: Partial support for base 4.6 (68955ee) Message-ID: <20140318101609.B13922406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/Win32 On branch : ghc-head Link : http://git.haskell.org/packages/Win32.git/commitdiff/68955ee0850c749c81f5123f72ca57a9189bbe74 >--------------------------------------------------------------- commit 68955ee0850c749c81f5123f72ca57a9189bbe74 Author: Bryan O'Sullivan Date: Tue Feb 4 12:14:11 2014 -0800 Partial support for base 4.6 >--------------------------------------------------------------- 68955ee0850c749c81f5123f72ca57a9189bbe74 System/Win32/Types.hs | 30 +++++++++++++++++++++++------- Win32.cabal | 2 +- 2 files changed, 24 insertions(+), 8 deletions(-) diff --git a/System/Win32/Types.hs b/System/Win32/Types.hs old mode 100644 new mode 100755 index 5b15b93..359e42f --- a/System/Win32/Types.hs +++ b/System/Win32/Types.hs @@ -20,14 +20,30 @@ module System.Win32.Types , nullPtr ) where -import Data.Maybe -import Foreign -import Foreign.C -import Control.Exception -import System.IO.Error -import System.IO.Unsafe -import Data.Char +import Control.Exception (throw) +import Data.Bits (shiftL, shiftR, (.|.), (.&.)) +import Data.Char (isSpace) +import Data.Int (Int32, Int64) +import Data.Maybe (fromMaybe) +import Data.Word (Word, Word8, Word16, Word32, Word64) +import Foreign.C.Error (getErrno, errnoToIOError) +import Foreign.C.String (newCWString, withCWStringLen) +import Foreign.C.String (peekCWString, peekCWStringLen, withCWString) +import Foreign.C.Types (CChar, CUChar, CWchar) +import Foreign.ForeignPtr (ForeignPtr, newForeignPtr, newForeignPtr_) +import Foreign.Ptr (FunPtr, Ptr, nullPtr) import Numeric (showHex) +import System.IO.Error (ioeSetErrorString) +import System.IO.Unsafe (unsafePerformIO) + +#if MIN_VERSION_base(4,7,0) +import Data.Bits (finiteBitSize) +#else +import Data.Bits (Bits, bitSize) + +finiteBitSize :: (Bits a) => a -> Int +finiteBitSize = bitSize +#endif #include "windows_cconv.h" diff --git a/Win32.cabal b/Win32.cabal old mode 100644 new mode 100755 index 00e0c25..4edf5b8 --- a/Win32.cabal +++ b/Win32.cabal @@ -17,7 +17,7 @@ extra-source-files: include/Win32Aux.h include/win32debug.h include/windows_cconv.h Library - build-depends: base >= 4.7 && < 5, bytestring + build-depends: base >= 4.6 && < 5, bytestring ghc-options: -Wall -fno-warn-name-shadowing cc-options: -fno-strict-aliasing exposed-modules: From git at git.haskell.org Tue Mar 18 10:16:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Mar 2014 10:16:11 +0000 (UTC) Subject: [commit: packages/Win32] ghc-head: Complete support for base 4.6 (e2d75e9) Message-ID: <20140318101611.D9D362406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/Win32 On branch : ghc-head Link : http://git.haskell.org/packages/Win32.git/commitdiff/e2d75e9bc3faf7377ae27601265795878f9fa44c >--------------------------------------------------------------- commit e2d75e9bc3faf7377ae27601265795878f9fa44c Author: Bryan O'Sullivan Date: Tue Feb 4 12:14:34 2014 -0800 Complete support for base 4.6 We now make a lot of imports more explicit, too. >--------------------------------------------------------------- e2d75e9bc3faf7377ae27601265795878f9fa44c Graphics/Win32/Control.hsc | 16 +++++++++------- Graphics/Win32/Window.hsc | 26 ++++++++++++++++++-------- System/Win32/Registry.hsc | 20 ++++++++++++++------ 3 files changed, 41 insertions(+), 21 deletions(-) diff --git a/Graphics/Win32/Control.hsc b/Graphics/Win32/Control.hsc old mode 100644 new mode 100755 index 84842b8..6e680ab --- a/Graphics/Win32/Control.hsc +++ b/Graphics/Win32/Control.hsc @@ -17,13 +17,15 @@ module Graphics.Win32.Control where -import Graphics.Win32.GDI.Types -import Graphics.Win32.Window -import System.Win32.Types -import Graphics.Win32.Message - -import Foreign -import System.IO.Unsafe +import Data.Bits ((.|.)) +import Graphics.Win32.GDI.Types (HMENU, HWND) +import Graphics.Win32.Message (WindowMessage) +import Graphics.Win32.Window (ClassName, Pos, WindowStyle, maybePos) +import Graphics.Win32.Window (c_CreateWindowEx) +import System.IO.Unsafe (unsafePerformIO) +import System.Win32.Types (HANDLE, UINT, maybePtr, newTString, withTString) +import System.Win32.Types (failIfFalse_, failIfNull, failIfZero) +import Foreign.Ptr (nullPtr) ##include "windows_cconv.h" diff --git a/Graphics/Win32/Key.hsc b/Graphics/Win32/Key.hsc old mode 100644 new mode 100755 diff --git a/Graphics/Win32/Window.hsc b/Graphics/Win32/Window.hsc old mode 100644 new mode 100755 index 791549a..abb9e15 --- a/Graphics/Win32/Window.hsc +++ b/Graphics/Win32/Window.hsc @@ -18,14 +18,24 @@ module Graphics.Win32.Window where -import System.Win32.Types -import Graphics.Win32.GDI.Types -import Graphics.Win32.Message - -import Control.Monad -import Data.Maybe -import Foreign -import System.IO.Unsafe +import Control.Monad (liftM) +import Data.Maybe (fromMaybe) +import Data.Word (Word32) +import Foreign.ForeignPtr (withForeignPtr) +import Foreign.Marshal.Alloc (allocaBytes) +import Foreign.Ptr (FunPtr, Ptr, castFunPtrToPtr, castPtr, nullPtr) +import Foreign.Storable (pokeByteOff) +import Graphics.Win32.GDI.Types (HBITMAP, HCURSOR, HDC, HDWP, HRGN, HWND, PRGN) +import Graphics.Win32.GDI.Types (HBRUSH, HICON, HMENU, prim_ChildWindowFromPoint) +import Graphics.Win32.GDI.Types (LPRECT, RECT, allocaRECT, peekRECT, withRECT) +import Graphics.Win32.GDI.Types (POINT, allocaPOINT, peekPOINT, withPOINT) +import Graphics.Win32.GDI.Types (prim_ChildWindowFromPointEx) +import Graphics.Win32.Message (WindowMessage) +import System.IO.Unsafe (unsafePerformIO) +import System.Win32.Types (ATOM, maybePtr, newTString, ptrToMaybe, numToMaybe) +import System.Win32.Types (Addr, BOOL, DWORD, INT, LONG, LRESULT, UINT, WPARAM) +import System.Win32.Types (HINSTANCE, LPARAM, LPCTSTR, LPVOID, withTString) +import System.Win32.Types (failIf, failIf_, failIfFalse_, failIfNull, maybeNum) ##include "windows_cconv.h" diff --git a/System/Win32/Registry.hsc b/System/Win32/Registry.hsc old mode 100644 new mode 100755 index 9d9f6ce..cb9cd8e --- a/System/Win32/Registry.hsc +++ b/System/Win32/Registry.hsc @@ -60,12 +60,20 @@ module System.Win32.Registry -} -import System.Win32.Time -import System.Win32.Types -import System.Win32.File - -import System.IO.Unsafe -import Foreign +import Data.Word (Word32) +import Foreign.ForeignPtr (withForeignPtr) +import Foreign.Marshal.Alloc (alloca, allocaBytes, free, mallocBytes) +import Foreign.Marshal.Array (allocaArray0) +import Foreign.Marshal.Utils (maybeWith, with) +import Foreign.Ptr (Ptr, castPtr, nullPtr) +import Foreign.Storable (peek, peekByteOff, peekElemOff, sizeOf) +import System.IO.Unsafe (unsafePerformIO) +import System.Win32.File (LPSECURITY_ATTRIBUTES) +import System.Win32.Time (FILETIME) +import System.Win32.Types (DWORD, ErrCode, HKEY, LPCTSTR, PKEY, withTString) +import System.Win32.Types (HANDLE, LONG, LPBYTE, newForeignHANDLE, peekTString) +import System.Win32.Types (LPTSTR, TCHAR, failUnlessSuccess, withTStringLen) +import System.Win32.Types (castUINTPtrToPtr, failUnlessSuccessOr, maybePtr) ##include "windows_cconv.h" From git at git.haskell.org Tue Mar 18 10:16:13 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Mar 2014 10:16:13 +0000 (UTC) Subject: [commit: packages/Win32] ghc-head: Allow building with base 4.5 once again (a420a0c) Message-ID: <20140318101613.A9C132406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/Win32 On branch : ghc-head Link : http://git.haskell.org/packages/Win32.git/commitdiff/a420a0cab1d824c47c0b7dc91ce9fc61be7faa00 >--------------------------------------------------------------- commit a420a0cab1d824c47c0b7dc91ce9fc61be7faa00 Author: Bryan O'Sullivan Date: Tue Feb 4 12:26:56 2014 -0800 Allow building with base 4.5 once again >--------------------------------------------------------------- a420a0cab1d824c47c0b7dc91ce9fc61be7faa00 Graphics/Win32/Key.hsc | 5 ++--- System/Win32/Info.hsc | 17 +++++++++++------ Win32.cabal | 2 +- 3 files changed, 14 insertions(+), 10 deletions(-) diff --git a/Graphics/Win32/Key.hsc b/Graphics/Win32/Key.hsc index ff21d51..e1c414b 100755 --- a/Graphics/Win32/Key.hsc +++ b/Graphics/Win32/Key.hsc @@ -17,10 +17,9 @@ module Graphics.Win32.Key where -import Graphics.Win32.GDI.Types -import System.Win32.Types - import Control.Monad (liftM) +import Graphics.Win32.GDI.Types (HWND) +import System.Win32.Types (DWORD, UINT, WORD, ptrToMaybe) ##include "windows_cconv.h" diff --git a/System/Win32/Info.hsc b/System/Win32/Info.hsc old mode 100644 new mode 100755 index b6275da..23e2eac --- a/System/Win32/Info.hsc +++ b/System/Win32/Info.hsc @@ -17,13 +17,18 @@ module System.Win32.Info where -import System.Win32.Types - import Control.Exception (catch) -import System.IO.Error -import Foreign ( Storable(sizeOf, alignment, peekByteOff, pokeByteOff, - peek, poke) - , Ptr, alloca, allocaArray ) +import Foreign.Marshal.Alloc (alloca) +import Foreign.Marshal.Array (allocaArray) +import Foreign.Ptr (Ptr, nullPtr) +import Foreign.Storable (Storable(..)) +import System.IO.Error (isDoesNotExistError) +import System.Win32.Types (DWORD, LPCTSTR, LPTSTR, LPVOID, UINT, WORD) +import System.Win32.Types (failIfZero, peekTStringLen, withTString) + +#if !MIN_VERSION_base(4,6,0) +import Prelude hiding (catch) +#endif ##include "windows_cconv.h" diff --git a/Win32.cabal b/Win32.cabal index 4edf5b8..e5eb693 100755 --- a/Win32.cabal +++ b/Win32.cabal @@ -17,7 +17,7 @@ extra-source-files: include/Win32Aux.h include/win32debug.h include/windows_cconv.h Library - build-depends: base >= 4.6 && < 5, bytestring + build-depends: base >= 4.5 && < 5, bytestring ghc-options: -Wall -fno-warn-name-shadowing cc-options: -fno-strict-aliasing exposed-modules: From git at git.haskell.org Tue Mar 18 10:16:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Mar 2014 10:16:15 +0000 (UTC) Subject: [commit: packages/Win32] ghc-head: Bump version to 2.3.0.2 (8f982f6) Message-ID: <20140318101615.ADCEB2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/Win32 On branch : ghc-head Link : http://git.haskell.org/packages/Win32.git/commitdiff/8f982f6c880f84d3d0f21aca361d59829841d166 >--------------------------------------------------------------- commit 8f982f6c880f84d3d0f21aca361d59829841d166 Author: Bryan O'Sullivan Date: Tue Feb 4 12:29:30 2014 -0800 Bump version to 2.3.0.2 >--------------------------------------------------------------- 8f982f6c880f84d3d0f21aca361d59829841d166 Win32.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Win32.cabal b/Win32.cabal index e5eb693..fa56f34 100755 --- a/Win32.cabal +++ b/Win32.cabal @@ -1,5 +1,5 @@ name: Win32 -version: 2.3.0.1 +version: 2.3.0.2 license: BSD3 license-file: LICENSE author: Alastair Reid From git at git.haskell.org Tue Mar 18 10:16:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Mar 2014 10:16:17 +0000 (UTC) Subject: [commit: packages/Win32] ghc-head: Update maintainer address (317571c) Message-ID: <20140318101617.A18782406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/Win32 On branch : ghc-head Link : http://git.haskell.org/packages/Win32.git/commitdiff/317571c6ca3e3720acf4e1eccf36fe3a0337150b >--------------------------------------------------------------- commit 317571c6ca3e3720acf4e1eccf36fe3a0337150b Author: Bryan O'Sullivan Date: Tue Feb 4 12:35:55 2014 -0800 Update maintainer address >--------------------------------------------------------------- 317571c6ca3e3720acf4e1eccf36fe3a0337150b Win32.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Win32.cabal b/Win32.cabal index fa56f34..2700cc0 100755 --- a/Win32.cabal +++ b/Win32.cabal @@ -4,7 +4,7 @@ license: BSD3 license-file: LICENSE author: Alastair Reid copyright: Alastair Reid, 1999-2003 -maintainer: Bryan O'Sullivan +maintainer: Haskell Libraries bug-reports: https://github.com/haskell/win32/issues homepage: https://github.com/haskell/win32 category: System, Graphics From git at git.haskell.org Tue Mar 18 10:16:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Mar 2014 10:16:19 +0000 (UTC) Subject: [commit: packages/Win32] ghc-head: Merge pull request #14 from arkeet/patch-1 (e95d1c5) Message-ID: <20140318101619.B1D4B2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/Win32 On branch : ghc-head Link : http://git.haskell.org/packages/Win32.git/commitdiff/e95d1c5eaed33fbb3e86116f6dda7ff3fff4f0cd >--------------------------------------------------------------- commit e95d1c5eaed33fbb3e86116f6dda7ff3fff4f0cd Merge: 317571c b5392c3 Author: Bryan O'Sullivan Date: Tue Feb 4 12:43:46 2014 -0800 Merge pull request #14 from arkeet/patch-1 Fix th32SnapEnumProcesses to use PROCESSENTRY32W >--------------------------------------------------------------- e95d1c5eaed33fbb3e86116f6dda7ff3fff4f0cd System/Win32/Process.hsc | 14 +++++++------- 1 file changed, 7 insertions(+), 7 deletions(-) From git at git.haskell.org Tue Mar 18 10:16:21 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Mar 2014 10:16:21 +0000 (UTC) Subject: [commit: packages/Win32] ghc-head: Fix examples/hello.lhs to actually work (!) (881c4f4) Message-ID: <20140318101621.A795C2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/Win32 On branch : ghc-head Link : http://git.haskell.org/packages/Win32.git/commitdiff/881c4f40bd1307de975bb9d2f049879ba9c9a73b >--------------------------------------------------------------- commit 881c4f40bd1307de975bb9d2f049879ba9c9a73b Author: Bryan O'Sullivan Date: Tue Feb 4 12:50:15 2014 -0800 Fix examples/hello.lhs to actually work (!) >--------------------------------------------------------------- 881c4f40bd1307de975bb9d2f049879ba9c9a73b examples/hello.lhs | 23 ++++++++--------------- 1 file changed, 8 insertions(+), 15 deletions(-) diff --git a/examples/hello.lhs b/examples/hello.lhs old mode 100644 new mode 100755 index c81b83b..7d20d01 --- a/examples/hello.lhs +++ b/examples/hello.lhs @@ -5,23 +5,16 @@ Haskell version of "Hello, World" using the Win32 library. Demonstrates how the Win32 library can be put to use. -Works with Hugs and GHC. To compile it up using the latter, -do: "ghc -o main hello.lhs -syslib win32 -fglasgow-exts" - -For GHC 5.03: - - ghc -package win32 hello.lhs -o hello.exe -optl "-Wl,--subsystem,windows" - \begin{code} +{-# LANGUAGE ScopedTypeVariables #-} module Main(main) where +import Control.Exception (SomeException, bracket, catch) +import Foreign.Ptr (nullPtr) +import System.Exit (ExitCode(ExitSuccess), exitWith) +import System.Win32.DLL (getModuleHandle) import qualified Graphics.Win32 -import qualified System.Win32.DLL -import qualified System.Win32.Types -import Control.Exception (bracket) -import Foreign -import System.Exit -{-import Addr-} + \end{code} Toplevel main just creates a window and pumps messages. @@ -82,7 +75,7 @@ createWindow width height wndProc = do icon <- Graphics.Win32.loadIcon Nothing Graphics.Win32.iDI_APPLICATION cursor <- Graphics.Win32.loadCursor Nothing Graphics.Win32.iDC_ARROW bgBrush <- Graphics.Win32.createSolidBrush (Graphics.Win32.rgb 0 0 255) - mainInstance <- System.Win32.DLL.getModuleHandle Nothing + mainInstance <- getModuleHandle Nothing Graphics.Win32.registerClass ( Graphics.Win32.cS_VREDRAW + Graphics.Win32.cS_HREDRAW , mainInstance @@ -112,7 +105,7 @@ messagePump :: Graphics.Win32.HWND -> IO () messagePump hwnd = Graphics.Win32.allocaMessage $ \ msg -> let pump = do Graphics.Win32.getMessage msg (Just hwnd) - `catch` \ _ -> exitWith ExitSuccess + `catch` \ (_::SomeException) -> exitWith ExitSuccess Graphics.Win32.translateMessage msg Graphics.Win32.dispatchMessage msg pump From git at git.haskell.org Tue Mar 18 10:16:23 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Mar 2014 10:16:23 +0000 (UTC) Subject: [commit: packages/Win32] ghc-head: Merge pull request #11 from ezyang/master (c3c8090) Message-ID: <20140318101623.ADADA2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/Win32 On branch : ghc-head Link : http://git.haskell.org/packages/Win32.git/commitdiff/c3c8090e0c84d55100f14eac8b168ea08ac4815b >--------------------------------------------------------------- commit c3c8090e0c84d55100f14eac8b168ea08ac4815b Merge: 881c4f4 8862fb6 Author: Bryan O'Sullivan Date: Tue Feb 4 12:51:42 2014 -0800 Merge pull request #11 from ezyang/master Use regCreateKey to be more robust when registry entry does not exist. >--------------------------------------------------------------- c3c8090e0c84d55100f14eac8b168ea08ac4815b tests/registry001.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) From git at git.haskell.org Tue Mar 18 10:16:25 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Mar 2014 10:16:25 +0000 (UTC) Subject: [commit: packages/Win32] ghc-head: Merge pull request #10 from redneb/GetFileAttributesEx (b4a375f) Message-ID: <20140318101625.B2E042406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/Win32 On branch : ghc-head Link : http://git.haskell.org/packages/Win32.git/commitdiff/b4a375ff24415eb77215a0acf15b1c084bea0de0 >--------------------------------------------------------------- commit b4a375ff24415eb77215a0acf15b1c084bea0de0 Merge: c3c8090 263c97f Author: Bryan O'Sullivan Date: Tue Feb 4 12:53:21 2014 -0800 Merge pull request #10 from redneb/GetFileAttributesEx Add support for GetFileAttributesEx >--------------------------------------------------------------- b4a375ff24415eb77215a0acf15b1c084bea0de0 System/Win32/File.hsc | 50 +++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 50 insertions(+) From git at git.haskell.org Tue Mar 18 10:16:27 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Mar 2014 10:16:27 +0000 (UTC) Subject: [commit: packages/Win32] ghc-head: Use throwIO instead of throw for correctness (5ccf179) Message-ID: <20140318101627.C31D02406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/Win32 On branch : ghc-head Link : http://git.haskell.org/packages/Win32.git/commitdiff/5ccf17927b873835bf980436ffa7ee100586de1e >--------------------------------------------------------------- commit 5ccf17927b873835bf980436ffa7ee100586de1e Author: Bryan O'Sullivan Date: Tue Feb 4 22:25:12 2014 -0800 Use throwIO instead of throw for correctness >--------------------------------------------------------------- 5ccf17927b873835bf980436ffa7ee100586de1e System/Win32/Types.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/System/Win32/Types.hs b/System/Win32/Types.hs index 359e42f..68a4ff1 100755 --- a/System/Win32/Types.hs +++ b/System/Win32/Types.hs @@ -20,7 +20,7 @@ module System.Win32.Types , nullPtr ) where -import Control.Exception (throw) +import Control.Exception (throwIO) import Data.Bits (shiftL, shiftR, (.|.), (.&.)) import Data.Char (isSpace) import Data.Int (Int32, Int64) @@ -242,7 +242,7 @@ failWith fn_name err_code = do let msg' = reverse $ dropWhile isSpace $ reverse msg -- drop trailing \n ioerror = errnoToIOError fn_name errno Nothing Nothing `ioeSetErrorString` msg' - throw ioerror + throwIO ioerror foreign import ccall unsafe "maperrno" -- in base/cbits/Win32Utils.c From git at git.haskell.org Tue Mar 18 10:16:29 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Mar 2014 10:16:29 +0000 (UTC) Subject: [commit: packages/Win32] ghc-head: Add FILE_SHARE_DELETE (c51e81a) Message-ID: <20140318101629.B9C8E2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/Win32 On branch : ghc-head Link : http://git.haskell.org/packages/Win32.git/commitdiff/c51e81a43cd5e9540453bd5ca6da8992245a4774 >--------------------------------------------------------------- commit c51e81a43cd5e9540453bd5ca6da8992245a4774 Author: Bryan O'Sullivan Date: Mon Mar 10 22:16:32 2014 -0700 Add FILE_SHARE_DELETE >--------------------------------------------------------------- c51e81a43cd5e9540453bd5ca6da8992245a4774 System/Win32/File.hsc | 1 + 1 file changed, 1 insertion(+) diff --git a/System/Win32/File.hsc b/System/Win32/File.hsc index d17c042..0b921c4 100644 --- a/System/Win32/File.hsc +++ b/System/Win32/File.hsc @@ -74,6 +74,7 @@ fILE_SHARE_NONE = 0 #{enum ShareMode, , fILE_SHARE_READ = FILE_SHARE_READ , fILE_SHARE_WRITE = FILE_SHARE_WRITE + , fILE_SHARE_DELETE = FILE_SHARE_DELETE } ---------------------------------------------------------------- From git at git.haskell.org Tue Mar 18 10:17:23 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Mar 2014 10:17:23 +0000 (UTC) Subject: [commit: ghc] master: Update submodule to Win32-2.3.0.2 (696bfc4) Message-ID: <20140318101723.574FF2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/696bfc4ba5fce6b75cc91bcb67c5d0a3c9f29bd2/ghc >--------------------------------------------------------------- commit 696bfc4ba5fce6b75cc91bcb67c5d0a3c9f29bd2 Author: Herbert Valerio Riedel Date: Tue Mar 18 11:06:57 2014 +0100 Update submodule to Win32-2.3.0.2 Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 696bfc4ba5fce6b75cc91bcb67c5d0a3c9f29bd2 libraries/Win32 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Win32 b/libraries/Win32 index 1e909ad..c51e81a 160000 --- a/libraries/Win32 +++ b/libraries/Win32 @@ -1 +1 @@ -Subproject commit 1e909adb06b766e107148b8b37a4a9f9e50baf74 +Subproject commit c51e81a43cd5e9540453bd5ca6da8992245a4774 From git at git.haskell.org Tue Mar 18 17:17:20 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 18 Mar 2014 17:17:20 +0000 (UTC) Subject: [commit: ghc] master: Make sure we occurrence-analyse unfoldings (fixes Trac #8892) (87bbc69) Message-ID: <20140318171720.25C442406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/87bbc69c40d36046492d754c8d7ff02c3be6ce43/ghc >--------------------------------------------------------------- commit 87bbc69c40d36046492d754c8d7ff02c3be6ce43 Author: Simon Peyton Jones Date: Tue Mar 18 17:10:18 2014 +0000 Make sure we occurrence-analyse unfoldings (fixes Trac #8892) For DFunUnfoldings we were failing to occurrence-analyse the unfolding, and that meant that a loop breaker wasn't marked as such, which in turn meant it was inlined away when it still had occurrence sites. See Note [Occurrrence analysis of unfoldings] in CoreUnfold. This is a pretty long-standing bug, happily nailed by John Lato. >--------------------------------------------------------------- 87bbc69c40d36046492d754c8d7ff02c3be6ce43 compiler/coreSyn/CoreUnfold.lhs | 25 ++++++++++++- compiler/simplCore/Simplify.lhs | 78 +++++++++++++++++++-------------------- 2 files changed, 62 insertions(+), 41 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 87bbc69c40d36046492d754c8d7ff02c3be6ce43 From git at git.haskell.org Wed Mar 19 01:54:34 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Mar 2014 01:54:34 +0000 (UTC) Subject: [commit: ghc] master: Implement ordering comparisons for type-level naturals and symbols. (5e4bdb5) Message-ID: <20140319015435.0ED1F2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5e4bdb5fc5e741522cbb787731422da3f12aa398/ghc >--------------------------------------------------------------- commit 5e4bdb5fc5e741522cbb787731422da3f12aa398 Author: Iavor S. Diatchki Date: Tue Mar 18 18:54:23 2014 -0700 Implement ordering comparisons for type-level naturals and symbols. This is done with two built-in type families: `CmpNat and `CmpSymbol`. Both of these return a promoted `Ordering` type (EQ, LT, or GT). >--------------------------------------------------------------- 5e4bdb5fc5e741522cbb787731422da3f12aa398 compiler/prelude/PrelNames.lhs | 3 + compiler/prelude/TysWiredIn.lhs | 16 +++++ compiler/typecheck/TcTypeNats.hs | 142 +++++++++++++++++++++++++++++++++++++- 3 files changed, 160 insertions(+), 1 deletion(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 5e4bdb5fc5e741522cbb787731422da3f12aa398 From git at git.haskell.org Wed Mar 19 02:35:33 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Mar 2014 02:35:33 +0000 (UTC) Subject: [commit: packages/base] master: Add functions for comparing type-level Nats and Symbols. (c1d3546) Message-ID: <20140319023533.B0DA42406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/base On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c1d3546420ee482bbbd9f15d45a6e8a26304d419/base >--------------------------------------------------------------- commit c1d3546420ee482bbbd9f15d45a6e8a26304d419 Author: Iavor S. Diatchki Date: Tue Mar 18 19:35:05 2014 -0700 Add functions for comparing type-level Nats and Symbols. >--------------------------------------------------------------- c1d3546420ee482bbbd9f15d45a6e8a26304d419 GHC/TypeLits.hs | 11 +++++++++-- 1 file changed, 9 insertions(+), 2 deletions(-) diff --git a/GHC/TypeLits.hs b/GHC/TypeLits.hs index e85b36c..ac0f1ae 100644 --- a/GHC/TypeLits.hs +++ b/GHC/TypeLits.hs @@ -29,12 +29,13 @@ module GHC.TypeLits , sameNat, sameSymbol - -- * Functions on type nats + -- * Functions on type literals , type (<=), type (<=?), type (+), type (*), type (^), type (-) + , CmpNat, CmpSymbol ) where -import GHC.Base(Eq(..), Ord(..), Bool(True,False), otherwise) +import GHC.Base(Eq(..), Ord(..), Bool(True,False), Ordering(..), otherwise) import GHC.Num(Integer) import GHC.Base(String) import GHC.Show(Show(..)) @@ -153,6 +154,12 @@ infixr 8 ^ type x <= y = (x <=? y) ~ True -- | Comparison of type-level naturals, as a function. +type family CmpSymbol (m :: Symbol) (n :: Symbol) :: Ordering + +-- | Comparison of type-level symbols, as a function. +type family CmpNat (m :: Nat) (n :: Nat) :: Ordering + +-- | Comparison of type-level naturals, as a function. type family (m :: Nat) <=? (n :: Nat) :: Bool -- | Addition of type-level naturals. From git at git.haskell.org Wed Mar 19 14:33:06 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Mar 2014 14:33:06 +0000 (UTC) Subject: [commit: ghc] wip/T8776: Add test case for #8776 (25f9858) Message-ID: <20140319143306.E59672406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8776 Link : http://ghc.haskell.org/trac/ghc/changeset/25f985851b7d9c343911a45ad67a1e5b4d66f53b/ghc >--------------------------------------------------------------- commit 25f985851b7d9c343911a45ad67a1e5b4d66f53b Author: Dr. ERDI Gergo Date: Fri Mar 14 22:34:56 2014 +0800 Add test case for #8776 >--------------------------------------------------------------- 25f985851b7d9c343911a45ad67a1e5b4d66f53b testsuite/tests/ghci/scripts/T8776.hs | 6 ++++++ testsuite/tests/ghci/scripts/T8776.script | 2 ++ testsuite/tests/ghci/scripts/T8776.stdout | 1 + testsuite/tests/ghci/scripts/all.T | 2 ++ 4 files changed, 11 insertions(+) diff --git a/testsuite/tests/ghci/scripts/T8776.hs b/testsuite/tests/ghci/scripts/T8776.hs new file mode 100644 index 0000000..55e329c --- /dev/null +++ b/testsuite/tests/ghci/scripts/T8776.hs @@ -0,0 +1,6 @@ +{-# LANGUAGE PatternSynonyms, GADTs #-} +data A x y = (Num x, Eq y) => B + +data R = R{ rX :: Int } + +pattern P = B diff --git a/testsuite/tests/ghci/scripts/T8776.script b/testsuite/tests/ghci/scripts/T8776.script new file mode 100644 index 0000000..baaca9f --- /dev/null +++ b/testsuite/tests/ghci/scripts/T8776.script @@ -0,0 +1,2 @@ +:load T8776.hs +:i P diff --git a/testsuite/tests/ghci/scripts/T8776.stdout b/testsuite/tests/ghci/scripts/T8776.stdout new file mode 100644 index 0000000..9c9e89a --- /dev/null +++ b/testsuite/tests/ghci/scripts/T8776.stdout @@ -0,0 +1 @@ +pattern (Num t, Eq t1) => P :: (A t t1) -- Defined at T8776.hs:6:9 diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T index e9fe6e8..06c0716 100755 --- a/testsuite/tests/ghci/scripts/all.T +++ b/testsuite/tests/ghci/scripts/all.T @@ -166,3 +166,5 @@ test('T8579', normal, ghci_script, ['T8579.script']) test('T8649', normal, ghci_script, ['T8649.script']) test('T8674', normal, ghci_script, ['T8674.script']) test('T8696', normal, ghci_script, ['T8696.script']) +test('T8776', normal, ghci_script, ['T8776.script']) + From git at git.haskell.org Wed Mar 19 14:33:09 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Mar 2014 14:33:09 +0000 (UTC) Subject: [commit: ghc] wip/T8776: isLexVarSym: check all characters of the name, not just the first one. (df87766) Message-ID: <20140319143309.89FD82406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8776 Link : http://ghc.haskell.org/trac/ghc/changeset/df87766ef9072ede0be5e074e6814b5662ebc626/ghc >--------------------------------------------------------------- commit df87766ef9072ede0be5e074e6814b5662ebc626 Author: Dr. ERDI Gergo Date: Wed Mar 19 20:07:47 2014 +0800 isLexVarSym: check all characters of the name, not just the first one. This is so that generated names like e.g. workers don't show up as infix operators when using something like -ddump-simpl. >--------------------------------------------------------------- df87766ef9072ede0be5e074e6814b5662ebc626 compiler/basicTypes/OccName.lhs | 25 +++++++++++++++++++------ 1 file changed, 19 insertions(+), 6 deletions(-) diff --git a/compiler/basicTypes/OccName.lhs b/compiler/basicTypes/OccName.lhs index 2d17b95..66e6550 100644 --- a/compiler/basicTypes/OccName.lhs +++ b/compiler/basicTypes/OccName.lhs @@ -501,7 +501,7 @@ isDataSymOcc _ = False -- it is a data constructor or variable or whatever) isSymOcc :: OccName -> Bool isSymOcc (OccName DataName s) = isLexConSym s -isSymOcc (OccName TcClsName s) = isLexConSym s || isLexVarSym s +isSymOcc (OccName TcClsName s) = isLexSym s isSymOcc (OccName VarName s) = isLexSym s isSymOcc (OccName TvName s) = isLexSym s -- Pretty inefficient! @@ -869,6 +869,15 @@ isTupleOcc_maybe (OccName ns fs) These functions test strings to see if they fit the lexical categories defined in the Haskell report. +Note [Classification of generated names] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +Some names generated for internal use can show up in debugging output, +e.g. when using -ddump-simpl. These generated names start with a $ +but should still be pretty-printed using prefix notation. We make sure +this is the case in isLexVarSym by only classifying a name as a symbol +if all its characters are symbols, not just its first one. + \begin{code} isLexCon, isLexVar, isLexId, isLexSym :: FastString -> Bool isLexConId, isLexConSym, isLexVarId, isLexVarSym :: FastString -> Bool @@ -895,19 +904,23 @@ isLexConSym cs -- Infix type or data constructors | cs == (fsLit "->") = True | otherwise = startsConSym (headFS cs) -isLexVarSym cs -- Infix identifiers - | nullFS cs = False -- e.g. "+" - | otherwise = startsVarSym (headFS cs) +isLexVarSym fs -- Infix identifiers e.g. "+" + = case (if nullFS fs then [] else unpackFS fs) of + [] -> False + (c:cs) -> startsVarSym c && all isVarSymChar cs ------------- startsVarSym, startsVarId, startsConSym, startsConId :: Char -> Bool -startsVarSym c = isSymbolASCII c || (ord c > 0x7f && isSymbol c) -- Infix Ids -startsConSym c = c == ':' -- Infix data constructors +startsVarSym c = isSymbolASCII c || (ord c > 0x7f && isSymbol c) -- Infix Ids +startsConSym c = c == ':' -- Infix data constructors startsVarId c = isLower c || c == '_' -- Ordinary Ids startsConId c = isUpper c || c == '(' -- Ordinary type constructors and data constructors isSymbolASCII :: Char -> Bool isSymbolASCII c = c `elem` "!#$%&*+./<=>?@\\^|~-" + +isVarSymChar :: Char -> Bool +isVarSymChar c = c == ':' || startsVarSym c \end{code} %************************************************************************ From git at git.haskell.org Wed Mar 19 14:33:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Mar 2014 14:33:11 +0000 (UTC) Subject: [commit: ghc] wip/T8776: Update expected test outputs to match new format of pretty-printing interface contents (7514865) Message-ID: <20140319143311.D69672406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8776 Link : http://ghc.haskell.org/trac/ghc/changeset/7514865a205ff8eff568d0f6e9e05c2b95418260/ghc >--------------------------------------------------------------- commit 7514865a205ff8eff568d0f6e9e05c2b95418260 Author: Dr. ERDI Gergo Date: Wed Mar 19 21:44:38 2014 +0800 Update expected test outputs to match new format of pretty-printing interface contents >--------------------------------------------------------------- 7514865a205ff8eff568d0f6e9e05c2b95418260 .../indexed-types/should_compile/T3017.stderr | 2 +- testsuite/tests/roles/should_compile/Roles1.stderr | 70 ++++++++++---------- testsuite/tests/roles/should_compile/Roles2.stderr | 20 +++--- testsuite/tests/roles/should_compile/all.T | 4 +- .../tests/typecheck/should_compile/tc231.stderr | 7 +- 5 files changed, 51 insertions(+), 52 deletions(-) diff --git a/testsuite/tests/indexed-types/should_compile/T3017.stderr b/testsuite/tests/indexed-types/should_compile/T3017.stderr index d11fad8..2019047 100644 --- a/testsuite/tests/indexed-types/should_compile/T3017.stderr +++ b/testsuite/tests/indexed-types/should_compile/T3017.stderr @@ -14,7 +14,7 @@ TYPE CONSTRUCTORS No C type associated Roles: [representational] RecFlag NonRecursive, Promotable - = L :: forall a. [a] -> ListColl a Stricts: _ + = L :: [a] -> ListColl a Stricts: _ FamilyInstance: none COERCION AXIOMS axiom Foo.TFCo:R:ElemListColl :: Elem (ListColl a) = a diff --git a/testsuite/tests/roles/should_compile/Roles1.stderr b/testsuite/tests/roles/should_compile/Roles1.stderr index e1808e8..cd027f1 100644 --- a/testsuite/tests/roles/should_compile/Roles1.stderr +++ b/testsuite/tests/roles/should_compile/Roles1.stderr @@ -2,53 +2,53 @@ TYPE SIGNATURES TYPE CONSTRUCTORS T1 :: * -> * data T1 a - No C type associated - Roles: [nominal] - RecFlag NonRecursive, Promotable - = K1 :: forall a. a -> T1 a Stricts: _ - FamilyInstance: none + No C type associated + Roles: [nominal] + RecFlag NonRecursive, Promotable + = K1 :: forall a. a -> T1 a Stricts: _ + FamilyInstance: none T2 :: * -> * data T2 a - No C type associated - Roles: [representational] - RecFlag NonRecursive, Promotable - = K2 :: forall a. a -> T2 a Stricts: _ - FamilyInstance: none + No C type associated + Roles: [representational] + RecFlag NonRecursive, Promotable + = K2 :: forall a. a -> T2 a Stricts: _ + FamilyInstance: none T3 :: k -> * data T3 (k::BOX) (a::k) - No C type associated - Roles: [nominal, phantom] - RecFlag NonRecursive, Not promotable - = K3 :: forall (k::BOX) (a::k). T3 k a - FamilyInstance: none + No C type associated + Roles: [nominal, phantom] + RecFlag NonRecursive, Not promotable + = K3 :: forall (k::BOX) (a::k). T3 k a + FamilyInstance: none T4 :: (* -> *) -> * -> * data T4 (a::* -> *) b - No C type associated - Roles: [nominal, nominal] - RecFlag NonRecursive, Not promotable - = K4 :: forall (a::* -> *) b. (a b) -> T4 a b Stricts: _ - FamilyInstance: none + No C type associated + Roles: [nominal, nominal] + RecFlag NonRecursive, Not promotable + = K4 :: forall (a::* -> *) b. (a b) -> T4 a b Stricts: _ + FamilyInstance: none T5 :: * -> * data T5 a - No C type associated - Roles: [representational] - RecFlag NonRecursive, Promotable - = K5 :: forall a. a -> T5 a Stricts: _ - FamilyInstance: none + No C type associated + Roles: [representational] + RecFlag NonRecursive, Promotable + = K5 :: forall a. a -> T5 a Stricts: _ + FamilyInstance: none T6 :: k -> * data T6 (k::BOX) (a::k) - No C type associated - Roles: [nominal, phantom] - RecFlag NonRecursive, Not promotable - = K6 :: forall (k::BOX) (a::k). T6 k a - FamilyInstance: none + No C type associated + Roles: [nominal, phantom] + RecFlag NonRecursive, Not promotable + = K6 :: forall (k::BOX) (a::k). T6 k a + FamilyInstance: none T7 :: k -> * -> * data T7 (k::BOX) (a::k) b - No C type associated - Roles: [nominal, phantom, representational] - RecFlag NonRecursive, Not promotable - = K7 :: forall (k::BOX) (a::k) b. b -> T7 k a b Stricts: _ - FamilyInstance: none + No C type associated + Roles: [nominal, phantom, representational] + RecFlag NonRecursive, Not promotable + = K7 :: forall (k::BOX) (a::k) b. b -> T7 k a b Stricts: _ + FamilyInstance: none COERCION AXIOMS Dependent modules: [] Dependent packages: [base, ghc-prim, integer-gmp] diff --git a/testsuite/tests/roles/should_compile/Roles2.stderr b/testsuite/tests/roles/should_compile/Roles2.stderr index ac7a94b..f5bcbe6 100644 --- a/testsuite/tests/roles/should_compile/Roles2.stderr +++ b/testsuite/tests/roles/should_compile/Roles2.stderr @@ -2,18 +2,18 @@ TYPE SIGNATURES TYPE CONSTRUCTORS T1 :: * -> * data T1 a - No C type associated - Roles: [representational] - RecFlag NonRecursive, Not promotable - = K1 :: forall a. (IO a) -> T1 a Stricts: _ - FamilyInstance: none + No C type associated + Roles: [representational] + RecFlag NonRecursive, Not promotable + = K1 :: forall a. (IO a) -> T1 a Stricts: _ + FamilyInstance: none T2 :: * -> * data T2 a - No C type associated - Roles: [representational] - RecFlag NonRecursive, Not promotable - = K2 :: forall a. (FunPtr a) -> T2 a Stricts: _ - FamilyInstance: none + No C type associated + Roles: [representational] + RecFlag NonRecursive, Not promotable + = K2 :: forall a. (FunPtr a) -> T2 a Stricts: _ + FamilyInstance: none COERCION AXIOMS Dependent modules: [] Dependent packages: [base, ghc-prim, integer-gmp] diff --git a/testsuite/tests/roles/should_compile/all.T b/testsuite/tests/roles/should_compile/all.T index a016de3..f77e61f 100644 --- a/testsuite/tests/roles/should_compile/all.T +++ b/testsuite/tests/roles/should_compile/all.T @@ -1,5 +1,5 @@ -test('Roles1', only_ways('normal'), compile, ['-ddump-tc']) -test('Roles2', only_ways('normal'), compile, ['-ddump-tc']) +test('Roles1', only_ways('normal'), compile, ['-ddump-tc -fprint-explicit-foralls']) +test('Roles2', only_ways('normal'), compile, ['-ddump-tc -fprint-explicit-foralls']) test('Roles3', only_ways('normal'), compile, ['-ddump-tc']) test('Roles4', only_ways('normal'), compile, ['-ddump-tc']) test('Roles13', only_ways('normal'), compile, ['-ddump-simpl -dsuppress-uniques']) diff --git a/testsuite/tests/typecheck/should_compile/tc231.stderr b/testsuite/tests/typecheck/should_compile/tc231.stderr index 4334d62..16dddda 100644 --- a/testsuite/tests/typecheck/should_compile/tc231.stderr +++ b/testsuite/tests/typecheck/should_compile/tc231.stderr @@ -10,21 +10,20 @@ TYPE CONSTRUCTORS No C type associated Roles: [representational, representational, representational] RecFlag NonRecursive, Promotable - = Node :: forall s a chain. s -> a -> chain -> Q s a chain - Stricts: _ _ _ + = Node :: s -> a -> chain -> Q s a chain Stricts: _ _ _ FamilyInstance: none Z :: * -> * data Z a No C type associated Roles: [representational] RecFlag NonRecursive, Promotable - = Z :: forall a. a -> Z a Stricts: _ + = Z :: a -> Z a Stricts: _ FamilyInstance: none Zork :: * -> * -> * -> Constraint class Zork s a b | a -> b Roles: [nominal, nominal, nominal] RecFlag NonRecursive - huh :: forall chain. Q s a chain -> ST s () + huh :: Q s a chain -> ST s () COERCION AXIOMS axiom ShouldCompile.NTCo:Zork :: Zork s a b = forall chain. Q s a chain -> ST s () From git at git.haskell.org Wed Mar 19 14:35:48 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Mar 2014 14:35:48 +0000 (UTC) Subject: [commit: ghc] master: isLexVarSym: check all characters of the name, not just the first one. (a3f78e2) Message-ID: <20140319143548.682AF2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a3f78e2476e3d4ead86ef3b10ddd4e14e189ada3/ghc >--------------------------------------------------------------- commit a3f78e2476e3d4ead86ef3b10ddd4e14e189ada3 Author: Dr. ERDI Gergo Date: Wed Mar 19 20:07:47 2014 +0800 isLexVarSym: check all characters of the name, not just the first one. This is so that generated names like e.g. workers don't show up as infix operators when using something like -ddump-simpl. >--------------------------------------------------------------- a3f78e2476e3d4ead86ef3b10ddd4e14e189ada3 compiler/basicTypes/OccName.lhs | 25 +++++++++++++++++++------ 1 file changed, 19 insertions(+), 6 deletions(-) diff --git a/compiler/basicTypes/OccName.lhs b/compiler/basicTypes/OccName.lhs index 2d17b95..66e6550 100644 --- a/compiler/basicTypes/OccName.lhs +++ b/compiler/basicTypes/OccName.lhs @@ -501,7 +501,7 @@ isDataSymOcc _ = False -- it is a data constructor or variable or whatever) isSymOcc :: OccName -> Bool isSymOcc (OccName DataName s) = isLexConSym s -isSymOcc (OccName TcClsName s) = isLexConSym s || isLexVarSym s +isSymOcc (OccName TcClsName s) = isLexSym s isSymOcc (OccName VarName s) = isLexSym s isSymOcc (OccName TvName s) = isLexSym s -- Pretty inefficient! @@ -869,6 +869,15 @@ isTupleOcc_maybe (OccName ns fs) These functions test strings to see if they fit the lexical categories defined in the Haskell report. +Note [Classification of generated names] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +Some names generated for internal use can show up in debugging output, +e.g. when using -ddump-simpl. These generated names start with a $ +but should still be pretty-printed using prefix notation. We make sure +this is the case in isLexVarSym by only classifying a name as a symbol +if all its characters are symbols, not just its first one. + \begin{code} isLexCon, isLexVar, isLexId, isLexSym :: FastString -> Bool isLexConId, isLexConSym, isLexVarId, isLexVarSym :: FastString -> Bool @@ -895,19 +904,23 @@ isLexConSym cs -- Infix type or data constructors | cs == (fsLit "->") = True | otherwise = startsConSym (headFS cs) -isLexVarSym cs -- Infix identifiers - | nullFS cs = False -- e.g. "+" - | otherwise = startsVarSym (headFS cs) +isLexVarSym fs -- Infix identifiers e.g. "+" + = case (if nullFS fs then [] else unpackFS fs) of + [] -> False + (c:cs) -> startsVarSym c && all isVarSymChar cs ------------- startsVarSym, startsVarId, startsConSym, startsConId :: Char -> Bool -startsVarSym c = isSymbolASCII c || (ord c > 0x7f && isSymbol c) -- Infix Ids -startsConSym c = c == ':' -- Infix data constructors +startsVarSym c = isSymbolASCII c || (ord c > 0x7f && isSymbol c) -- Infix Ids +startsConSym c = c == ':' -- Infix data constructors startsVarId c = isLower c || c == '_' -- Ordinary Ids startsConId c = isUpper c || c == '(' -- Ordinary type constructors and data constructors isSymbolASCII :: Char -> Bool isSymbolASCII c = c `elem` "!#$%&*+./<=>?@\\^|~-" + +isVarSymChar :: Char -> Bool +isVarSymChar c = c == ':' || startsVarSym c \end{code} %************************************************************************ From git at git.haskell.org Wed Mar 19 14:35:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 19 Mar 2014 14:35:50 +0000 (UTC) Subject: [commit: ghc] master: Update expected test outputs to match new format of pretty-printing interface contents (21028ee) Message-ID: <20140319143550.B2B0A2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/21028ee6805b896dbbd8a2d46b9690d1adecdcd1/ghc >--------------------------------------------------------------- commit 21028ee6805b896dbbd8a2d46b9690d1adecdcd1 Author: Dr. ERDI Gergo Date: Wed Mar 19 21:44:38 2014 +0800 Update expected test outputs to match new format of pretty-printing interface contents >--------------------------------------------------------------- 21028ee6805b896dbbd8a2d46b9690d1adecdcd1 .../indexed-types/should_compile/T3017.stderr | 2 +- testsuite/tests/roles/should_compile/Roles1.stderr | 70 ++++++++++---------- testsuite/tests/roles/should_compile/Roles2.stderr | 20 +++--- testsuite/tests/roles/should_compile/all.T | 4 +- .../tests/typecheck/should_compile/tc231.stderr | 7 +- 5 files changed, 51 insertions(+), 52 deletions(-) diff --git a/testsuite/tests/indexed-types/should_compile/T3017.stderr b/testsuite/tests/indexed-types/should_compile/T3017.stderr index d11fad8..2019047 100644 --- a/testsuite/tests/indexed-types/should_compile/T3017.stderr +++ b/testsuite/tests/indexed-types/should_compile/T3017.stderr @@ -14,7 +14,7 @@ TYPE CONSTRUCTORS No C type associated Roles: [representational] RecFlag NonRecursive, Promotable - = L :: forall a. [a] -> ListColl a Stricts: _ + = L :: [a] -> ListColl a Stricts: _ FamilyInstance: none COERCION AXIOMS axiom Foo.TFCo:R:ElemListColl :: Elem (ListColl a) = a diff --git a/testsuite/tests/roles/should_compile/Roles1.stderr b/testsuite/tests/roles/should_compile/Roles1.stderr index e1808e8..cd027f1 100644 --- a/testsuite/tests/roles/should_compile/Roles1.stderr +++ b/testsuite/tests/roles/should_compile/Roles1.stderr @@ -2,53 +2,53 @@ TYPE SIGNATURES TYPE CONSTRUCTORS T1 :: * -> * data T1 a - No C type associated - Roles: [nominal] - RecFlag NonRecursive, Promotable - = K1 :: forall a. a -> T1 a Stricts: _ - FamilyInstance: none + No C type associated + Roles: [nominal] + RecFlag NonRecursive, Promotable + = K1 :: forall a. a -> T1 a Stricts: _ + FamilyInstance: none T2 :: * -> * data T2 a - No C type associated - Roles: [representational] - RecFlag NonRecursive, Promotable - = K2 :: forall a. a -> T2 a Stricts: _ - FamilyInstance: none + No C type associated + Roles: [representational] + RecFlag NonRecursive, Promotable + = K2 :: forall a. a -> T2 a Stricts: _ + FamilyInstance: none T3 :: k -> * data T3 (k::BOX) (a::k) - No C type associated - Roles: [nominal, phantom] - RecFlag NonRecursive, Not promotable - = K3 :: forall (k::BOX) (a::k). T3 k a - FamilyInstance: none + No C type associated + Roles: [nominal, phantom] + RecFlag NonRecursive, Not promotable + = K3 :: forall (k::BOX) (a::k). T3 k a + FamilyInstance: none T4 :: (* -> *) -> * -> * data T4 (a::* -> *) b - No C type associated - Roles: [nominal, nominal] - RecFlag NonRecursive, Not promotable - = K4 :: forall (a::* -> *) b. (a b) -> T4 a b Stricts: _ - FamilyInstance: none + No C type associated + Roles: [nominal, nominal] + RecFlag NonRecursive, Not promotable + = K4 :: forall (a::* -> *) b. (a b) -> T4 a b Stricts: _ + FamilyInstance: none T5 :: * -> * data T5 a - No C type associated - Roles: [representational] - RecFlag NonRecursive, Promotable - = K5 :: forall a. a -> T5 a Stricts: _ - FamilyInstance: none + No C type associated + Roles: [representational] + RecFlag NonRecursive, Promotable + = K5 :: forall a. a -> T5 a Stricts: _ + FamilyInstance: none T6 :: k -> * data T6 (k::BOX) (a::k) - No C type associated - Roles: [nominal, phantom] - RecFlag NonRecursive, Not promotable - = K6 :: forall (k::BOX) (a::k). T6 k a - FamilyInstance: none + No C type associated + Roles: [nominal, phantom] + RecFlag NonRecursive, Not promotable + = K6 :: forall (k::BOX) (a::k). T6 k a + FamilyInstance: none T7 :: k -> * -> * data T7 (k::BOX) (a::k) b - No C type associated - Roles: [nominal, phantom, representational] - RecFlag NonRecursive, Not promotable - = K7 :: forall (k::BOX) (a::k) b. b -> T7 k a b Stricts: _ - FamilyInstance: none + No C type associated + Roles: [nominal, phantom, representational] + RecFlag NonRecursive, Not promotable + = K7 :: forall (k::BOX) (a::k) b. b -> T7 k a b Stricts: _ + FamilyInstance: none COERCION AXIOMS Dependent modules: [] Dependent packages: [base, ghc-prim, integer-gmp] diff --git a/testsuite/tests/roles/should_compile/Roles2.stderr b/testsuite/tests/roles/should_compile/Roles2.stderr index ac7a94b..f5bcbe6 100644 --- a/testsuite/tests/roles/should_compile/Roles2.stderr +++ b/testsuite/tests/roles/should_compile/Roles2.stderr @@ -2,18 +2,18 @@ TYPE SIGNATURES TYPE CONSTRUCTORS T1 :: * -> * data T1 a - No C type associated - Roles: [representational] - RecFlag NonRecursive, Not promotable - = K1 :: forall a. (IO a) -> T1 a Stricts: _ - FamilyInstance: none + No C type associated + Roles: [representational] + RecFlag NonRecursive, Not promotable + = K1 :: forall a. (IO a) -> T1 a Stricts: _ + FamilyInstance: none T2 :: * -> * data T2 a - No C type associated - Roles: [representational] - RecFlag NonRecursive, Not promotable - = K2 :: forall a. (FunPtr a) -> T2 a Stricts: _ - FamilyInstance: none + No C type associated + Roles: [representational] + RecFlag NonRecursive, Not promotable + = K2 :: forall a. (FunPtr a) -> T2 a Stricts: _ + FamilyInstance: none COERCION AXIOMS Dependent modules: [] Dependent packages: [base, ghc-prim, integer-gmp] diff --git a/testsuite/tests/roles/should_compile/all.T b/testsuite/tests/roles/should_compile/all.T index a016de3..f77e61f 100644 --- a/testsuite/tests/roles/should_compile/all.T +++ b/testsuite/tests/roles/should_compile/all.T @@ -1,5 +1,5 @@ -test('Roles1', only_ways('normal'), compile, ['-ddump-tc']) -test('Roles2', only_ways('normal'), compile, ['-ddump-tc']) +test('Roles1', only_ways('normal'), compile, ['-ddump-tc -fprint-explicit-foralls']) +test('Roles2', only_ways('normal'), compile, ['-ddump-tc -fprint-explicit-foralls']) test('Roles3', only_ways('normal'), compile, ['-ddump-tc']) test('Roles4', only_ways('normal'), compile, ['-ddump-tc']) test('Roles13', only_ways('normal'), compile, ['-ddump-simpl -dsuppress-uniques']) diff --git a/testsuite/tests/typecheck/should_compile/tc231.stderr b/testsuite/tests/typecheck/should_compile/tc231.stderr index 4334d62..16dddda 100644 --- a/testsuite/tests/typecheck/should_compile/tc231.stderr +++ b/testsuite/tests/typecheck/should_compile/tc231.stderr @@ -10,21 +10,20 @@ TYPE CONSTRUCTORS No C type associated Roles: [representational, representational, representational] RecFlag NonRecursive, Promotable - = Node :: forall s a chain. s -> a -> chain -> Q s a chain - Stricts: _ _ _ + = Node :: s -> a -> chain -> Q s a chain Stricts: _ _ _ FamilyInstance: none Z :: * -> * data Z a No C type associated Roles: [representational] RecFlag NonRecursive, Promotable - = Z :: forall a. a -> Z a Stricts: _ + = Z :: a -> Z a Stricts: _ FamilyInstance: none Zork :: * -> * -> * -> Constraint class Zork s a b | a -> b Roles: [nominal, nominal, nominal] RecFlag NonRecursive - huh :: forall chain. Q s a chain -> ST s () + huh :: Q s a chain -> ST s () COERCION AXIOMS axiom ShouldCompile.NTCo:Zork :: Zork s a b = forall chain. Q s a chain -> ST s () From git at git.haskell.org Thu Mar 20 07:52:20 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 20 Mar 2014 07:52:20 +0000 (UTC) Subject: [commit: ghc] master: Don't use gcptr for interior pointers (a6939ec) Message-ID: <20140320075221.0A7922406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a6939ec29a9238cee38bee20844ae8cdcd4952fd/ghc >--------------------------------------------------------------- commit a6939ec29a9238cee38bee20844ae8cdcd4952fd Author: Johan Tibell Date: Thu Mar 20 07:58:10 2014 +0100 Don't use gcptr for interior pointers gcptr should only be used for pointers that the GC should follow. While this didn't cause any bugs right now, since these variables aren't live over a GC, it's clearer to use the right type. >--------------------------------------------------------------- a6939ec29a9238cee38bee20844ae8cdcd4952fd rts/PrimOps.cmm | 18 ++++++++---------- 1 file changed, 8 insertions(+), 10 deletions(-) diff --git a/rts/PrimOps.cmm b/rts/PrimOps.cmm index 0e547be..25e6534 100644 --- a/rts/PrimOps.cmm +++ b/rts/PrimOps.cmm @@ -142,8 +142,7 @@ stg_newAlignedPinnedByteArrayzh ( W_ n, W_ alignment ) stg_casIntArrayzh( gcptr arr, W_ ind, W_ old, W_ new ) /* MutableByteArray# s -> Int# -> Int# -> Int# -> State# s -> (# State# s, Int# #) */ { - gcptr p; - W_ h; + W_ p, h; p = arr + SIZEOF_StgArrWords + WDS(ind); (h) = ccall cas(p, old, new); @@ -155,8 +154,7 @@ stg_casIntArrayzh( gcptr arr, W_ ind, W_ old, W_ new ) stg_fetchAddIntArrayzh( gcptr arr, W_ ind, W_ incr ) /* MutableByteArray# s -> Int# -> Int# -> State# s -> (# State# s, Int# #) */ { - gcptr p; - W_ h; + W_ p, h; p = arr + SIZEOF_StgArrWords + WDS(ind); (h) = ccall atomic_inc(p, incr); @@ -167,8 +165,8 @@ stg_fetchAddIntArrayzh( gcptr arr, W_ ind, W_ incr ) stg_newArrayzh ( W_ n /* words */, gcptr init ) { - W_ words, size; - gcptr p, arr; + W_ words, size, p; + gcptr arr; again: MAYBE_GC(again); @@ -231,8 +229,8 @@ stg_unsafeThawArrayzh ( gcptr arr ) stg_casArrayzh ( gcptr arr, W_ ind, gcptr old, gcptr new ) /* MutableArray# s a -> Int# -> a -> a -> State# s -> (# State# s, Int#, Any a #) */ { - gcptr p, h; - W_ len; + gcptr h; + W_ p, len; p = arr + SIZEOF_StgMutArrPtrs + WDS(ind); (h) = ccall cas(p, old, new); @@ -252,8 +250,8 @@ stg_casArrayzh ( gcptr arr, W_ ind, gcptr old, gcptr new ) stg_newArrayArrayzh ( W_ n /* words */ ) { - W_ words, size; - gcptr p, arr; + W_ words, size, p; + gcptr arr; MAYBE_GC_N(stg_newArrayArrayzh, n); From git at git.haskell.org Fri Mar 21 12:48:32 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Mar 2014 12:48:32 +0000 (UTC) Subject: [commit: ghc] master: Flush after TH in #8884 test case (df409de) Message-ID: <20140321124833.16FD82406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/df409de9550dc8a07e010964a54112266d809341/ghc >--------------------------------------------------------------- commit df409de9550dc8a07e010964a54112266d809341 Author: Joachim Breitner Date: Fri Mar 21 13:46:15 2014 +0100 Flush after TH in #8884 test case (I recall that this was needed in some cases in the past, and might fix the validate error on travis.) >--------------------------------------------------------------- df409de9550dc8a07e010964a54112266d809341 testsuite/tests/th/T8884.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/testsuite/tests/th/T8884.hs b/testsuite/tests/th/T8884.hs index 782bf90..ca6ed9c 100644 --- a/testsuite/tests/th/T8884.hs +++ b/testsuite/tests/th/T8884.hs @@ -3,6 +3,7 @@ module T8884 where import Language.Haskell.TH +import System.IO type family Foo a where Foo x = x @@ -16,6 +17,7 @@ $( do FamilyI foo@(ClosedTypeFamilyD _ tvbs1 m_kind1 eqns1) [] <- reify ''Foo runIO $ putStrLn $ pprint foo runIO $ putStrLn $ pprint baz runIO $ putStrLn $ pprint inst + runIO $ hFlush stdout return [ ClosedTypeFamilyD (mkName "Foo'") tvbs1 m_kind1 eqns1 , FamilyD TypeFam (mkName "Baz'") tvbs2 m_kind2 , TySynInstD (mkName "Baz'") eqn2 ] ) From git at git.haskell.org Fri Mar 21 16:19:40 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Mar 2014 16:19:40 +0000 (UTC) Subject: [commit: packages/Win32] tag 'Win32-2.3.0.2-release' created Message-ID: <20140321161940.CF0D22406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/Win32 New tag : Win32-2.3.0.2-release Referencing: 4e60b809d21b40a17d96e8070c2993934ef77d28 From git at git.haskell.org Fri Mar 21 17:21:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Mar 2014 17:21:52 +0000 (UTC) Subject: [commit: haddock] ghc-7.8: Merge remote-tracking branch 'v2.14' into ghc-7.8 (e0299ec) Message-ID: <20140321172152.AD8702406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : ghc-7.8 Link : http://git.haskell.org/haddock.git/commitdiff/e0299ec51516db981ec0aeb74982d0e7dfc03c58 >--------------------------------------------------------------- commit e0299ec51516db981ec0aeb74982d0e7dfc03c58 Merge: d74fe55 40d2b41 Author: Herbert Valerio Riedel Date: Fri Mar 21 18:20:37 2014 +0100 Merge remote-tracking branch 'v2.14' into ghc-7.8 Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- e0299ec51516db981ec0aeb74982d0e7dfc03c58 haddock.cabal | 2 +- html-test/ref/DeprecatedClass.html | 16 -- html-test/ref/Hash.html | 8 - html-test/ref/Test.html | 8 - html-test/ref/Ticket61.html | 8 - html-test/ref/TypeFamilies.html | 304 ++++++++++++++++++++++-------- html-test/src/Minimal.hs | 40 ++++ html-test/src/TypeFamilies.hs | 16 +- resources/html/Ocean.std-theme/ocean.css | 7 +- src/Haddock/Backends/Xhtml/Decl.hs | 23 ++- src/Haddock/Backends/Xhtml/Layout.hs | 8 +- 11 files changed, 298 insertions(+), 142 deletions(-) From git at git.haskell.org Fri Mar 21 17:21:54 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Mar 2014 17:21:54 +0000 (UTC) Subject: [commit: haddock] ghc-7.8's head updated: Merge remote-tracking branch 'v2.14' into ghc-7.8 (e0299ec) Message-ID: <20140321172154.C74412406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock Branch 'ghc-7.8' now includes: 620e062 Add Fuuzetsu maintainers field in cabal file cac5384 Hide minimal definition for only-method classes 40d2b41 Fix issue #281 e0299ec Merge remote-tracking branch 'v2.14' into ghc-7.8 From git at git.haskell.org Fri Mar 21 17:48:18 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Mar 2014 17:48:18 +0000 (UTC) Subject: [commit: haddock] v2.14: Please cabal sdist (78d195c) Message-ID: <20140321174818.734282406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : v2.14 Link : http://git.haskell.org/haddock.git/commitdiff/78d195c4165a34510d0cffef513851500fe121fd >--------------------------------------------------------------- commit 78d195c4165a34510d0cffef513851500fe121fd Author: Mateusz Kowalczyk Date: Fri Mar 21 17:46:18 2014 +0000 Please cabal sdist >--------------------------------------------------------------- 78d195c4165a34510d0cffef513851500fe121fd haddock.cabal | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/haddock.cabal b/haddock.cabal index 84e5b9d..40591fa 100644 --- a/haddock.cabal +++ b/haddock.cabal @@ -31,9 +31,9 @@ extra-source-files: src/haddock.sh html-test/src/*.hs html-test/ref/*.html - latex-test/src/*.hs - latex-test/ref/*/*.tex - latex-test/ref/*/*.sty + latex-test/src/Simple/*.hs + latex-test/ref/Simple/*.tex + latex-test/ref/Simple/*.sty data-dir: resources data-files: html/frames.html From git at git.haskell.org Fri Mar 21 17:48:51 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Mar 2014 17:48:51 +0000 (UTC) Subject: [commit: haddock] master: Please cabal sdist (77af42d) Message-ID: <20140321174851.ECF852406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : master Link : http://git.haskell.org/haddock.git/commitdiff/77af42d7c5752214b1d5a762f3fec77910d583aa >--------------------------------------------------------------- commit 77af42d7c5752214b1d5a762f3fec77910d583aa Author: Mateusz Kowalczyk Date: Fri Mar 21 17:46:18 2014 +0000 Please cabal sdist >--------------------------------------------------------------- 77af42d7c5752214b1d5a762f3fec77910d583aa haddock.cabal | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/haddock.cabal b/haddock.cabal index 0df89be..0739a17 100644 --- a/haddock.cabal +++ b/haddock.cabal @@ -31,9 +31,9 @@ extra-source-files: src/haddock.sh html-test/src/*.hs html-test/ref/*.html - latex-test/src/*.hs - latex-test/ref/*/*.tex - latex-test/ref/*/*.sty + latex-test/src/Simple/*.hs + latex-test/ref/Simple/*.tex + latex-test/ref/Simple/*.sty data-dir: resources data-files: html/frames.html From git at git.haskell.org Fri Mar 21 17:54:13 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Mar 2014 17:54:13 +0000 (UTC) Subject: [commit: haddock] ghc-7.8: Merge remote-tracking branch 'v2.14' into ghc-7.8 (3e6da2f) Message-ID: <20140321175413.6D5802406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : ghc-7.8 Link : http://git.haskell.org/haddock.git/commitdiff/3e6da2f7b2b734da7dfe688a9f0eb764dcf6e8f0 >--------------------------------------------------------------- commit 3e6da2f7b2b734da7dfe688a9f0eb764dcf6e8f0 Merge: e0299ec 78d195c Author: Herbert Valerio Riedel Date: Fri Mar 21 18:52:19 2014 +0100 Merge remote-tracking branch 'v2.14' into ghc-7.8 Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 3e6da2f7b2b734da7dfe688a9f0eb764dcf6e8f0 haddock.cabal | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) From git at git.haskell.org Fri Mar 21 17:54:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Mar 2014 17:54:15 +0000 (UTC) Subject: [commit: haddock] ghc-7.8's head updated: Merge remote-tracking branch 'v2.14' into ghc-7.8 (3e6da2f) Message-ID: <20140321175415.5FBEB2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock Branch 'ghc-7.8' now includes: 78d195c Please cabal sdist 3e6da2f Merge remote-tracking branch 'v2.14' into ghc-7.8 From git at git.haskell.org Fri Mar 21 18:32:40 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Mar 2014 18:32:40 +0000 (UTC) Subject: [commit: packages/filepath] master: Convert changelog to markdown (78748dc) Message-ID: <20140321183240.ADCDD2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/78748dc2ccbe2fb0d96963a8a1ad5057365eb6eb >--------------------------------------------------------------- commit 78748dc2ccbe2fb0d96963a8a1ad5057365eb6eb Author: Herbert Valerio Riedel Date: Fri Mar 21 19:13:28 2014 +0100 Convert changelog to markdown Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 78748dc2ccbe2fb0d96963a8a1ad5057365eb6eb changelog | 14 -------------- changelog.md | 23 +++++++++++++++++++++++ filepath.cabal | 2 +- 3 files changed, 24 insertions(+), 15 deletions(-) diff --git a/changelog b/changelog deleted file mode 100644 index 447eda6..0000000 --- a/changelog +++ /dev/null @@ -1,14 +0,0 @@ --*- changelog -*- - -1.3.0.2 Nov 2013 - * Update to Cabal 1.10 format - * Minor Haddock cleanups - -1.3.0.1 Sep 2012 - * Bundled with GHC 7.6.1 - * No changes - -1.3.0.0 Feb 2012 - * Bundled with GHC 7.4.1 - * Add support for SafeHaskell - * Fix `normalise` "/" to result in "/" rather than "/.". diff --git a/changelog.md b/changelog.md new file mode 100644 index 0000000..ef3eb46 --- /dev/null +++ b/changelog.md @@ -0,0 +1,23 @@ +# Changelog for [`filepath` package](http://hackage.haskell.org/package/filepath) + +## 1.3.0.2 *Mar 2014* + + * Bundled with GHC 7.8.1 + + * Update to Cabal 1.10 format + + * Minor Haddock cleanups + +## 1.3.0.1 *Sep 2012* + + * Bundled with GHC 7.6.1 + + * No changes + +## 1.3.0.0 *Feb 2012* + + * Bundled with GHC 7.4.1 + + * Add support for SafeHaskell + + * Fix `normalise "/"` to result in `"/"` rather than `"/."` diff --git a/filepath.cabal b/filepath.cabal index e2b45ec..c510089 100644 --- a/filepath.cabal +++ b/filepath.cabal @@ -23,7 +23,7 @@ description: Extra-Source-Files: System/FilePath/Internal.hs README.md - changelog + changelog.md Library default-language: Haskell98 From git at git.haskell.org Fri Mar 21 18:32:42 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Mar 2014 18:32:42 +0000 (UTC) Subject: [commit: packages/filepath] master: Minor refactorings as suggested by hlint (486373c) Message-ID: <20140321183242.B8EB22406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath On branch : master Link : http://git.haskell.org/packages/filepath.git/commitdiff/486373cb6bc3de8bf7f0b8532558c5fff32df20a >--------------------------------------------------------------- commit 486373cb6bc3de8bf7f0b8532558c5fff32df20a Author: Herbert Valerio Riedel Date: Fri Mar 21 19:31:22 2014 +0100 Minor refactorings as suggested by hlint Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 486373cb6bc3de8bf7f0b8532558c5fff32df20a System/FilePath/Internal.hs | 16 +++++++--------- 1 file changed, 7 insertions(+), 9 deletions(-) diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs index b509541..09f3560 100644 --- a/System/FilePath/Internal.hs +++ b/System/FilePath/Internal.hs @@ -87,7 +87,7 @@ module System.FilePath.MODULE_NAME ) where -import Data.Char(toLower, toUpper) +import Data.Char(toLower, toUpper, isAsciiLower, isAsciiUpper) import Data.Maybe(isJust, fromJust) import Data.List(isPrefixOf) @@ -304,7 +304,7 @@ takeExtensions = snd . splitExtensions -- | Is the given character a valid drive letter? -- only a-z and A-Z are letters, not isAlpha which is more unicodey isLetter :: Char -> Bool -isLetter x = (x >= 'a' && x <= 'z') || (x >= 'A' && x <= 'Z') +isLetter x = isAsciiLower x || isAsciiUpper x -- | Split a path into a drive and a path. @@ -536,9 +536,7 @@ dropTrailingPathSeparator x = -- > Windows: takeDirectory "foo\\bar\\\\" == "foo\\bar" -- > Windows: takeDirectory "C:\\" == "C:\\" takeDirectory :: FilePath -> FilePath -takeDirectory x = if isDrive file then file - else if null res && not (null file) then file - else res +takeDirectory x = if isDrive file || (null res && not (null file)) then file else res where res = reverse $ dropWhile isPathSeparator $ reverse file file = dropFileName x @@ -593,7 +591,7 @@ splitPath x = [drive | drive /= ""] ++ f path f y = (a++c) : f d where (a,b) = break isPathSeparator y - (c,d) = break (not . isPathSeparator) b + (c,d) = span isPathSeparator b -- | Just as 'splitPath', but don't add the trailing slashes to each element. -- @@ -608,7 +606,7 @@ splitDirectories path = where pathComponents = splitPath path - f xs = map g xs + f = map g g x = if null res then x else res where res = takeWhile (not . isPathSeparator) x @@ -621,7 +619,7 @@ splitDirectories path = -- Note that this definition on c:\\c:\\, join then split will give c:\\. joinPath :: [FilePath] -> FilePath -joinPath x = foldr combine "" x +joinPath = foldr combine "" @@ -799,7 +797,7 @@ makeValid path = joinDrive drv $ validElements $ validChars pth where (drv,pth) = splitDrive path - validChars x = map f x + validChars = map f f x | x `elem` badCharacters = '_' | otherwise = x From git at git.haskell.org Fri Mar 21 18:44:51 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Mar 2014 18:44:51 +0000 (UTC) Subject: [commit: packages/filepath] ghc-7.8's head updated: Minor refactorings as suggested by hlint (486373c) Message-ID: <20140321184453.BD98D2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath Branch 'ghc-7.8' now includes: 78748dc Convert changelog to markdown 486373c Minor refactorings as suggested by hlint From git at git.haskell.org Fri Mar 21 21:18:18 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Mar 2014 21:18:18 +0000 (UTC) Subject: [commit: packages/filepath] tag 'filepath-1.3.0.2-release' created Message-ID: <20140321211818.50D982406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/filepath New tag : filepath-1.3.0.2-release Referencing: b8b8362db4c4fbbd96b758eb28481cac8b7ced27 From git at git.haskell.org Fri Mar 21 22:09:45 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Mar 2014 22:09:45 +0000 (UTC) Subject: [commit: packages/directory] master: Bump to version 1.2.1.0 and add missing /Since/-annotations (68f85c8) Message-ID: <20140321220946.09D742406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/68f85c8b2b3553fe36f0b8783574cdd7201209e4/directory >--------------------------------------------------------------- commit 68f85c8b2b3553fe36f0b8783574cdd7201209e4 Author: Herbert Valerio Riedel Date: Fri Mar 21 23:03:49 2014 +0100 Bump to version 1.2.1.0 and add missing /Since/-annotations The /Since/-annotations and version bump are due to newly exported symbols (added via 7789d1cc) Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 68f85c8b2b3553fe36f0b8783574cdd7201209e4 System/Directory.hs | 6 ++++++ directory.cabal | 2 +- 2 files changed, 7 insertions(+), 1 deletion(-) diff --git a/System/Directory.hs b/System/Directory.hs index ab035d8..739892c 100644 --- a/System/Directory.hs +++ b/System/Directory.hs @@ -757,6 +757,8 @@ findExecutable fileName = do -- | Given a file name, searches for the file and returns a list of all -- occurences that are executable. +-- +-- /Since: 1.2.1.0/ findExecutables :: String -> IO [FilePath] findExecutables binary = do #if defined(mingw32_HOST_OS) @@ -779,12 +781,16 @@ findFile path fileName = do -- | Search through the given set of directories for the given file and -- returns a list of paths where the given file exists. +-- +-- /Since: 1.2.1.0/ findFiles :: [FilePath] -> String -> IO [FilePath] findFiles = findFilesWith (\_ -> return True) -- | Search through the given set of directories for the given file and -- with the given property (usually permissions) and returns a list of -- paths where the given file exists and has the property. +-- +-- /Since: 1.2.1.0/ findFilesWith :: (FilePath -> IO Bool) -> [FilePath] -> String -> IO [FilePath] findFilesWith _ [] _ = return [] findFilesWith f (d:ds) fileName = do diff --git a/directory.cabal b/directory.cabal index c4dc921..cce1aa2 100644 --- a/directory.cabal +++ b/directory.cabal @@ -1,5 +1,5 @@ name: directory -version: 1.2.0.2 +version: 1.2.1.0 -- GHC 7.6.3 released with 1.2.0.1 license: BSD3 license-file: LICENSE From git at git.haskell.org Fri Mar 21 22:09:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Mar 2014 22:09:47 +0000 (UTC) Subject: [commit: packages/directory] master: Convert changelog to markdown (0c64d54) Message-ID: <20140321220947.C7F762406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0c64d5420e54bb871f0407a4ec3155c6be600756/directory >--------------------------------------------------------------- commit 0c64d5420e54bb871f0407a4ec3155c6be600756 Author: Herbert Valerio Riedel Date: Fri Mar 21 23:02:38 2014 +0100 Convert changelog to markdown (and update changelog while at it) Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 0c64d5420e54bb871f0407a4ec3155c6be600756 changelog | 11 ----------- changelog.md | 21 +++++++++++++++++++++ directory.cabal | 2 +- 3 files changed, 22 insertions(+), 12 deletions(-) diff --git a/changelog b/changelog deleted file mode 100644 index 8f2cf93..0000000 --- a/changelog +++ /dev/null @@ -1,11 +0,0 @@ --*-changelog-*- - -1.2.0.2 Oct 2013 - - * Add support for sub-second precision in `getModificationTime` - when linked against `unix>=2.6.0.0` - * Fix `createDirectoryIfMissing _ "."` in `C:\` on Windows - * Remove support for NHC98 compiler - * Update package to `cabal-version >= 1.10` format - * Enhance Haddock documentation for `doesDirectoryExist` and - `canonicalizePath` diff --git a/changelog.md b/changelog.md new file mode 100644 index 0000000..4796194 --- /dev/null +++ b/changelog.md @@ -0,0 +1,21 @@ +# Changelog for [`directory` package](http://hackage.haskell.org/package/directory) + +## 1.2.1.0 *Mar 2014* + + * Bundled with GHC 7.8.1 + + * Add support for sub-second precision in `getModificationTime` when + linked against `unix>=2.6.0.0` + + * Fix `createDirectoryIfMissing _ "."` in `C:\` on Windows + + * Remove support for NHC98 compiler + + * Update package to `cabal-version >= 1.10` format + + * Enhance Haddock documentation for `doesDirectoryExist` and + `canonicalizePath` + + * Fix `findExecutable` to check that file permissions indicate executable + + * New convenience functions `findFiles` and `findFilesWith` diff --git a/directory.cabal b/directory.cabal index cce1aa2..de282df 100644 --- a/directory.cabal +++ b/directory.cabal @@ -20,7 +20,7 @@ extra-tmp-files: include/HsDirectoryConfig.h extra-source-files: - changelog + changelog.md config.guess config.sub configure From git at git.haskell.org Fri Mar 21 22:13:18 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 21 Mar 2014 22:13:18 +0000 (UTC) Subject: [commit: packages/directory] ghc-7.8's head updated: Convert changelog to markdown (0c64d54) Message-ID: <20140321221318.AE4AE2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory Branch 'ghc-7.8' now includes: 68f85c8 Bump to version 1.2.1.0 and add missing /Since/-annotations 0c64d54 Convert changelog to markdown From git at git.haskell.org Sat Mar 22 01:10:32 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 01:10:32 +0000 (UTC) Subject: [commit: ghc] master: Typos (ba0c012) Message-ID: <20140322011032.D68922406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ba0c0123fb2f6942f57636ca458d5a87870f1ecc/ghc >--------------------------------------------------------------- commit ba0c0123fb2f6942f57636ca458d5a87870f1ecc Author: Austin Seipp Date: Fri Mar 21 04:36:23 2014 -0500 Typos Signed-off-by: Austin Seipp >--------------------------------------------------------------- ba0c0123fb2f6942f57636ca458d5a87870f1ecc compiler/main/HscTypes.lhs | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/compiler/main/HscTypes.lhs b/compiler/main/HscTypes.lhs index b8ecc10..c4c5efd 100644 --- a/compiler/main/HscTypes.lhs +++ b/compiler/main/HscTypes.lhs @@ -1119,10 +1119,10 @@ shadowed by the second declaration. But it has a respectable qualified name (Ghci1.T), and its source location says where it was defined. -So the main invariant continues to hold, that in any session an original -name M.T only refers to oe unique thing. (In a previous iteration both -the T's above were called :Interactive.T, albeit with different uniques, -which gave rise to all sorts of trouble.) +So the main invariant continues to hold, that in any session an +original name M.T only refers to one unique thing. (In a previous +iteration both the T's above were called :Interactive.T, albeit with +different uniques, which gave rise to all sorts of trouble.) The details are a bit tricky though: @@ -1132,7 +1132,7 @@ The details are a bit tricky though: * ic_tythings contains only things from the 'interactive' package. * Module from the 'interactive' package (Ghci1, Ghci2 etc) never go - in the Home Package Table (HPT). When you say :load, that's when + in the Home Package Table (HPT). When you say :load, that's when we extend the HPT. * The 'thisPackage' field of DynFlags is *not* set to 'interactive'. From git at git.haskell.org Sat Mar 22 01:10:35 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 01:10:35 +0000 (UTC) Subject: [commit: ghc] master: testsuite: add test for #8831 (f9b6a2b) Message-ID: <20140322011035.C6E772406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f9b6a2bb6574904ab11476d79896491b111ad7cc/ghc >--------------------------------------------------------------- commit f9b6a2bb6574904ab11476d79896491b111ad7cc Author: Austin Seipp Date: Fri Mar 21 04:42:32 2014 -0500 testsuite: add test for #8831 Signed-off-by: Austin Seipp >--------------------------------------------------------------- f9b6a2bb6574904ab11476d79896491b111ad7cc .../tests/{driver/recomp009/Sub1.hs => ghci/scripts/T8831.hs} | 4 ++-- testsuite/tests/ghci/scripts/T8831.script | 4 ++++ .../should_run/cgrun049.stdout => ghci/scripts/T8831.stdout} | 0 testsuite/tests/ghci/scripts/all.T | 2 +- 4 files changed, 7 insertions(+), 3 deletions(-) diff --git a/testsuite/tests/driver/recomp009/Sub1.hs b/testsuite/tests/ghci/scripts/T8831.hs similarity index 50% copy from testsuite/tests/driver/recomp009/Sub1.hs copy to testsuite/tests/ghci/scripts/T8831.hs index 25ea755..b0a3cc5 100644 --- a/testsuite/tests/driver/recomp009/Sub1.hs +++ b/testsuite/tests/ghci/scripts/T8831.hs @@ -1,3 +1,3 @@ {-# LANGUAGE TemplateHaskell #-} -module Sub where -x = [| 1 |] +module T8831 where +foo = [| 3 |] diff --git a/testsuite/tests/ghci/scripts/T8831.script b/testsuite/tests/ghci/scripts/T8831.script new file mode 100644 index 0000000..bc6ba89 --- /dev/null +++ b/testsuite/tests/ghci/scripts/T8831.script @@ -0,0 +1,4 @@ +:seti -XTemplateHaskell +:load T8831.hs +$foo + diff --git a/testsuite/tests/codeGen/should_run/cgrun049.stdout b/testsuite/tests/ghci/scripts/T8831.stdout similarity index 100% copy from testsuite/tests/codeGen/should_run/cgrun049.stdout copy to testsuite/tests/ghci/scripts/T8831.stdout diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T index 6812c9d..bc5597d 100755 --- a/testsuite/tests/ghci/scripts/all.T +++ b/testsuite/tests/ghci/scripts/all.T @@ -168,4 +168,4 @@ test('T8674', normal, ghci_script, ['T8674.script']) test('T8696', normal, ghci_script, ['T8696.script']) test('T8776', normal, ghci_script, ['T8776.script']) test('ghci059', normal, ghci_script, ['ghci059.script']) - +test('T8831', normal, ghci_script, ['T8831.script']) From git at git.haskell.org Sat Mar 22 01:10:38 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 01:10:38 +0000 (UTC) Subject: [commit: ghc] master: linker: Fix indirect calls for x86_64 windows (#2283) (7a1c851) Message-ID: <20140322011038.50C002406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7a1c85113dd082153cc07f4792216beaf34daeeb/ghc >--------------------------------------------------------------- commit 7a1c85113dd082153cc07f4792216beaf34daeeb Author: Kyrill Briantsev Date: Fri Mar 21 05:42:48 2014 -0500 linker: Fix indirect calls for x86_64 windows (#2283) Signed-off-by: Austin Seipp >--------------------------------------------------------------- 7a1c85113dd082153cc07f4792216beaf34daeeb rts/Linker.c | 30 ++++++++++++++++++++++++++++-- 1 file changed, 28 insertions(+), 2 deletions(-) diff --git a/rts/Linker.c b/rts/Linker.c index 8f57873..814f930 100644 --- a/rts/Linker.c +++ b/rts/Linker.c @@ -1718,6 +1718,18 @@ typedef /* A list thereof. */ static OpenedDLL* opened_dlls = NULL; + +/* A record for storing indirectly linked functions from DLLs. */ +typedef + struct _IndirectAddr { + void* addr; + struct _IndirectAddr* next; + } + IndirectAddr; + +/* A list thereof. */ +static IndirectAddr* indirects = NULL; + #endif # if defined(OBJFORMAT_ELF) || defined(OBJFORMAT_MACHO) @@ -2189,6 +2201,15 @@ void freeObjectCode (ObjectCode *oc) stgFree(oc->image); #else VirtualFree(oc->image - PEi386_IMAGE_OFFSET, 0, MEM_RELEASE); + + IndirectAddr *ia, *ia_next; + ia = indirects; + while (ia != NULL) { + ia_next = ia->next; + stgFree(ia); + ia = ia_next; + } + #endif #if defined(powerpc_HOST_ARCH) || defined(x86_64_HOST_ARCH) || defined(arm_HOST_ARCH) @@ -3698,15 +3719,20 @@ lookupSymbolInDLLs ( UChar *lbl ) Long description: http://support.microsoft.com/kb/132044 tl;dr: If C/C++ compiler sees __declspec(dllimport) ... foo ... - it generates call __imp_foo, and __imp_foo here has exactly + it generates call *__imp_foo, and __imp_foo here has exactly the same semantics as in __imp_foo = GetProcAddress(..., "foo") */ if (sym == NULL && strncmp ((const char*)lbl, "__imp_", 6) == 0) { sym = GetProcAddress(o_dll->instance, (char*)(lbl+6)); if (sym != NULL) { + IndirectAddr* ret; + ret = stgMallocBytes( sizeof(IndirectAddr), "lookupSymbolInDLLs" ); + ret->addr = sym; + ret->next = indirects; + indirects = ret; errorBelch("warning: %s from %S is linked instead of %s", (char*)(lbl+6), o_dll->name, (char*)lbl); - return sym; + return (void*) & ret->addr; } } From git at git.haskell.org Sat Mar 22 01:10:40 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 01:10:40 +0000 (UTC) Subject: [commit: ghc] master: Update ghc --help references to --make and a.out (fixes #8600) (99ef279) Message-ID: <20140322011040.D90982406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/99ef27913dbe55fa57891bbf97d131e0933733e3/ghc >--------------------------------------------------------------- commit 99ef27913dbe55fa57891bbf97d131e0933733e3 Author: ccatalfo Date: Tue Mar 11 22:11:11 2014 -0400 Update ghc --help references to --make and a.out (fixes #8600) Signed-off-by: Austin Seipp >--------------------------------------------------------------- 99ef27913dbe55fa57891bbf97d131e0933733e3 driver/ghc-usage.txt | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/driver/ghc-usage.txt b/driver/ghc-usage.txt index 239b454..9de4090 100644 --- a/driver/ghc-usage.txt +++ b/driver/ghc-usage.txt @@ -5,12 +5,12 @@ Usage: To compile and link a complete Haskell program, run the compiler like so: - $$ --make Main + $$ Main where the module Main is in a file named Main.hs (or Main.lhs) in the current directory. The other modules in the program will be located and compiled automatically, and the linked program will be placed in -the file `a.out' (or `Main.exe' on Windows). +the file `Main' (or `Main.exe' on Windows). Alternatively, $$ can be used to compile files individually. Each input file is guided through (some of the) possible phases of a From git at git.haskell.org Sat Mar 22 08:51:42 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 08:51:42 +0000 (UTC) Subject: [commit: packages/old-locale] master: Add changelog and update Cabal file (d0c1d68) Message-ID: <20140322085142.C1B912406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/old-locale On branch : master Link : http://git.haskell.org/packages/old-locale.git/commitdiff/d0c1d68d0232500d875384d8a5abd936f8a6b9bf >--------------------------------------------------------------- commit d0c1d68d0232500d875384d8a5abd936f8a6b9bf Author: Herbert Valerio Riedel Date: Sat Mar 22 09:19:25 2014 +0100 Add changelog and update Cabal file Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- d0c1d68d0232500d875384d8a5abd936f8a6b9bf changelog.md | 19 +++++++++++++++++++ old-locale.cabal | 5 ++++- 2 files changed, 23 insertions(+), 1 deletion(-) diff --git a/changelog.md b/changelog.md new file mode 100644 index 0000000..7f59c7a --- /dev/null +++ b/changelog.md @@ -0,0 +1,19 @@ +# Changelog for [`old-locale` package](http://hackage.haskell.org/package/old-locale) + +## 1.0.0.6 *Mar 2014* + + * Bundled with GHC 7.8.1 + + * Update to Cabal 1.10 format + +## 1.0.0.5 *Sep 2012* + + * Bundled with GHC 7.6.1 + + * Un-deprecate `old-locale` package + +## 1.0.0.4 *Feb 2012* + + * Bundled with GHC 7.4.1 + + * Add support for SafeHaskell diff --git a/old-locale.cabal b/old-locale.cabal index 9b94fc1..e535fe1 100644 --- a/old-locale.cabal +++ b/old-locale.cabal @@ -14,11 +14,14 @@ description: This package provides the ability to adapt to locale conventions such as date and time formats. +extra-source-files: + changelog.md + source-repository head type: git location: http://git.haskell.org/packages/old-locale.git -source-repository head +source-repository this type: git location: http://git.haskell.org/packages/old-locale.git tag: old-locale-1.0.0.6-release From git at git.haskell.org Sat Mar 22 08:51:44 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 08:51:44 +0000 (UTC) Subject: [commit: packages/old-locale] master: Update Haddock comments (7e7f672) Message-ID: <20140322085144.D94522406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/old-locale On branch : master Link : http://git.haskell.org/packages/old-locale.git/commitdiff/7e7f6722895af36ca4e2f60f2fdfdc056b70db0b >--------------------------------------------------------------- commit 7e7f6722895af36ca4e2f60f2fdfdc056b70db0b Author: Herbert Valerio Riedel Date: Sat Mar 22 09:51:11 2014 +0100 Update Haddock comments Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 7e7f6722895af36ca4e2f60f2fdfdc056b70db0b System/Locale.hs | 20 ++++++++++++++------ changelog.md | 2 ++ 2 files changed, 16 insertions(+), 6 deletions(-) diff --git a/System/Locale.hs b/System/Locale.hs index c9469db..2a87af2 100644 --- a/System/Locale.hs +++ b/System/Locale.hs @@ -6,16 +6,17 @@ -- | -- Module : System.Locale -- Copyright : (c) The University of Glasgow 2001 --- License : BSD-style (see the file libraries/base/LICENSE) +-- License : BSD3 (see LICENSE file) -- -- Maintainer : libraries at haskell.org -- Stability : stable -- Portability : portable -- -- This module provides the ability to adapt to local conventions. +-- -- At present, it supports only time and date information as used by --- System.Time.calendarTimeToString from the System.Time module in the --- old-time package. +-- @calendarTimeToString@ from the @System.Time@ module in the +-- @old-time@ package. -- ----------------------------------------------------------------------------- @@ -76,8 +77,15 @@ defaultTimeLocale = TimeLocale { } --- |Normally, ISO-8601 just defines YYYY-MM-DD --- but we can add a time spec. +{- | Construct format string according to . + +The @Maybe String@ argument allows to supply an optional time specification. E.g.: + +@ +'iso8601DateFormat' Nothing == "%Y-%m-%d" -- i.e. @/YYYY-MM-DD/@ +'iso8601DateFormat' (Just "%H:%M:%S") == "%Y-%m-%dT%H:%M:%S" -- i.e. @/YYYY-MM-DD/T/HH:MM:SS/@ +@ +-} iso8601DateFormat :: Maybe String -> String iso8601DateFormat mTimeFmt = @@ -85,6 +93,6 @@ iso8601DateFormat mTimeFmt = Nothing -> "" Just fmt -> 'T' : fmt - +-- | Format string according to . rfc822DateFormat :: String rfc822DateFormat = "%a, %_d %b %Y %H:%M:%S %Z" diff --git a/changelog.md b/changelog.md index 7f59c7a..65ba802 100644 --- a/changelog.md +++ b/changelog.md @@ -4,6 +4,8 @@ * Bundled with GHC 7.8.1 + * Update Haddock comments + * Update to Cabal 1.10 format ## 1.0.0.5 *Sep 2012* From git at git.haskell.org Sat Mar 22 08:55:13 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 08:55:13 +0000 (UTC) Subject: [commit: packages/old-locale] ghc-7.8's head updated: Update Haddock comments (7e7f672) Message-ID: <20140322085513.61B092406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/old-locale Branch 'ghc-7.8' now includes: d0c1d68 Add changelog and update Cabal file 7e7f672 Update Haddock comments From git at git.haskell.org Sat Mar 22 08:55:37 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 08:55:37 +0000 (UTC) Subject: [commit: packages/old-locale] tag 'old-locale-1.0.0.6-release' created Message-ID: <20140322085537.1887E2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/old-locale New tag : old-locale-1.0.0.6-release Referencing: 8dd47749382cbd0b6407d8321a7a667e2b18442b From git at git.haskell.org Sat Mar 22 09:32:26 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 09:32:26 +0000 (UTC) Subject: [commit: ghc] master: codeGen: inline allocation optimization for clone array primops (1eece45) Message-ID: <20140322093226.753502406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1eece45692fb5d1a5f4ec60c1537f8068237e9c1/ghc >--------------------------------------------------------------- commit 1eece45692fb5d1a5f4ec60c1537f8068237e9c1 Author: Johan Tibell Date: Thu Mar 13 09:35:21 2014 +0100 codeGen: inline allocation optimization for clone array primops The inline allocation version is 69% faster than the out-of-line version, when cloning an array of 16 unit elements on a 64-bit machine. Comparing the new and the old primop implementations isn't straightforward. The old version had a missing heap check that I discovered during the development of the new version. Comparing the old and the new version would requiring fixing the old version, which in turn means reimplementing the equivalent of MAYBE_CG in StgCmmPrim. The inline allocation threshold is configurable via -fmax-inline-alloc-size which gives the maximum array size, in bytes, to allocate inline. The size does not include the closure header size. Allowing the same primop to be either inline or out-of-line has some implication for how we lay out heap checks. We always place a heap check around out-of-line primops, as they may allocate outside of our knowledge. However, for the inline primops we only allow allocation via the standard means (i.e. virtHp). Since the clone primops might be either inline or out-of-line the heap check layout code now consults shouldInlinePrimOp to know whether a primop will be inlined. >--------------------------------------------------------------- 1eece45692fb5d1a5f4ec60c1537f8068237e9c1 compiler/cmm/CLabel.hs | 6 +- compiler/codeGen/StgCmmExpr.hs | 33 +++-- compiler/codeGen/StgCmmPrim.hs | 132 ++++++++------------ compiler/main/DynFlags.hs | 12 +- compiler/prelude/primops.txt.pp | 4 + docs/users_guide/flags.xml | 13 ++ includes/Cmm.h | 31 +++++ includes/stg/MiscClosures.h | 4 + rts/Linker.c | 4 + rts/PrimOps.cmm | 21 ++++ testsuite/tests/codeGen/should_run/cgrun064.hs | 79 +++++++++++- testsuite/tests/codeGen/should_run/cgrun064.stdout | 8 ++ .../tests/perf/should_run/InlineCloneArrayAlloc.hs | 24 ++++ testsuite/tests/perf/should_run/all.T | 7 ++ 14 files changed, 279 insertions(+), 99 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1eece45692fb5d1a5f4ec60c1537f8068237e9c1 From git at git.haskell.org Sat Mar 22 09:43:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 09:43:01 +0000 (UTC) Subject: [commit: packages/old-time] master: Add changelog (8901741) Message-ID: <20140322094301.996C92406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/old-time On branch : master Link : http://git.haskell.org/packages/old-time.git/commitdiff/89017411036b24875393e4fd6ca8ef92fc181ad2 >--------------------------------------------------------------- commit 89017411036b24875393e4fd6ca8ef92fc181ad2 Author: Herbert Valerio Riedel Date: Sat Mar 22 10:41:25 2014 +0100 Add changelog Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 89017411036b24875393e4fd6ca8ef92fc181ad2 changelog.md | 19 +++++++++++++++++++ old-time.cabal | 1 + 2 files changed, 20 insertions(+) diff --git a/changelog.md b/changelog.md new file mode 100644 index 0000000..155acf7 --- /dev/null +++ b/changelog.md @@ -0,0 +1,19 @@ +# Changelog for [`old-time` package](http://hackage.haskell.org/package/old-time) + +## 1.1.0.2 *Mar 2014* + + * Bundled with GHC 7.8.1 + + * Supports `base-4.7.0.0` + + * Remove NHC98-specific code + + * Update to Cabal 1.10 format + +## 1.1.0.1 *Sep 2012* + + * Bundled with GHC 7.6.1 + + * Don't include deprecated `` on FreeBSD + + * Fix `gettimeofday(2)` call on Win64 diff --git a/old-time.cabal b/old-time.cabal index 99bfdad..1d99557 100644 --- a/old-time.cabal +++ b/old-time.cabal @@ -18,6 +18,7 @@ description: extra-source-files: aclocal.m4 + changelog.md config.guess config.sub configure From git at git.haskell.org Sat Mar 22 09:43:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 09:43:11 +0000 (UTC) Subject: [commit: packages/old-time] ghc-7.8's head updated: Add changelog (8901741) Message-ID: <20140322094311.8E8862406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/old-time Branch 'ghc-7.8' now includes: 8901741 Add changelog From git at git.haskell.org Sat Mar 22 09:43:22 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 09:43:22 +0000 (UTC) Subject: [commit: packages/old-time] tag 'old-time-1.1.0.2-release' created Message-ID: <20140322094322.843172406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/old-time New tag : old-time-1.1.0.2-release Referencing: 0083feb144b0a3e67a8f3c33159bc6b10ac2d508 From git at git.haskell.org Sat Mar 22 10:44:39 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 10:44:39 +0000 (UTC) Subject: [commit: packages/hoopl] master: Update hoopl.cabal and convert changelog to MD (e57da77) Message-ID: <20140322104439.BCD1B2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hoopl On branch : master Link : http://git.haskell.org/packages/hoopl.git/commitdiff/e57da77f74ef4e5b29801a2e44667a35c153410d >--------------------------------------------------------------- commit e57da77f74ef4e5b29801a2e44667a35c153410d Author: Herbert Valerio Riedel Date: Sat Mar 22 11:38:41 2014 +0100 Update hoopl.cabal and convert changelog to MD This is in preparation for the hoopl-3.10.0.0 and ghc-7.8.1 release Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- e57da77f74ef4e5b29801a2e44667a35c153410d changelog | 270 -------------------------------------------------------- changelog.md | 278 ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ hoopl.cabal | 25 +++--- 3 files changed, 291 insertions(+), 282 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc e57da77f74ef4e5b29801a2e44667a35c153410d From git at git.haskell.org Sat Mar 22 10:44:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 10:44:50 +0000 (UTC) Subject: [commit: packages/hoopl] ghc-7.8's head updated: Update hoopl.cabal and convert changelog to MD (e57da77) Message-ID: <20140322104450.CE5C52406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hoopl Branch 'ghc-7.8' now includes: e57da77 Update hoopl.cabal and convert changelog to MD From git at git.haskell.org Sat Mar 22 10:51:40 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 10:51:40 +0000 (UTC) Subject: [commit: packages/hoopl] tag 'hoopl-3.10.0.0-release' created Message-ID: <20140322105140.869AC2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hoopl New tag : hoopl-3.10.0.0-release Referencing: 4d6643bedf971729d1c581f6d372d6ea1c73bc72 From git at git.haskell.org Sat Mar 22 10:53:30 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 10:53:30 +0000 (UTC) Subject: [commit: ghc] master: Mark test for #8831 as known-broken (4bc3c82) Message-ID: <20140322105330.EC17E2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4bc3c8265f988f4456664f502164f52466aab67d/ghc >--------------------------------------------------------------- commit 4bc3c8265f988f4456664f502164f52466aab67d Author: Joachim Breitner Date: Sat Mar 22 11:53:03 2014 +0100 Mark test for #8831 as known-broken to keep validate working. >--------------------------------------------------------------- 4bc3c8265f988f4456664f502164f52466aab67d testsuite/tests/ghci/scripts/all.T | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T index bc5597d..0181c2d 100755 --- a/testsuite/tests/ghci/scripts/all.T +++ b/testsuite/tests/ghci/scripts/all.T @@ -168,4 +168,4 @@ test('T8674', normal, ghci_script, ['T8674.script']) test('T8696', normal, ghci_script, ['T8696.script']) test('T8776', normal, ghci_script, ['T8776.script']) test('ghci059', normal, ghci_script, ['ghci059.script']) -test('T8831', normal, ghci_script, ['T8831.script']) +test('T8831', expect_broken(8831), ghci_script, ['T8831.script']) From git at git.haskell.org Sat Mar 22 11:29:08 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 11:29:08 +0000 (UTC) Subject: [commit: packages/hpc] ghc-7.8: Tweak Haddock docs (1d4ec41) Message-ID: <20140322112908.AD1332406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hpc On branch : ghc-7.8 Link : http://git.haskell.org/packages/hpc.git/commitdiff/1d4ec41feee8299b13e7f6a5a072251b2894f238 >--------------------------------------------------------------- commit 1d4ec41feee8299b13e7f6a5a072251b2894f238 Author: Herbert Valerio Riedel Date: Sat Mar 22 12:26:13 2014 +0100 Tweak Haddock docs Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 1d4ec41feee8299b13e7f6a5a072251b2894f238 Trace/Hpc/Mix.hs | 9 +++++---- Trace/Hpc/Tix.hs | 21 +++++++++++---------- Trace/Hpc/Util.hs | 6 +++--- 3 files changed, 19 insertions(+), 17 deletions(-) diff --git a/Trace/Hpc/Mix.hs b/Trace/Hpc/Mix.hs index a02cd46..e5396b2 100644 --- a/Trace/Hpc/Mix.hs +++ b/Trace/Hpc/Mix.hs @@ -6,7 +6,7 @@ -- Colin Runciman and Andy Gill, June 2006 --------------------------------------------------------------- --- | Datatypes and file-access routines for the per-module (.mix) +-- | Datatypes and file-access routines for the per-module (@.mix@) -- indexes used by Hpc. module Trace.Hpc.Mix ( Mix(..) @@ -34,10 +34,11 @@ import Trace.Hpc.Tix -- | 'Mix' is the information about a modules static properties, like -- location of Tix's in a file. --- tab stops are the size of a tab in the provided line:colunm values. +-- +-- Tab stops are the size of a tab in the provided /line:colunm/ values. +-- -- * In GHC, this is 1 (a tab is just a character) --- * With hpc-tracer, this is 8 (a tab represents several spaces). - +-- * With @hpc-tracer@, this is 8 (a tab represents several spaces). data Mix = Mix FilePath -- location of original file UTCTime -- time of original file's last update diff --git a/Trace/Hpc/Tix.hs b/Trace/Hpc/Tix.hs index 579d263..512c6c5 100644 --- a/Trace/Hpc/Tix.hs +++ b/Trace/Hpc/Tix.hs @@ -7,7 +7,7 @@ ------------------------------------------------------------ -- | Datatypes and file-access routines for the tick data file --- used by HPC. (.tix) +-- (@.tix@) used by Hpc. module Trace.Hpc.Tix(Tix(..), TixModule(..), tixModuleName, tixModuleHash, tixModuleTixs, readTix, writeTix, getTixFileName) where @@ -15,18 +15,19 @@ module Trace.Hpc.Tix(Tix(..), TixModule(..), import Data.List (isSuffixOf) import Trace.Hpc.Util (Hash, catchIO) --- 'Tix ' is the storage format for our dynamic imformation about what --- boxes are ticked. +-- | 'Tix' is the storage format for our dynamic imformation about +-- what boxes are ticked. data Tix = Tix [TixModule] deriving (Read, Show, Eq) data TixModule = TixModule - String -- module name - Hash -- hash number - Int -- length of tix list (allows pre-allocation at parse time). + String -- module name + Hash -- hash number + Int -- length of Tix list (allows pre-allocation at parse time). [Integer] -- actual ticks deriving (Read, Show, Eq) +-- TODO: Turn extractors below into proper 'TixModule' field-labels tixModuleName :: TixModule -> String tixModuleName (TixModule nm _ _ _) = nm tixModuleHash :: TixModule -> Hash @@ -36,7 +37,7 @@ tixModuleTixs (TixModule _ _ _ tixs) = tixs -- We /always/ read and write Tix from the current working directory. --- read a Tix File. +-- | Read a @.tix@ File. readTix :: String -> IO (Maybe Tix) readTix tix_filename = @@ -44,7 +45,7 @@ readTix tix_filename = return $ Just $ read contents) (\ _ -> return $ Nothing) --- write a Tix File. +-- | Write a @.tix@ File. writeTix :: String -> Tix -> IO () @@ -56,8 +57,8 @@ tixName :: String -> String tixName name = name ++ ".tix" -} --- getTixFullName takes a binary or .tix-file name, --- and normalizes it into a .tix-file name. +-- | 'getTixFullName' takes a binary or @.tix at -file name, +-- and normalizes it into a @.tix at -file name. getTixFileName :: String -> String getTixFileName str | ".tix" `isSuffixOf` str = str diff --git a/Trace/Hpc/Util.hs b/Trace/Hpc/Util.hs index 019f1c7..6846b2f 100644 --- a/Trace/Hpc/Util.hs +++ b/Trace/Hpc/Util.hs @@ -27,15 +27,15 @@ import Data.Word -- | 'HpcPos' is an Hpc local rendition of a Span. data HpcPos = P !Int !Int !Int !Int deriving (Eq, Ord) --- | 'fromHpcPos' explodes the HpcPos into line:column-line:colunm +-- | 'fromHpcPos' explodes the HpcPos into /line:column/-/line:colunm/ fromHpcPos :: HpcPos -> (Int,Int,Int,Int) fromHpcPos (P l1 c1 l2 c2) = (l1,c1,l2,c2) --- | 'toHpcPos' implodes to HpcPos, from line:column-line:colunm +-- | 'toHpcPos' implodes to HpcPos, from /line:column/-/line:colunm/ toHpcPos :: (Int,Int,Int,Int) -> HpcPos toHpcPos (l1,c1,l2,c2) = P l1 c1 l2 c2 --- | asks the question, is the first argument inside the second argument. +-- | Predicate determining whether the first argument is inside the second argument. insideHpcPos :: HpcPos -> HpcPos -> Bool insideHpcPos small big = sl1 >= bl1 && From git at git.haskell.org Sat Mar 22 11:29:10 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 11:29:10 +0000 (UTC) Subject: [commit: packages/hpc] ghc-7.8: Add changelog (50ed27f) Message-ID: <20140322112910.AB2AD2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hpc On branch : ghc-7.8 Link : http://git.haskell.org/packages/hpc.git/commitdiff/50ed27faf857380e282e0c85472a55210a5022c8 >--------------------------------------------------------------- commit 50ed27faf857380e282e0c85472a55210a5022c8 Author: Herbert Valerio Riedel Date: Sat Mar 22 12:27:10 2014 +0100 Add changelog Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 50ed27faf857380e282e0c85472a55210a5022c8 changelog.md | 11 +++++++++++ hpc.cabal | 3 +++ 2 files changed, 14 insertions(+) diff --git a/changelog.md b/changelog.md new file mode 100644 index 0000000..65446bc --- /dev/null +++ b/changelog.md @@ -0,0 +1,11 @@ +# Changelog for [`hpc` package](http://hackage.haskell.org/package/hpc) + +## 0.6.0.1 *Mar 2014* + + * Bundled with GHC 7.8.1 + + * Update to Cabal 1.10 format + + * Drop support for GHC prior to version 7.2.2 + + * Minor improvements to Haddock docs diff --git a/hpc.cabal b/hpc.cabal index 2304e58..42e4d3b 100644 --- a/hpc.cabal +++ b/hpc.cabal @@ -17,6 +17,9 @@ description: See for more information. +extra-source-files: + changelog.md + source-repository head type: git location: http://git.haskell.org/packages/hpc.git From git at git.haskell.org Sat Mar 22 11:29:18 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 11:29:18 +0000 (UTC) Subject: [commit: packages/hpc] master's head updated: Add changelog (50ed27f) Message-ID: <20140322112919.373BF2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hpc Branch 'master' now includes: 1d4ec41 Tweak Haddock docs 50ed27f Add changelog From git at git.haskell.org Sat Mar 22 11:33:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 11:33:52 +0000 (UTC) Subject: [commit: packages/hpc] tag 'hpc-0.6.0.1-release' created Message-ID: <20140322113353.04D542406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hpc New tag : hpc-0.6.0.1-release Referencing: 1f8c1b343c2f0ccda5abb9476e97a20a26e4187c From git at git.haskell.org Sat Mar 22 12:09:03 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 12:09:03 +0000 (UTC) Subject: [commit: packages/haskell98] master: Update haskell98.cabal and add changelog (446b1af) Message-ID: <20140322120904.15F1B2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskell98 On branch : master Link : http://git.haskell.org/packages/haskell98.git/commitdiff/446b1af378b185383b879ab7d1db99c291629144 >--------------------------------------------------------------- commit 446b1af378b185383b879ab7d1db99c291629144 Author: Herbert Valerio Riedel Date: Sat Mar 22 13:08:00 2014 +0100 Update haskell98.cabal and add changelog Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 446b1af378b185383b879ab7d1db99c291629144 changelog.md | 11 +++++++++++ haskell98.cabal | 7 +++++-- 2 files changed, 16 insertions(+), 2 deletions(-) diff --git a/changelog.md b/changelog.md new file mode 100644 index 0000000..d3a71ec --- /dev/null +++ b/changelog.md @@ -0,0 +1,11 @@ +# Changelog for [`haskell98` package](http://hackage.haskell.org/package/haskell98) + +## 2.0.0.3 *Mar 2014* + + - Bundled with GHC 7.8.1 + + - Remove NHC98-specific code + + - Adapt to changes in GHC 7.8's core-libaries + + - Update to Cabal format 1.10 diff --git a/haskell98.cabal b/haskell98.cabal index 92cf90f..8a22c65 100644 --- a/haskell98.cabal +++ b/haskell98.cabal @@ -14,8 +14,11 @@ description: This package provides compatibility with the modules of Haskell 98 and the FFI addendum, by means of wrappers around modules from the base package (which in many cases have additional features). - However Prelude, Numeric and Foreign are provided directly by - the base package. + However "Prelude", "Numeric" and "Foreign" are provided directly by + the @base@ package. + +extra-source-files: + changelog.md source-repository head type: git From git at git.haskell.org Sat Mar 22 12:09:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 12:09:11 +0000 (UTC) Subject: [commit: packages/haskell98] ghc-7.8's head updated: Update haskell98.cabal and add changelog (446b1af) Message-ID: <20140322120911.AE6D02406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskell98 Branch 'ghc-7.8' now includes: 446b1af Update haskell98.cabal and add changelog From git at git.haskell.org Sat Mar 22 12:21:07 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 12:21:07 +0000 (UTC) Subject: [commit: packages/haskell98] tag 'haskell98-2.0.0.3-release' created Message-ID: <20140322122107.CE1662406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskell98 New tag : haskell98-2.0.0.3-release Referencing: 459690e41e6b2198c7b8cdd017ea428cd8ac5f0a From git at git.haskell.org Sat Mar 22 12:41:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 12:41:50 +0000 (UTC) Subject: [commit: packages/haskell2010] master: Bump to 1.1.2.0 and add changelog (5c5b84b) Message-ID: <20140322124150.C2B3A2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskell2010 On branch : master Link : http://git.haskell.org/packages/haskell2010.git/commitdiff/5c5b84b02d940b2487ffe0778ca62e329ad0bf75 >--------------------------------------------------------------- commit 5c5b84b02d940b2487ffe0778ca62e329ad0bf75 Author: Herbert Valerio Riedel Date: Sat Mar 22 13:25:37 2014 +0100 Bump to 1.1.2.0 and add changelog The minor version bump is performed `haskell2010` now leaks the new `Bits Bool` instance from `base-4.7.0.0`. Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 5c5b84b02d940b2487ffe0778ca62e329ad0bf75 changelog.md | 13 +++++++++++++ haskell2010.cabal | 7 +++++-- 2 files changed, 18 insertions(+), 2 deletions(-) diff --git a/changelog.md b/changelog.md new file mode 100644 index 0000000..87acfc5 --- /dev/null +++ b/changelog.md @@ -0,0 +1,13 @@ +# Changelog for [`haskell2010` package](http://hackage.haskell.org/package/haskell2010) + +## 1.1.2.0 *Mar 2014* + + - Bundled with GHC 7.8.1 + + - Leaks new `Bits Bool` instance (deviation from H2010) + + - Remove NHC98-specific code + + - Adapt to changes in GHC 7.8's core-libaries + + - Update to Cabal format 1.10 diff --git a/haskell2010.cabal b/haskell2010.cabal index 35d10a0..4cc8167 100644 --- a/haskell2010.cabal +++ b/haskell2010.cabal @@ -1,5 +1,5 @@ name: haskell2010 -version: 1.1.1.1 +version: 1.1.2.0 -- GHC 7.6.1 released with 1.1.1.0 license: BSD3 license-file: LICENSE @@ -14,6 +14,9 @@ description: This package provides exactly the library modules defined by the . +extra-source-files: + changelog.md + source-repository head type: git location: http://git.haskell.org/packages/haskell2010.git @@ -21,7 +24,7 @@ source-repository head source-repository this type: git location: http://git.haskell.org/packages/haskell2010.git - tag: haskell2010-1.1.1.1-release + tag: haskell2010-1.1.2.0-release Library default-language: Haskell2010 From git at git.haskell.org Sat Mar 22 12:41:55 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 12:41:55 +0000 (UTC) Subject: [commit: packages/haskell2010] ghc-7.8's head updated: Bump to 1.1.2.0 and add changelog (5c5b84b) Message-ID: <20140322124155.699BB2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskell2010 Branch 'ghc-7.8' now includes: 5c5b84b Bump to 1.1.2.0 and add changelog From git at git.haskell.org Sat Mar 22 12:42:00 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 12:42:00 +0000 (UTC) Subject: [commit: packages/haskell2010] tag 'haskell2010-1.1.2.0-release' created Message-ID: <20140322124200.1E4392406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskell2010 New tag : haskell2010-1.1.2.0-release Referencing: 95a636b6ca54cd3c3259cf56e59af043c2b4de02 From git at git.haskell.org Sat Mar 22 13:51:02 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 13:51:02 +0000 (UTC) Subject: [commit: packages/array] tag 'array-0.5.0.0-release' created Message-ID: <20140322135102.130A82406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/array New tag : array-0.5.0.0-release Referencing: 8e9f7d0d742694d17152d41a9987c81a424c3963 From git at git.haskell.org Sat Mar 22 14:30:38 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 14:30:38 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T8545-ghc-7.8' created Message-ID: <20140322143038.BE6F92406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T8545-ghc-7.8 Referencing: 85b6eec0b72ee523ea7c4a0f29c433f89e69449e From git at git.haskell.org Sat Mar 22 14:30:41 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 14:30:41 +0000 (UTC) Subject: [commit: ghc] wip/T8545-ghc-7.8: Switch to relative URLs in .gitmodules (1995ba7) Message-ID: <20140322143042.182AD2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8545-ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/1995ba7a9264a31b607128088e119eeaa6133443/ghc >--------------------------------------------------------------- commit 1995ba7a9264a31b607128088e119eeaa6133443 Author: Herbert Valerio Riedel Date: Thu Feb 6 08:42:27 2014 +0100 Switch to relative URLs in .gitmodules Previously, the `http://`-protocol part was hardcoded in the URLs, causing the initial clone process to fall back to `http://` even when the ghc.git repo was cloned via one of the other 3 supported transport protocols. This is slightly related to #8545, as it will make it possible to e.g. git clone --recursive git://git.haskell.org/ghc and clone ghc.git including all submodules in one go (i.e. w/o `sync-all`), and w/o falling back to a different (hardwired) Git transport protocol for the submodules. Signed-off-by: Herbert Valerio Riedel (cherry picked from commit ad44e47542a822ac3e02cf514b5d2be52880fc95) >--------------------------------------------------------------- 1995ba7a9264a31b607128088e119eeaa6133443 .gitmodules | 28 ++++++++++++++-------------- 1 file changed, 14 insertions(+), 14 deletions(-) diff --git a/.gitmodules b/.gitmodules index f0fd280..d83bfd0 100644 --- a/.gitmodules +++ b/.gitmodules @@ -1,56 +1,56 @@ [submodule "libraries/binary"] path = libraries/binary - url = http://git.haskell.org/packages/binary.git + url = ../packages/binary.git ignore = untracked [submodule "libraries/bytestring"] path = libraries/bytestring - url = http://git.haskell.org/packages/bytestring.git + url = ../packages/bytestring.git ignore = untracked [submodule "libraries/Cabal"] path = libraries/Cabal - url = http://git.haskell.org/packages/Cabal.git + url = ../packages/Cabal.git ignore = untracked [submodule "libraries/containers"] path = libraries/containers - url = http://git.haskell.org/packages/containers.git + url = ../packages/containers.git ignore = untracked [submodule "libraries/haskeline"] path = libraries/haskeline - url = http://git.haskell.org/packages/haskeline.git + url = ../packages/haskeline.git ignore = untracked [submodule "libraries/pretty"] path = libraries/pretty - url = http://git.haskell.org/packages/pretty.git + url = ../packages/pretty.git ignore = untracked [submodule "libraries/terminfo"] path = libraries/terminfo - url = http://git.haskell.org/packages/terminfo.git + url = ../packages/terminfo.git ignore = untracked [submodule "libraries/transformers"] path = libraries/transformers - url = http://git.haskell.org/packages/transformers.git + url = ../packages/transformers.git ignore = untracked [submodule "libraries/xhtml"] path = libraries/xhtml - url = http://git.haskell.org/packages/xhtml.git + url = ../packages/xhtml.git ignore = untracked [submodule "libraries/Win32"] path = libraries/Win32 - url = http://git.haskell.org/packages/Win32.git + url = ../packages/Win32.git ignore = untracked [submodule "libraries/primitive"] path = libraries/primitive - url = http://git.haskell.org/packages/primitive.git + url = ../packages/primitive.git ignore = untracked [submodule "libraries/vector"] path = libraries/vector - url = http://git.haskell.org/packages/vector.git + url = ../packages/vector.git ignore = untracked [submodule "libraries/time"] path = libraries/time - url = http://git.haskell.org/packages/time.git + url = ../packages/time.git ignore = untracked [submodule "libraries/random"] path = libraries/random - url = http://git.haskell.org/packages/random.git + url = ../packages/random.git ignore = untracked From git at git.haskell.org Sat Mar 22 14:30:44 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 14:30:44 +0000 (UTC) Subject: [commit: ghc] wip/T8545-ghc-7.8: Convert all sub-repos into proper submodules (re #8545) (85b6eec) Message-ID: <20140322143044.3AAE22406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8545-ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/85b6eec0b72ee523ea7c4a0f29c433f89e69449e/ghc >--------------------------------------------------------------- commit 85b6eec0b72ee523ea7c4a0f29c433f89e69449e Author: Herbert Valerio Riedel Date: Sat Mar 22 15:26:34 2014 +0100 Convert all sub-repos into proper submodules (re #8545) ...except for ghc-tarballs which is a waste of bandwidth Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 85b6eec0b72ee523ea7c4a0f29c433f89e69449e .gitignore | 27 ----------------- .gitmodules | 72 ++++++++++++++++++++++++++++++++++++++++++++ libffi-tarballs | 1 + libraries/array | 1 + libraries/base | 1 + libraries/deepseq | 1 + libraries/directory | 1 + libraries/dph | 1 + libraries/filepath | 1 + libraries/ghc-prim | 1 + libraries/haskell2010 | 1 + libraries/haskell98 | 1 + libraries/hoopl | 1 + libraries/hpc | 1 + libraries/integer-gmp | 1 + libraries/integer-simple | 1 + libraries/old-locale | 1 + libraries/old-time | 1 + libraries/parallel | 1 + libraries/process | 1 + libraries/stm | 1 + libraries/template-haskell | 1 + libraries/unix | 1 + nofib | 1 + packages | 48 ++++++++++++++--------------- utils/haddock | 1 + utils/hsc2hs | 1 + 27 files changed, 120 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 85b6eec0b72ee523ea7c4a0f29c433f89e69449e From git at git.haskell.org Sat Mar 22 14:38:58 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 14:38:58 +0000 (UTC) Subject: [commit: packages/base] ghc-7.8: Fixup release month in changelog (6a1961d) Message-ID: <20140322143858.362AD2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/base On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/6a1961dda2a6b4a4c1de9f5835b40ba4ababf0b7/base >--------------------------------------------------------------- commit 6a1961dda2a6b4a4c1de9f5835b40ba4ababf0b7 Author: Herbert Valerio Riedel Date: Fri Mar 21 18:14:47 2014 +0100 Fixup release month in changelog Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 6a1961dda2a6b4a4c1de9f5835b40ba4ababf0b7 changelog.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/changelog.md b/changelog.md index c88c79e..d86f6df 100644 --- a/changelog.md +++ b/changelog.md @@ -1,6 +1,6 @@ # Changelog for [`base` package](http://hackage.haskell.org/package/base) -## 4.7.0.0 *Feb 2014* +## 4.7.0.0 *Mar 2014* * Bundled with GHC 7.8.1 From git at git.haskell.org Sat Mar 22 14:41:59 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 14:41:59 +0000 (UTC) Subject: [commit: packages/dph] ghc-7.8's head updated: Fix breaking changes due to issue #7021 (aeef7aa) Message-ID: <20140322144159.7A1412406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/dph Branch 'ghc-7.8' now includes: aeef7aa Fix breaking changes due to issue #7021 From git at git.haskell.org Sat Mar 22 16:01:26 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 16:01:26 +0000 (UTC) Subject: [commit: packages/pretty] tag 'pretty-1.1.1.1-release' created Message-ID: <20140322160126.B94FC2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/pretty New tag : pretty-1.1.1.1-release Referencing: 5ad27fc84a19a5ba8ce8ff41be957ed90494065e From git at git.haskell.org Sat Mar 22 16:04:16 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 16:04:16 +0000 (UTC) Subject: [commit: packages/bytestring] tag 'bytestring-0.10.4.0-release' created Message-ID: <20140322160416.D75D82406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/bytestring New tag : bytestring-0.10.4.0-release Referencing: 968c0bbfa9833c6d0634ec2f3e3b41206efb87f3 From git at git.haskell.org Sat Mar 22 16:10:07 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 16:10:07 +0000 (UTC) Subject: [commit: packages/deepseq] tag 'deepseq-1.3.0.2-release' created Message-ID: <20140322161007.281812406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/deepseq New tag : deepseq-1.3.0.2-release Referencing: c32a156c8dafaea05e91563afe2f72ad3590f57b From git at git.haskell.org Sat Mar 22 16:13:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 16:13:50 +0000 (UTC) Subject: [commit: packages/process] tag 'process-1.2.0.0-release' created Message-ID: <20140322161351.19B4A2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process New tag : process-1.2.0.0-release Referencing: 2a715ce6072f5eb1b6c9c0be6c2458129cfe50f8 From git at git.haskell.org Sat Mar 22 16:16:58 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 16:16:58 +0000 (UTC) Subject: [commit: packages/parallel] tag 'parallel-3.2.0.4-release' created Message-ID: <20140322161700.D65462406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/parallel New tag : parallel-3.2.0.4-release Referencing: 257adcdf9009a0fa2eaeef54575a2bc7aec08b9d From git at git.haskell.org Sat Mar 22 16:19:25 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 16:19:25 +0000 (UTC) Subject: [commit: packages/transformers] tag 'transformers-0.3.0.0-release' created Message-ID: <20140322161925.3CB442406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/transformers New tag : transformers-0.3.0.0-release Referencing: a058a9a7413d578f572e29b099445260e2253f17 From git at git.haskell.org Sat Mar 22 16:33:20 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 16:33:20 +0000 (UTC) Subject: [commit: packages/unix] tag 'unix-2.7.0.1-release' created Message-ID: <20140322163320.229702406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix New tag : unix-2.7.0.1-release Referencing: 6b89e6bc9c8b1199bbe12e0f4d6d2c3422f7a1eb From git at git.haskell.org Sat Mar 22 16:33:22 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 16:33:22 +0000 (UTC) Subject: [commit: packages/unix] : Update changelog and prepare for 2.7.0.1 release (dc0e771) Message-ID: <20140322163322.30BEA2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branch : Link : http://ghc.haskell.org/trac/ghc/changeset/dc0e771a282df8ba92892b9619aed0c2b5b1bb7a/unix >--------------------------------------------------------------- commit dc0e771a282df8ba92892b9619aed0c2b5b1bb7a Author: Herbert Valerio Riedel Date: Sat Mar 22 17:28:41 2014 +0100 Update changelog and prepare for 2.7.0.1 release Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- dc0e771a282df8ba92892b9619aed0c2b5b1bb7a changelog.md | 10 ++++++++-- unix.cabal | 2 +- 2 files changed, 9 insertions(+), 3 deletions(-) diff --git a/changelog.md b/changelog.md index 54e5a96..9d587ab 100644 --- a/changelog.md +++ b/changelog.md @@ -1,6 +1,12 @@ -## 2.7.0.1 +## 2.7.0.1 *Mar 2014* - * Handle EROFS and ETXTBSY as (non-exceptional) permission denied in `fileAccess` + * Bundled with GHC 7.8.1 + + * Handle `EROFS` and `ETXTBSY` as (non-exceptional) permission denied in + `fileAccess` + + * Fix `getFileStatus` to retry `stat(2)` when it returns `EAGAIN` + (this can happen on Solaris) ## 2.7.0.0 *Nov 2013* diff --git a/unix.cabal b/unix.cabal index 03d47b4..12f463b 100644 --- a/unix.cabal +++ b/unix.cabal @@ -43,7 +43,7 @@ source-repository head source-repository this type: git location: http://git.haskell.org/packages/unix.git - tag: unix-2.7.0.0-release + tag: unix-2.7.0.1-release library default-language: Haskell2010 From git at git.haskell.org Sat Mar 22 16:33:39 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 16:33:39 +0000 (UTC) Subject: [commit: packages/unix] ghc-7.8's head updated: Update changelog and prepare for 2.7.0.1 release (dc0e771) Message-ID: <20140322163339.2DE592406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix Branch 'ghc-7.8' now includes: dc0e771 Update changelog and prepare for 2.7.0.1 release From git at git.haskell.org Sat Mar 22 16:38:44 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 16:38:44 +0000 (UTC) Subject: [commit: packages/unix] master: Merge branch 'ghc-7.8' (53dec0e) Message-ID: <20140322163844.CB0322406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/53dec0eaa542a9e3062e39fad2b60102440a6291/unix >--------------------------------------------------------------- commit 53dec0eaa542a9e3062e39fad2b60102440a6291 Merge: f4d0e10 dc0e771 Author: Herbert Valerio Riedel Date: Sat Mar 22 17:37:02 2014 +0100 Merge branch 'ghc-7.8' Re-unite branches which diverged for now good reason Conflicts: changelog.md >--------------------------------------------------------------- 53dec0eaa542a9e3062e39fad2b60102440a6291 changelog.md | 10 ++++++++-- unix.cabal | 2 +- 2 files changed, 9 insertions(+), 3 deletions(-) From git at git.haskell.org Sat Mar 22 16:38:46 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 16:38:46 +0000 (UTC) Subject: [commit: packages/unix] master's head updated: Merge branch 'ghc-7.8' (53dec0e) Message-ID: <20140322163846.E15732406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix Branch 'master' now includes: 0eb7d4b Convert `changelog` to markdown format 444750d Handle EROFS/ETXTBSY as permission denied in `fileAccess` (re #8741) a712abb M-x delete-trailing-whitespace & M-x untabify 5961343 fix getFileStatus: interrupted (Interrupted system call) build failure on Solaris dc0e771 Update changelog and prepare for 2.7.0.1 release 53dec0e Merge branch 'ghc-7.8' From git at git.haskell.org Sat Mar 22 16:39:54 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 16:39:54 +0000 (UTC) Subject: [commit: haddock] master: Drop needless --split-objs which slows us down. (725faca) Message-ID: <20140322163954.B8B1B2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : master Link : http://git.haskell.org/haddock.git/commitdiff/725faca5ee670f80359321adc112408880e9c073 >--------------------------------------------------------------- commit 725faca5ee670f80359321adc112408880e9c073 Author: Mateusz Kowalczyk Date: Sat Mar 22 16:36:16 2014 +0000 Drop needless --split-objs which slows us down. Involves tiny cleanup of all the dynflag bindings. Fixes #292. >--------------------------------------------------------------- 725faca5ee670f80359321adc112408880e9c073 src/Haddock.hs | 17 ++++++++--------- 1 file changed, 8 insertions(+), 9 deletions(-) diff --git a/src/Haddock.hs b/src/Haddock.hs index 6d975c9..78844c9 100644 --- a/src/Haddock.hs +++ b/src/Haddock.hs @@ -317,19 +317,18 @@ readInterfaceFiles name_cache_accessor pairs = do withGhc :: String -> [String] -> (DynFlags -> Ghc a) -> IO a withGhc libDir flags ghcActs = runGhc (Just libDir) $ do dynflags <- getSessionDynFlags - let dynflags' = gopt_set dynflags Opt_Haddock - let dynflags'' = dynflags' { - hscTarget = HscNothing, - ghcMode = CompManager, - ghcLink = NoLink + dynflags' <- parseGhcFlags (gopt_set dynflags Opt_Haddock) { + hscTarget = HscNothing, + ghcMode = CompManager, + ghcLink = NoLink } - dynflags''' <- parseGhcFlags dynflags'' - defaultCleanupHandler dynflags''' $ do + let dynflags'' = gopt_unset dynflags' Opt_SplitObjs + defaultCleanupHandler dynflags'' $ do -- ignore the following return-value, which is a list of packages -- that may need to be re-linked: Haddock doesn't do any -- dynamic or static linking at all! - _ <- setSessionDynFlags dynflags''' - ghcActs dynflags''' + _ <- setSessionDynFlags dynflags'' + ghcActs dynflags'' where parseGhcFlags :: MonadIO m => DynFlags -> m DynFlags parseGhcFlags dynflags = do From git at git.haskell.org Sat Mar 22 16:42:21 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 16:42:21 +0000 (UTC) Subject: [commit: ghc] wip/T8545-ghc-7.8: Convert all sub-repos into proper submodules (re #8545) (ee20507) Message-ID: <20140322164222.119A22406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8545-ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/ee205077ef5380de4db5e1900fe97f2816aabb8a/ghc >--------------------------------------------------------------- commit ee205077ef5380de4db5e1900fe97f2816aabb8a Author: Herbert Valerio Riedel Date: Sat Mar 22 15:26:34 2014 +0100 Convert all sub-repos into proper submodules (re #8545) ...except for ghc-tarballs which is a waste of bandwidth Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- ee205077ef5380de4db5e1900fe97f2816aabb8a .gitignore | 27 ----------------- .gitmodules | 72 ++++++++++++++++++++++++++++++++++++++++++++ libffi-tarballs | 1 + libraries/array | 1 + libraries/base | 1 + libraries/deepseq | 1 + libraries/directory | 1 + libraries/dph | 1 + libraries/filepath | 1 + libraries/ghc-prim | 1 + libraries/haskell2010 | 1 + libraries/haskell98 | 1 + libraries/hoopl | 1 + libraries/hpc | 1 + libraries/integer-gmp | 1 + libraries/integer-simple | 1 + libraries/old-locale | 1 + libraries/old-time | 1 + libraries/parallel | 1 + libraries/process | 1 + libraries/stm | 1 + libraries/template-haskell | 1 + libraries/unix | 1 + nofib | 1 + packages | 48 ++++++++++++++--------------- utils/haddock | 1 + utils/hsc2hs | 1 + 27 files changed, 120 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 ee205077ef5380de4db5e1900fe97f2816aabb8a From git at git.haskell.org Sat Mar 22 17:35:13 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 17:35:13 +0000 (UTC) Subject: [commit: packages/ghc-prim] master: Make argument types in popcnt.c match declared primop types (ad9bf96) Message-ID: <20140322173513.728E42406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc-prim On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ad9bf96815cb5a9bb4acc51c99eff20be3e50da3/ghc-prim >--------------------------------------------------------------- commit ad9bf96815cb5a9bb4acc51c99eff20be3e50da3 Author: Reid Barton Date: Fri Sep 6 19:22:38 2013 -0400 Make argument types in popcnt.c match declared primop types On 64-bit Mac OS, gcc 4.2 (which comes with Xcode 4.6) generates code that assumes that an argument that is smaller than the register it is passed in has been sign- or zero-extended. But ghc thinks the types of the PopCnt*Op primops are Word# -> Word#, so it passes the entire argument word to the hs_popcnt* function as though it was declared to have an argument of type StgWord. Segfaults ensue. The easiest fix is to sidestep all this zero-extension business by declaring the hs_popcnt* functions to take a whole StgWord (when their argument would fit in a register), thereby matching the list of primops. Fixes #7684. >--------------------------------------------------------------- ad9bf96815cb5a9bb4acc51c99eff20be3e50da3 cbits/popcnt.c | 20 ++++++++++---------- 1 file changed, 10 insertions(+), 10 deletions(-) diff --git a/cbits/popcnt.c b/cbits/popcnt.c index b17b624..fc44ee7 100644 --- a/cbits/popcnt.c +++ b/cbits/popcnt.c @@ -12,24 +12,24 @@ static const unsigned char popcount_tab[] = 3,4,4,5,4,5,5,6,4,5,5,6,5,6,6,7,4,5,5,6,5,6,6,7,5,6,6,7,6,7,7,8, }; -extern StgWord hs_popcnt8(StgWord8 x); +extern StgWord hs_popcnt8(StgWord x); StgWord -hs_popcnt8(StgWord8 x) +hs_popcnt8(StgWord x) { return popcount_tab[(unsigned char)x]; } -extern StgWord hs_popcnt16(StgWord16 x); +extern StgWord hs_popcnt16(StgWord x); StgWord -hs_popcnt16(StgWord16 x) +hs_popcnt16(StgWord x) { return popcount_tab[(unsigned char)x] + popcount_tab[(unsigned char)(x >> 8)]; } -extern StgWord hs_popcnt32(StgWord32 x); +extern StgWord hs_popcnt32(StgWord x); StgWord -hs_popcnt32(StgWord32 x) +hs_popcnt32(StgWord x) { return popcount_tab[(unsigned char)x] + popcount_tab[(unsigned char)(x >> 8)] + @@ -53,9 +53,9 @@ hs_popcnt64(StgWord64 x) #ifdef i386_HOST_ARCH -extern StgWord hs_popcnt(StgWord32 x); +extern StgWord hs_popcnt(StgWord x); StgWord -hs_popcnt(StgWord32 x) +hs_popcnt(StgWord x) { return popcount_tab[(unsigned char)x] + popcount_tab[(unsigned char)(x >> 8)] + @@ -65,9 +65,9 @@ hs_popcnt(StgWord32 x) #else -extern StgWord hs_popcnt(StgWord64 x); +extern StgWord hs_popcnt(StgWord x); StgWord -hs_popcnt(StgWord64 x) +hs_popcnt(StgWord x) { return popcount_tab[(unsigned char)x] + popcount_tab[(unsigned char)(x >> 8)] + From git at git.haskell.org Sat Mar 22 17:35:57 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 17:35:57 +0000 (UTC) Subject: [commit: ghc] master: Enable popcnt test now when segfault is fixed (16d04d9) Message-ID: <20140322173557.8C5E62406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/16d04d902d4720b3137e07a503fbf72c90b9e164/ghc >--------------------------------------------------------------- commit 16d04d902d4720b3137e07a503fbf72c90b9e164 Author: Johan Tibell Date: Sat Mar 22 18:30:36 2014 +0100 Enable popcnt test now when segfault is fixed The fix was to ghc-prim. >--------------------------------------------------------------- 16d04d902d4720b3137e07a503fbf72c90b9e164 testsuite/tests/codeGen/should_run/all.T | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/codeGen/should_run/all.T b/testsuite/tests/codeGen/should_run/all.T index 23393cd..bfe393d 100644 --- a/testsuite/tests/codeGen/should_run/all.T +++ b/testsuite/tests/codeGen/should_run/all.T @@ -75,7 +75,7 @@ test('cgrun068', reqlib('random'), compile_and_run, ['']) test('cgrun069', omit_ways(['ghci']), multi_compile_and_run, ['cgrun069', [('cgrun069_cmm.cmm', '')], '']) test('cgrun070', normal, compile_and_run, ['']) -test('cgrun071', when(opsys('darwin'), expect_broken(7684)), compile_and_run, ['']) +test('cgrun071', normal, compile_and_run, ['']) test('cgrun072', normal, compile_and_run, ['']) test('T1852', normal, compile_and_run, ['']) From git at git.haskell.org Sat Mar 22 17:36:00 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 17:36:00 +0000 (UTC) Subject: [commit: ghc] master: Follow hs_popcntX changes in ghc-prim (1a63f17) Message-ID: <20140322173600.94BD32406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1a63f17f19a6c83980efe453966eac1cf441b277/ghc >--------------------------------------------------------------- commit 1a63f17f19a6c83980efe453966eac1cf441b277 Author: Johan Tibell Date: Sat Mar 22 18:29:29 2014 +0100 Follow hs_popcntX changes in ghc-prim >--------------------------------------------------------------- 1a63f17f19a6c83980efe453966eac1cf441b277 includes/stg/Prim.h | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/includes/stg/Prim.h b/includes/stg/Prim.h index 2b23c3d..7d94d18 100644 --- a/includes/stg/Prim.h +++ b/includes/stg/Prim.h @@ -22,14 +22,14 @@ StgWord64 hs_bswap64(StgWord64 x); /* TODO: longlong.c */ /* libraries/ghc-prim/cbits/popcnt.c */ -StgWord hs_popcnt8(StgWord8 x); -StgWord hs_popcnt16(StgWord16 x); -StgWord hs_popcnt32(StgWord32 x); +StgWord hs_popcnt8(StgWord x); +StgWord hs_popcnt16(StgWord x); +StgWord hs_popcnt32(StgWord x); StgWord hs_popcnt64(StgWord64 x); #ifdef i386_HOST_ARCH -StgWord hs_popcnt(StgWord32 x); +StgWord hs_popcnt(StgWord x); #else -StgWord hs_popcnt(StgWord64 x); +StgWord hs_popcnt(StgWord x); #endif /* libraries/ghc-prim/cbits/word2float.c */ From git at git.haskell.org Sat Mar 22 19:38:02 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 19:38:02 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Update submodule to Win32-2.3.0.2 (a8bf4d4) Message-ID: <20140322193802.D478B2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/a8bf4d4a69cfaea04c6959dbd8587a943fc66343/ghc >--------------------------------------------------------------- commit a8bf4d4a69cfaea04c6959dbd8587a943fc66343 Author: Herbert Valerio Riedel Date: Tue Mar 18 11:06:57 2014 +0100 Update submodule to Win32-2.3.0.2 Signed-off-by: Herbert Valerio Riedel (cherry picked from commit 696bfc4ba5fce6b75cc91bcb67c5d0a3c9f29bd2) >--------------------------------------------------------------- a8bf4d4a69cfaea04c6959dbd8587a943fc66343 libraries/Win32 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Win32 b/libraries/Win32 index 1e909ad..c51e81a 160000 --- a/libraries/Win32 +++ b/libraries/Win32 @@ -1 +1 @@ -Subproject commit 1e909adb06b766e107148b8b37a4a9f9e50baf74 +Subproject commit c51e81a43cd5e9540453bd5ca6da8992245a4774 From git at git.haskell.org Sat Mar 22 19:38:05 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 19:38:05 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Revert ad15c2, which causes Windows seg-faults (Trac #8834) (07d58b2) Message-ID: <20140322193805.700FF2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/07d58b2eb7feac9971fb858898a974f2a15653a4/ghc >--------------------------------------------------------------- commit 07d58b2eb7feac9971fb858898a974f2a15653a4 Author: Simon Peyton Jones Date: Fri Mar 14 22:55:26 2014 +0000 Revert ad15c2, which causes Windows seg-faults (Trac #8834) We don't yet understand WHY commit ad15c2, which is to do with CmmSink, causes seg-faults on Windows, but it certainly seems to. So reverting it is a stop-gap, but we need to un-block the 7.8 release. Many thanks to awson for identifying the offending commit. (cherry picked from commit a79613a75c7da0d3d225850382f0f578a07113b5) >--------------------------------------------------------------- 07d58b2eb7feac9971fb858898a974f2a15653a4 compiler/cmm/CmmSink.hs | 85 ++++++++++++----------------------------------- 1 file changed, 21 insertions(+), 64 deletions(-) diff --git a/compiler/cmm/CmmSink.hs b/compiler/cmm/CmmSink.hs index c404a2e..635b002 100644 --- a/compiler/cmm/CmmSink.hs +++ b/compiler/cmm/CmmSink.hs @@ -3,6 +3,8 @@ module CmmSink ( cmmSink ) where +import CodeGen.Platform (callerSaves) + import Cmm import CmmOpt import BlockId @@ -236,9 +238,11 @@ some tool like perf or VTune and make decisions what to inline based on that. -- global) and literals. -- isTrivial :: CmmExpr -> Bool -isTrivial (CmmReg _) = True -isTrivial (CmmLit _) = True -isTrivial _ = False +isTrivial (CmmReg (CmmLocal _)) = True +-- isTrivial (CmmLit _) = True -- Disabled because it used to make thing worse. + -- Needs further investigation +isTrivial _ = False + -- -- annotate each node with the set of registers live *after* the node @@ -501,8 +505,7 @@ regsUsedIn ls e = wrapRecExpf f e False -- nor the NCG can do it. See Note [Register parameter passing] -- See also StgCmmForeign:load_args_into_temps. okToInline :: DynFlags -> CmmExpr -> CmmNode e x -> Bool -okToInline dflags expr node@(CmmUnsafeForeignCall{}) = - not (globalRegistersConflict dflags expr node) +okToInline dflags expr CmmUnsafeForeignCall{} = not (anyCallerSavesRegs dflags expr) okToInline _ _ _ = True -- ----------------------------------------------------------------------------- @@ -515,23 +518,23 @@ okToInline _ _ _ = True conflicts :: DynFlags -> Assignment -> CmmNode O x -> Bool conflicts dflags (r, rhs, addr) node - -- (1) node defines registers used by rhs of assignment. This catches - -- assignmnets and all three kinds of calls. See Note [Sinking and calls] - | globalRegistersConflict dflags rhs node = True - | localRegistersConflict dflags rhs node = True - - -- (2) node uses register defined by assignment + -- (1) an assignment to a register conflicts with a use of the register + | CmmAssign reg _ <- node, reg `regUsedIn` rhs = True | foldRegsUsed dflags (\b r' -> r == r' || b) False node = True - -- (3) a store to an address conflicts with a read of the same memory + -- (2) a store to an address conflicts with a read of the same memory | CmmStore addr' e <- node , memConflicts addr (loadAddr dflags addr' (cmmExprWidth dflags e)) = True - -- (4) an assignment to Hp/Sp conflicts with a heap/stack read respectively + -- (3) an assignment to Hp/Sp conflicts with a heap/stack read respectively | HeapMem <- addr, CmmAssign (CmmGlobal Hp) _ <- node = True | StackMem <- addr, CmmAssign (CmmGlobal Sp) _ <- node = True | SpMem{} <- addr, CmmAssign (CmmGlobal Sp) _ <- node = True + -- (4) assignments that read caller-saves GlobalRegs conflict with a + -- foreign call. See Note [Unsafe foreign calls clobber caller-save registers] + | CmmUnsafeForeignCall{} <- node, anyCallerSavesRegs dflags rhs = True + -- (5) foreign calls clobber heap: see Note [Foreign calls clobber heap] | CmmUnsafeForeignCall{} <- node, memConflicts addr AnyMem = True @@ -541,57 +544,11 @@ conflicts dflags (r, rhs, addr) node -- (7) otherwise, no conflict | otherwise = False --- Returns True if node defines any global registers that are used in the --- Cmm expression -globalRegistersConflict :: DynFlags -> CmmExpr -> CmmNode e x -> Bool -globalRegistersConflict dflags expr node = - foldRegsDefd dflags (\b r -> b || (CmmGlobal r) `regUsedIn` expr) False node - --- Returns True if node defines any local registers that are used in the --- Cmm expression -localRegistersConflict :: DynFlags -> CmmExpr -> CmmNode e x -> Bool -localRegistersConflict dflags expr node = - foldRegsDefd dflags (\b r -> b || (CmmLocal r) `regUsedIn` expr) False node - --- Note [Sinking and calls] --- ~~~~~~~~~~~~~~~~~~~~~~~~ --- --- We have three kinds of calls: normal (CmmCall), safe foreign (CmmForeignCall) --- and unsafe foreign (CmmUnsafeForeignCall). We perform sinking pass after --- stack layout (see Note [Sinking after stack layout]) which leads to two --- invariants related to calls: --- --- a) during stack layout phase all safe foreign calls are turned into --- unsafe foreign calls (see Note [Lower safe foreign calls]). This --- means that we will never encounter CmmForeignCall node when running --- sinking after stack layout --- --- b) stack layout saves all variables live across a call on the stack --- just before making a call (remember we are not sinking assignments to --- stack): --- --- L1: --- x = R1 --- P64[Sp - 16] = L2 --- P64[Sp - 8] = x --- Sp = Sp - 16 --- call f() returns L2 --- L2: --- --- We will attempt to sink { x = R1 } but we will detect conflict with --- { P64[Sp - 8] = x } and hence we will drop { x = R1 } without even --- checking whether it conflicts with { call f() }. In this way we will --- never need to check any assignment conflicts with CmmCall. Remember --- that we still need to check for potential memory conflicts. --- --- So the result is that we only need to worry about CmmUnsafeForeignCall nodes --- when checking conflicts (see Note [Unsafe foreign calls clobber caller-save registers]). --- This assumption holds only when we do sinking after stack layout. If we run --- it before stack layout we need to check for possible conflicts with all three --- kinds of calls. Our `conflicts` function does that by using a generic --- foldRegsDefd and foldRegsUsed functions defined in DefinerOfRegs and --- UserOfRegs typeclasses. --- +anyCallerSavesRegs :: DynFlags -> CmmExpr -> Bool +anyCallerSavesRegs dflags e = wrapRecExpf f e False + where f (CmmReg (CmmGlobal r)) _ + | callerSaves (targetPlatform dflags) r = True + f _ z = z -- An abstraction of memory read or written. data AbsMem From git at git.haskell.org Sat Mar 22 19:38:08 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 19:38:08 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Add some documentation about type-level literals. (57ec032) Message-ID: <20140322193808.47ED32406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/57ec03258c52814636024b0130bff6b70e6b8da4/ghc >--------------------------------------------------------------- commit 57ec03258c52814636024b0130bff6b70e6b8da4 Author: Iavor S. Diatchki Date: Mon Mar 17 23:19:16 2014 -0700 Add some documentation about type-level literals. I moved the "promoted literals" sub-section into a separate section, as many folks were not finding the docs. I also added some additional paragraphs describing the current state of the feature. (cherry picked from commit 3099e40d2737172c746a6456ddcd34b54e120aa0) >--------------------------------------------------------------- 57ec03258c52814636024b0130bff6b70e6b8da4 docs/users_guide/glasgow_exts.xml | 178 ++++++++++++++++++++++++++++--------- 1 file changed, 135 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 57ec03258c52814636024b0130bff6b70e6b8da4 From git at git.haskell.org Sat Mar 22 19:38:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 19:38:11 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Flush after TH in #8884 test case (7f5d1f5) Message-ID: <20140322193811.1EA8F2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/7f5d1f52f84cf18a53d6f256ab828df6c005163a/ghc >--------------------------------------------------------------- commit 7f5d1f52f84cf18a53d6f256ab828df6c005163a Author: Joachim Breitner Date: Fri Mar 21 13:46:15 2014 +0100 Flush after TH in #8884 test case (I recall that this was needed in some cases in the past, and might fix the validate error on travis.) (cherry picked from commit df409de9550dc8a07e010964a54112266d809341) >--------------------------------------------------------------- 7f5d1f52f84cf18a53d6f256ab828df6c005163a testsuite/tests/th/T8884.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/testsuite/tests/th/T8884.hs b/testsuite/tests/th/T8884.hs index 782bf90..ca6ed9c 100644 --- a/testsuite/tests/th/T8884.hs +++ b/testsuite/tests/th/T8884.hs @@ -3,6 +3,7 @@ module T8884 where import Language.Haskell.TH +import System.IO type family Foo a where Foo x = x @@ -16,6 +17,7 @@ $( do FamilyI foo@(ClosedTypeFamilyD _ tvbs1 m_kind1 eqns1) [] <- reify ''Foo runIO $ putStrLn $ pprint foo runIO $ putStrLn $ pprint baz runIO $ putStrLn $ pprint inst + runIO $ hFlush stdout return [ ClosedTypeFamilyD (mkName "Foo'") tvbs1 m_kind1 eqns1 , FamilyD TypeFam (mkName "Baz'") tvbs2 m_kind2 , TySynInstD (mkName "Baz'") eqn2 ] ) From git at git.haskell.org Sat Mar 22 19:38:14 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 19:38:14 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Typos (0bbb8dc) Message-ID: <20140322193814.413BC2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/0bbb8dc74a76d1f694263147725b451c25ed0661/ghc >--------------------------------------------------------------- commit 0bbb8dc74a76d1f694263147725b451c25ed0661 Author: Austin Seipp Date: Fri Mar 21 04:36:23 2014 -0500 Typos Signed-off-by: Austin Seipp (cherry picked from commit ba0c0123fb2f6942f57636ca458d5a87870f1ecc) >--------------------------------------------------------------- 0bbb8dc74a76d1f694263147725b451c25ed0661 compiler/main/HscTypes.lhs | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/compiler/main/HscTypes.lhs b/compiler/main/HscTypes.lhs index b8ecc10..c4c5efd 100644 --- a/compiler/main/HscTypes.lhs +++ b/compiler/main/HscTypes.lhs @@ -1119,10 +1119,10 @@ shadowed by the second declaration. But it has a respectable qualified name (Ghci1.T), and its source location says where it was defined. -So the main invariant continues to hold, that in any session an original -name M.T only refers to oe unique thing. (In a previous iteration both -the T's above were called :Interactive.T, albeit with different uniques, -which gave rise to all sorts of trouble.) +So the main invariant continues to hold, that in any session an +original name M.T only refers to one unique thing. (In a previous +iteration both the T's above were called :Interactive.T, albeit with +different uniques, which gave rise to all sorts of trouble.) The details are a bit tricky though: @@ -1132,7 +1132,7 @@ The details are a bit tricky though: * ic_tythings contains only things from the 'interactive' package. * Module from the 'interactive' package (Ghci1, Ghci2 etc) never go - in the Home Package Table (HPT). When you say :load, that's when + in the Home Package Table (HPT). When you say :load, that's when we extend the HPT. * The 'thisPackage' field of DynFlags is *not* set to 'interactive'. From git at git.haskell.org Sat Mar 22 19:38:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 19:38:17 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Add OutputableBndr instance for OccName (db6c7a9) Message-ID: <20140322193817.473F52406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/db6c7a97139512312cecb732a3c2973d51d199d9/ghc >--------------------------------------------------------------- commit db6c7a97139512312cecb732a3c2973d51d199d9 Author: Dr. ERDI Gergo Date: Wed Mar 12 20:37:22 2014 +0800 Add OutputableBndr instance for OccName (cherry picked from commit 4d1b7b4a9b986e87755784478b4ea4883a5e203e) >--------------------------------------------------------------- db6c7a97139512312cecb732a3c2973d51d199d9 compiler/basicTypes/OccName.lhs | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/compiler/basicTypes/OccName.lhs b/compiler/basicTypes/OccName.lhs index 6dbae4b..d53292b 100644 --- a/compiler/basicTypes/OccName.lhs +++ b/compiler/basicTypes/OccName.lhs @@ -261,6 +261,11 @@ instance Data OccName where instance Outputable OccName where ppr = pprOccName +instance OutputableBndr OccName where + pprBndr _ = ppr + pprInfixOcc n = pprInfixVar (isSymOcc n) (ppr n) + pprPrefixOcc n = pprPrefixVar (isSymOcc n) (ppr n) + pprOccName :: OccName -> SDoc pprOccName (OccName sp occ) = getPprStyle $ \ sty -> From git at git.haskell.org Sat Mar 22 19:38:19 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 19:38:19 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: pprIfaceContextArr: print a context including the "=>" arrow (8da725b) Message-ID: <20140322193819.E3C912406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/8da725b876294f3649176ca746223447b40b65ef/ghc >--------------------------------------------------------------- commit 8da725b876294f3649176ca746223447b40b65ef Author: Dr. ERDI Gergo Date: Wed Mar 12 20:38:26 2014 +0800 pprIfaceContextArr: print a context including the "=>" arrow (cherry picked from commit 23c0f1ec2cf06c0178c2ae7414fe57ea648689e7) >--------------------------------------------------------------- 8da725b876294f3649176ca746223447b40b65ef compiler/iface/IfaceSyn.lhs | 2 +- compiler/iface/IfaceType.lhs | 16 ++++++++-------- 2 files changed, 9 insertions(+), 9 deletions(-) diff --git a/compiler/iface/IfaceSyn.lhs b/compiler/iface/IfaceSyn.lhs index b582305..3691fca 100644 --- a/compiler/iface/IfaceSyn.lhs +++ b/compiler/iface/IfaceSyn.lhs @@ -1152,7 +1152,7 @@ instance Outputable IfaceAT where pprIfaceDeclHead :: IfaceContext -> OccName -> [IfaceTvBndr] -> SDoc pprIfaceDeclHead context thing tyvars - = hsep [pprIfaceContext context, parenSymOcc thing (ppr thing), + = hsep [pprIfaceContextArr context, parenSymOcc thing (ppr thing), pprIfaceTvBndrs tyvars] pp_condecls :: OccName -> IfaceConDecls -> SDoc diff --git a/compiler/iface/IfaceType.lhs b/compiler/iface/IfaceType.lhs index 822e3da..8c1791a 100644 --- a/compiler/iface/IfaceType.lhs +++ b/compiler/iface/IfaceType.lhs @@ -22,7 +22,7 @@ module IfaceType ( toIfaceCoercion, -- Printing - pprIfaceType, pprParendIfaceType, pprIfaceContext, + pprIfaceType, pprParendIfaceType, pprIfaceContext, pprIfaceContextArr, pprIfaceIdBndr, pprIfaceTvBndr, pprIfaceTvBndrs, pprIfaceBndrs, tOP_PREC, tYCON_PREC, noParens, maybeParen, pprIfaceForAllPart, @@ -253,7 +253,7 @@ ppr_ty ctxt_prec ty@(IfaceForAllTy _ _) -- generality pprIfaceForAllPart :: Outputable a => [IfaceTvBndr] -> [a] -> SDoc -> SDoc pprIfaceForAllPart tvs ctxt doc - = sep [ppr_tvs, pprIfaceContext ctxt, doc] + = sep [ppr_tvs, pprIfaceContextArr ctxt, doc] where ppr_tvs | null tvs = empty | otherwise = ptext (sLit "forall") <+> pprIfaceTvBndrs tvs <> dot @@ -386,14 +386,14 @@ instance Binary IfaceTyLit where _ -> panic ("get IfaceTyLit " ++ show tag) ------------------- -pprIfaceContext :: Outputable a => [a] -> SDoc +pprIfaceContextArr :: Outputable a => [a] -> SDoc -- Prints "(C a, D b) =>", including the arrow -pprIfaceContext [] = empty -pprIfaceContext theta = ppr_preds theta <+> darrow +pprIfaceContextArr [] = empty +pprIfaceContextArr theta = pprIfaceContext theta <+> darrow -ppr_preds :: Outputable a => [a] -> SDoc -ppr_preds [pred] = ppr pred -- No parens -ppr_preds preds = parens (sep (punctuate comma (map ppr preds))) +pprIfaceContext :: Outputable a => [a] -> SDoc +pprIfaceContext [pred] = ppr pred -- No parens +pprIfaceContext preds = parens (sep (punctuate comma (map ppr preds))) instance Binary IfaceType where put_ bh (IfaceForAllTy aa ab) = do From git at git.haskell.org Sat Mar 22 19:38:22 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 19:38:22 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: pprIfaceDecl for IfacePatSyn: use pprPatSynSig (2712bcd) Message-ID: <20140322193822.619162406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/2712bcd58124d649729bd305c039210a42b9c842/ghc >--------------------------------------------------------------- commit 2712bcd58124d649729bd305c039210a42b9c842 Author: Dr. ERDI Gergo Date: Wed Mar 12 20:38:54 2014 +0800 pprIfaceDecl for IfacePatSyn: use pprPatSynSig (cherry picked from commit 24eea38c70eae90d166de26d71a178fb0c1ffc30) >--------------------------------------------------------------- 2712bcd58124d649729bd305c039210a42b9c842 compiler/iface/IfaceSyn.lhs | 26 +++++++++++--------------- 1 file changed, 11 insertions(+), 15 deletions(-) diff --git a/compiler/iface/IfaceSyn.lhs b/compiler/iface/IfaceSyn.lhs index 3691fca..8ca8582 100644 --- a/compiler/iface/IfaceSyn.lhs +++ b/compiler/iface/IfaceSyn.lhs @@ -55,6 +55,7 @@ import TysWiredIn ( eqTyConName ) import Fingerprint import Binary import BooleanFormula ( BooleanFormula ) +import HsBinds import Control.Monad import System.IO.Unsafe @@ -1104,27 +1105,22 @@ pprIfaceDecl (IfaceAxiom {ifName = name, ifTyCon = tycon, ifAxBranches = branche pprIfaceDecl (IfacePatSyn { ifName = name, ifPatHasWrapper = has_wrap, ifPatIsInfix = is_infix, - ifPatUnivTvs = univ_tvs, ifPatExTvs = ex_tvs, + ifPatUnivTvs = _univ_tvs, ifPatExTvs = _ex_tvs, ifPatProvCtxt = prov_ctxt, ifPatReqCtxt = req_ctxt, ifPatArgs = args, ifPatTy = ty }) - = hang (text "pattern" <+> header) - 4 details + = pprPatSynSig name has_wrap args' ty' (pprCtxt prov_ctxt) (pprCtxt req_ctxt) where - header = ppr name <+> dcolon <+> - (pprIfaceForAllPart univ_tvs req_ctxt $ - pprIfaceForAllPart ex_tvs prov_ctxt $ - pp_tau) + args' = case (is_infix, map snd args) of + (True, [left_ty, right_ty]) -> + InfixPatSyn (pprParendIfaceType left_ty) (pprParendIfaceType right_ty) + (_, tys) -> + PrefixPatSyn (map pprParendIfaceType tys) - details = sep [ if is_infix then text "Infix" else empty - , if has_wrap then text "HasWrapper" else empty - ] + ty' = pprParendIfaceType ty - pp_tau = case map pprParendIfaceType (arg_tys ++ [ty]) of - (t:ts) -> fsep (t : map (arrow <+>) ts) - [] -> panic "pp_tau" - - arg_tys = map snd args + pprCtxt [] = Nothing + pprCtxt ctxt = Just $ pprIfaceContext ctxt pprCType :: Maybe CType -> SDoc pprCType Nothing = ptext (sLit "No C type associated") From git at git.haskell.org Sat Mar 22 19:38:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 19:38:24 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Pretty-print the following TyThings via their IfaceDecl counterpart: * AnId * ACoAxiom * AConLike (0f51f1c) Message-ID: <20140322193824.9E9D22406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/0f51f1c243766045977547cd6afd9c7c5181b788/ghc >--------------------------------------------------------------- commit 0f51f1c243766045977547cd6afd9c7c5181b788 Author: Dr. ERDI Gergo Date: Thu Mar 13 21:18:39 2014 +0800 Pretty-print the following TyThings via their IfaceDecl counterpart: * AnId * ACoAxiom * AConLike (cherry picked from commit 065c35a9d6d48060c8fac8d755833349ce58b35b) >--------------------------------------------------------------- 0f51f1c243766045977547cd6afd9c7c5181b788 compiler/iface/IfaceSyn.lhs | 2 +- compiler/iface/MkIface.lhs | 10 +++++++- compiler/main/PprTyThing.hs | 59 ++++++++++--------------------------------- 3 files changed, 23 insertions(+), 48 deletions(-) diff --git a/compiler/iface/IfaceSyn.lhs b/compiler/iface/IfaceSyn.lhs index 8ca8582..7484b37 100644 --- a/compiler/iface/IfaceSyn.lhs +++ b/compiler/iface/IfaceSyn.lhs @@ -1100,7 +1100,7 @@ pprIfaceDecl (IfaceClass {ifCtxt = context, ifName = clas, ifTyVars = tyvars, sep (map ppr sigs)]) pprIfaceDecl (IfaceAxiom {ifName = name, ifTyCon = tycon, ifAxBranches = branches }) - = hang (ptext (sLit "axiom") <+> ppr name <> colon) + = hang (ptext (sLit "axiom") <+> ppr name <> dcolon) 2 (vcat $ map (pprAxBranch $ Just tycon) branches) pprIfaceDecl (IfacePatSyn { ifName = name, ifPatHasWrapper = has_wrap, diff --git a/compiler/iface/MkIface.lhs b/compiler/iface/MkIface.lhs index 379b39d..8b004cf 100644 --- a/compiler/iface/MkIface.lhs +++ b/compiler/iface/MkIface.lhs @@ -1461,7 +1461,7 @@ tyThingToIfaceDecl (AnId id) = idToIfaceDecl id tyThingToIfaceDecl (ATyCon tycon) = tyConToIfaceDecl emptyTidyEnv tycon tyThingToIfaceDecl (ACoAxiom ax) = coAxiomToIfaceDecl ax tyThingToIfaceDecl (AConLike cl) = case cl of - RealDataCon dc -> pprPanic "toIfaceDecl" (ppr dc) -- Should be trimmed out earlier + RealDataCon dc -> dataConToIfaceDecl dc -- for ppr purposes only PatSynCon ps -> patSynToIfaceDecl ps -------------------------- @@ -1477,6 +1477,14 @@ idToIfaceDecl id ifIdInfo = toIfaceIdInfo (idInfo id) } -------------------------- +dataConToIfaceDecl :: DataCon -> IfaceDecl +dataConToIfaceDecl dataCon + = IfaceId { ifName = getOccName dataCon, + ifType = toIfaceType (dataConUserType dataCon), + ifIdDetails = IfVanillaId, + ifIdInfo = NoInfo } + +-------------------------- patSynToIfaceDecl :: PatSyn -> IfaceDecl patSynToIfaceDecl ps = IfacePatSyn { ifName = getOccName . getName $ ps diff --git a/compiler/main/PprTyThing.hs b/compiler/main/PprTyThing.hs index 27e7390..fb92b5a 100644 --- a/compiler/main/PprTyThing.hs +++ b/compiler/main/PprTyThing.hs @@ -23,20 +23,18 @@ module PprTyThing ( ) where import TypeRep ( TyThing(..) ) -import ConLike import DataCon -import PatSyn import Id import TyCon import Class -import Coercion( pprCoAxiom, pprCoAxBranch ) +import Coercion( pprCoAxBranch ) import CoAxiom( CoAxiom(..), brListMap ) import HscTypes( tyThingParent_maybe ) -import HsBinds( pprPatSynSig ) import Type( tidyTopType, tidyOpenType, splitForAllTys, funResultTy ) import Kind( synTyConResKind ) import TypeRep( pprTvBndrs, pprForAll, suppressKinds ) import TysPrim( alphaTyVars ) +import MkIface ( tyThingToIfaceDecl ) import TcType import Name import VarEnv( emptyTidyEnv ) @@ -44,7 +42,6 @@ import StaticFlags( opt_PprStyle_Debug ) import DynFlags import Outputable import FastString -import Data.Maybe -- ----------------------------------------------------------------------------- -- Pretty-printing entities that we get from the GHC API @@ -76,7 +73,7 @@ pprTyThingLoc tyThing -- | Pretty-prints a 'TyThing'. pprTyThing :: TyThing -> SDoc -pprTyThing thing = ppr_ty_thing showAll thing +pprTyThing thing = ppr_ty_thing (Just showAll) thing -- | Pretty-prints a 'TyThing' in context: that is, if the entity -- is a data constructor, record selector, or class method, then @@ -88,7 +85,7 @@ pprTyThingInContext thing where go ss thing = case tyThingParent_maybe thing of Just parent -> go (getName thing : ss) parent - Nothing -> ppr_ty_thing ss thing + Nothing -> ppr_ty_thing (Just ss) thing -- | Like 'pprTyThingInContext', but adds the defining location. pprTyThingInContextLoc :: TyThing -> SDoc @@ -100,21 +97,17 @@ pprTyThingInContextLoc tyThing -- the function is equivalent to 'pprTyThing' but for type constructors -- and classes it prints only the header part of the declaration. pprTyThingHdr :: TyThing -> SDoc -pprTyThingHdr (AnId id) = pprId id -pprTyThingHdr (AConLike conLike) = case conLike of - RealDataCon dataCon -> pprDataConSig dataCon - PatSynCon patSyn -> pprPatSyn patSyn -pprTyThingHdr (ATyCon tyCon) = pprTyConHdr tyCon -pprTyThingHdr (ACoAxiom ax) = pprCoAxiom ax +pprTyThingHdr = ppr_ty_thing Nothing ------------------------ -ppr_ty_thing :: ShowSub -> TyThing -> SDoc -ppr_ty_thing _ (AnId id) = pprId id -ppr_ty_thing _ (AConLike conLike) = case conLike of - RealDataCon dataCon -> pprDataConSig dataCon - PatSynCon patSyn -> pprPatSyn patSyn -ppr_ty_thing ss (ATyCon tyCon) = pprTyCon ss tyCon -ppr_ty_thing _ (ACoAxiom ax) = pprCoAxiom ax +-- NOTE: We pretty-print 'TyThing' via 'IfaceDecl' so that we can reuse the +-- 'TyCon' tidying happening in 'tyThingToIfaceDecl'. See #8776 for details. +ppr_ty_thing :: Maybe ShowSub -> TyThing -> SDoc +ppr_ty_thing mss tyThing = case tyThing of + ATyCon tyCon -> case mss of + Nothing -> pprTyConHdr tyCon + Just ss -> pprTyCon ss tyCon + _ -> ppr $ tyThingToIfaceDecl tyThing pprTyConHdr :: TyCon -> SDoc pprTyConHdr tyCon @@ -143,10 +136,6 @@ pprTyConHdr tyCon | isAlgTyCon tyCon = pprThetaArrowTy (tyConStupidTheta tyCon) | otherwise = empty -- Returns 'empty' if null theta -pprDataConSig :: DataCon -> SDoc -pprDataConSig dataCon - = ppr_bndr dataCon <+> dcolon <+> pprTypeForUser (dataConUserType dataCon) - pprClassHdr :: Class -> SDoc pprClassHdr cls = sdocWithDynFlags $ \dflags -> @@ -158,28 +147,6 @@ pprClassHdr cls where (tvs, funDeps) = classTvsFds cls -pprId :: Var -> SDoc -pprId ident - = hang (ppr_bndr ident <+> dcolon) - 2 (pprTypeForUser (idType ident)) - -pprPatSyn :: PatSyn -> SDoc -pprPatSyn patSyn - = pprPatSynSig ident is_bidir args (pprTypeForUser rhs_ty) prov req - where - ident = patSynId patSyn - is_bidir = isJust $ patSynWrapper patSyn - - args = fmap pprParendType (patSynTyDetails patSyn) - prov = pprThetaOpt prov_theta - req = pprThetaOpt req_theta - - pprThetaOpt [] = Nothing - pprThetaOpt theta = Just $ pprTheta theta - - (_univ_tvs, _ex_tvs, (prov_theta, req_theta)) = patSynSig patSyn - rhs_ty = patSynType patSyn - pprTypeForUser :: Type -> SDoc -- We do two things here. -- a) We tidy the type, regardless From git at git.haskell.org Sat Mar 22 19:38:26 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 19:38:26 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Honor Op_PrintExplicitForalls setting in pprIfaceForAllPart (0a2e5aa) Message-ID: <20140322193827.07F842406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/0a2e5aa2ac80969c6ccc95ad8e6d031b8aaa1771/ghc >--------------------------------------------------------------- commit 0a2e5aa2ac80969c6ccc95ad8e6d031b8aaa1771 Author: Dr. ERDI Gergo Date: Fri Mar 14 19:50:15 2014 +0800 Honor Op_PrintExplicitForalls setting in pprIfaceForAllPart (cherry picked from commit f3eeb93529798b80721a9801aa1bf2ea7a1de049) >--------------------------------------------------------------- 0a2e5aa2ac80969c6ccc95ad8e6d031b8aaa1771 compiler/iface/IfaceType.lhs | 9 +++++++-- 1 file changed, 7 insertions(+), 2 deletions(-) diff --git a/compiler/iface/IfaceType.lhs b/compiler/iface/IfaceType.lhs index 8c1791a..e4a789f 100644 --- a/compiler/iface/IfaceType.lhs +++ b/compiler/iface/IfaceType.lhs @@ -31,6 +31,8 @@ module IfaceType ( ) where import Coercion +import TcType +import DynFlags import TypeRep hiding( maybeParen ) import Unique( hasKey ) import TyCon @@ -248,7 +250,7 @@ ppr_ty ctxt_prec ty@(IfaceForAllTy _ _) where (tvs, theta, tau) = splitIfaceSigmaTy ty - ------------------- +------------------- -- needs to handle type contexts and coercion contexts, hence the -- generality pprIfaceForAllPart :: Outputable a => [IfaceTvBndr] -> [a] -> SDoc -> SDoc @@ -256,7 +258,10 @@ pprIfaceForAllPart tvs ctxt doc = sep [ppr_tvs, pprIfaceContextArr ctxt, doc] where ppr_tvs | null tvs = empty - | otherwise = ptext (sLit "forall") <+> pprIfaceTvBndrs tvs <> dot + | otherwise = sdocWithDynFlags $ \ dflags -> + if gopt Opt_PrintExplicitForalls dflags + then ptext (sLit "forall") <+> pprIfaceTvBndrs tvs <> dot + else empty ------------------- ppr_tc_app :: (Int -> a -> SDoc) -> Int -> IfaceTyCon -> [a] -> SDoc From git at git.haskell.org Sat Mar 22 19:38:29 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 19:38:29 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Use prefix notation in pprIfaceDecl for IfaceIds (dfeca0d) Message-ID: <20140322193829.6FB172406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/dfeca0d688d172c876121414e3ae0af878a582a9/ghc >--------------------------------------------------------------- commit dfeca0d688d172c876121414e3ae0af878a582a9 Author: Dr. ERDI Gergo Date: Fri Mar 14 21:35:30 2014 +0800 Use prefix notation in pprIfaceDecl for IfaceIds (cherry picked from commit 5908a7427abd35264f5bafd5bf7bce3a0c9dde8e) >--------------------------------------------------------------- dfeca0d688d172c876121414e3ae0af878a582a9 compiler/iface/IfaceSyn.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/iface/IfaceSyn.lhs b/compiler/iface/IfaceSyn.lhs index 7484b37..1283b09 100644 --- a/compiler/iface/IfaceSyn.lhs +++ b/compiler/iface/IfaceSyn.lhs @@ -1047,7 +1047,7 @@ instance Outputable IfaceDecl where pprIfaceDecl :: IfaceDecl -> SDoc pprIfaceDecl (IfaceId {ifName = var, ifType = ty, ifIdDetails = details, ifIdInfo = info}) - = sep [ ppr var <+> dcolon <+> ppr ty, + = sep [ pprPrefixOcc var <+> dcolon <+> ppr ty, nest 2 (ppr details), nest 2 (ppr info) ] From git at git.haskell.org Sat Mar 22 19:38:31 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 19:38:31 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Reinstate pretty-printing of AnIds via pprId (#8776) (8d29dbe) Message-ID: <20140322193831.BEFE62406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/8d29dbea3afc6e94ec3a13f7beb2f86a8e87ab5e/ghc >--------------------------------------------------------------- commit 8d29dbea3afc6e94ec3a13f7beb2f86a8e87ab5e Author: Dr. ERDI Gergo Date: Fri Mar 14 22:17:45 2014 +0800 Reinstate pretty-printing of AnIds via pprId (#8776) (cherry picked from commit 52003696ff7a2bbf86fbfccfe29b9f146a1ea549) >--------------------------------------------------------------- 8d29dbea3afc6e94ec3a13f7beb2f86a8e87ab5e compiler/main/PprTyThing.hs | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/compiler/main/PprTyThing.hs b/compiler/main/PprTyThing.hs index fb92b5a..1fd5d0c 100644 --- a/compiler/main/PprTyThing.hs +++ b/compiler/main/PprTyThing.hs @@ -104,6 +104,7 @@ pprTyThingHdr = ppr_ty_thing Nothing -- 'TyCon' tidying happening in 'tyThingToIfaceDecl'. See #8776 for details. ppr_ty_thing :: Maybe ShowSub -> TyThing -> SDoc ppr_ty_thing mss tyThing = case tyThing of + AnId id -> pprId id ATyCon tyCon -> case mss of Nothing -> pprTyConHdr tyCon Just ss -> pprTyCon ss tyCon @@ -147,6 +148,11 @@ pprClassHdr cls where (tvs, funDeps) = classTvsFds cls +pprId :: Var -> SDoc +pprId ident + = hang (ppr_bndr ident <+> dcolon) + 2 (pprTypeForUser (idType ident)) + pprTypeForUser :: Type -> SDoc -- We do two things here. -- a) We tidy the type, regardless From git at git.haskell.org Sat Mar 22 19:38:34 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 19:38:34 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Add test case for #8776 (171fe78) Message-ID: <20140322193834.A27B52406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/171fe78f248952af52299484c684eb2885751e1c/ghc >--------------------------------------------------------------- commit 171fe78f248952af52299484c684eb2885751e1c Author: Dr. ERDI Gergo Date: Fri Mar 14 22:34:56 2014 +0800 Add test case for #8776 (cherry picked from commit de32a95ef21970c2db959509861b4f59d1dcbb82) >--------------------------------------------------------------- 171fe78f248952af52299484c684eb2885751e1c testsuite/tests/ghci/scripts/T8776.hs | 6 ++++++ testsuite/tests/ghci/scripts/T8776.script | 2 ++ testsuite/tests/ghci/scripts/T8776.stdout | 1 + testsuite/tests/ghci/scripts/all.T | 2 ++ 4 files changed, 11 insertions(+) diff --git a/testsuite/tests/ghci/scripts/T8776.hs b/testsuite/tests/ghci/scripts/T8776.hs new file mode 100644 index 0000000..55e329c --- /dev/null +++ b/testsuite/tests/ghci/scripts/T8776.hs @@ -0,0 +1,6 @@ +{-# LANGUAGE PatternSynonyms, GADTs #-} +data A x y = (Num x, Eq y) => B + +data R = R{ rX :: Int } + +pattern P = B diff --git a/testsuite/tests/ghci/scripts/T8776.script b/testsuite/tests/ghci/scripts/T8776.script new file mode 100644 index 0000000..baaca9f --- /dev/null +++ b/testsuite/tests/ghci/scripts/T8776.script @@ -0,0 +1,2 @@ +:load T8776.hs +:i P diff --git a/testsuite/tests/ghci/scripts/T8776.stdout b/testsuite/tests/ghci/scripts/T8776.stdout new file mode 100644 index 0000000..9c9e89a --- /dev/null +++ b/testsuite/tests/ghci/scripts/T8776.stdout @@ -0,0 +1 @@ +pattern (Num t, Eq t1) => P :: (A t t1) -- Defined at T8776.hs:6:9 diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T index e9fe6e8..06c0716 100755 --- a/testsuite/tests/ghci/scripts/all.T +++ b/testsuite/tests/ghci/scripts/all.T @@ -166,3 +166,5 @@ test('T8579', normal, ghci_script, ['T8579.script']) test('T8649', normal, ghci_script, ['T8649.script']) test('T8674', normal, ghci_script, ['T8674.script']) test('T8696', normal, ghci_script, ['T8696.script']) +test('T8776', normal, ghci_script, ['T8776.script']) + From git at git.haskell.org Sat Mar 22 19:38:36 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 19:38:36 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: isLexVarSym: check all characters of the name, not just the first one. (7e6ef49) Message-ID: <20140322193837.07DFA2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/7e6ef49593fb6902f8faec0f056788bb8bc81138/ghc >--------------------------------------------------------------- commit 7e6ef49593fb6902f8faec0f056788bb8bc81138 Author: Dr. ERDI Gergo Date: Wed Mar 19 20:07:47 2014 +0800 isLexVarSym: check all characters of the name, not just the first one. This is so that generated names like e.g. workers don't show up as infix operators when using something like -ddump-simpl. (cherry picked from commit a3f78e2476e3d4ead86ef3b10ddd4e14e189ada3) >--------------------------------------------------------------- 7e6ef49593fb6902f8faec0f056788bb8bc81138 compiler/basicTypes/OccName.lhs | 25 +++++++++++++++++++------ 1 file changed, 19 insertions(+), 6 deletions(-) diff --git a/compiler/basicTypes/OccName.lhs b/compiler/basicTypes/OccName.lhs index d53292b..81f7e5d 100644 --- a/compiler/basicTypes/OccName.lhs +++ b/compiler/basicTypes/OccName.lhs @@ -501,7 +501,7 @@ isDataSymOcc _ = False -- it is a data constructor or variable or whatever) isSymOcc :: OccName -> Bool isSymOcc (OccName DataName s) = isLexConSym s -isSymOcc (OccName TcClsName s) = isLexConSym s || isLexVarSym s +isSymOcc (OccName TcClsName s) = isLexSym s isSymOcc (OccName VarName s) = isLexSym s isSymOcc (OccName TvName s) = isLexSym s -- Pretty inefficient! @@ -868,6 +868,15 @@ isTupleOcc_maybe (OccName ns fs) These functions test strings to see if they fit the lexical categories defined in the Haskell report. +Note [Classification of generated names] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +Some names generated for internal use can show up in debugging output, +e.g. when using -ddump-simpl. These generated names start with a $ +but should still be pretty-printed using prefix notation. We make sure +this is the case in isLexVarSym by only classifying a name as a symbol +if all its characters are symbols, not just its first one. + \begin{code} isLexCon, isLexVar, isLexId, isLexSym :: FastString -> Bool isLexConId, isLexConSym, isLexVarId, isLexVarSym :: FastString -> Bool @@ -894,19 +903,23 @@ isLexConSym cs -- Infix type or data constructors | cs == (fsLit "->") = True | otherwise = startsConSym (headFS cs) -isLexVarSym cs -- Infix identifiers - | nullFS cs = False -- e.g. "+" - | otherwise = startsVarSym (headFS cs) +isLexVarSym fs -- Infix identifiers e.g. "+" + = case (if nullFS fs then [] else unpackFS fs) of + [] -> False + (c:cs) -> startsVarSym c && all isVarSymChar cs ------------- startsVarSym, startsVarId, startsConSym, startsConId :: Char -> Bool -startsVarSym c = isSymbolASCII c || (ord c > 0x7f && isSymbol c) -- Infix Ids -startsConSym c = c == ':' -- Infix data constructors +startsVarSym c = isSymbolASCII c || (ord c > 0x7f && isSymbol c) -- Infix Ids +startsConSym c = c == ':' -- Infix data constructors startsVarId c = isLower c || c == '_' -- Ordinary Ids startsConId c = isUpper c || c == '(' -- Ordinary type constructors and data constructors isSymbolASCII :: Char -> Bool isSymbolASCII c = c `elem` "!#$%&*+./<=>?@\\^|~-" + +isVarSymChar :: Char -> Bool +isVarSymChar c = c == ':' || startsVarSym c \end{code} %************************************************************************ From git at git.haskell.org Sat Mar 22 19:38:39 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 19:38:39 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Update expected test outputs to match new format of pretty-printing interface contents (5f28357) Message-ID: <20140322193839.709502406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/5f2835770427121b2e6926ea4af72347d4e2268e/ghc >--------------------------------------------------------------- commit 5f2835770427121b2e6926ea4af72347d4e2268e Author: Dr. ERDI Gergo Date: Wed Mar 19 21:44:38 2014 +0800 Update expected test outputs to match new format of pretty-printing interface contents (cherry picked from commit 21028ee6805b896dbbd8a2d46b9690d1adecdcd1) >--------------------------------------------------------------- 5f2835770427121b2e6926ea4af72347d4e2268e .../indexed-types/should_compile/T3017.stderr | 2 +- testsuite/tests/roles/should_compile/Roles1.stderr | 70 ++++++++++---------- testsuite/tests/roles/should_compile/Roles2.stderr | 20 +++--- testsuite/tests/roles/should_compile/all.T | 4 +- .../tests/typecheck/should_compile/tc231.stderr | 7 +- 5 files changed, 51 insertions(+), 52 deletions(-) diff --git a/testsuite/tests/indexed-types/should_compile/T3017.stderr b/testsuite/tests/indexed-types/should_compile/T3017.stderr index d11fad8..2019047 100644 --- a/testsuite/tests/indexed-types/should_compile/T3017.stderr +++ b/testsuite/tests/indexed-types/should_compile/T3017.stderr @@ -14,7 +14,7 @@ TYPE CONSTRUCTORS No C type associated Roles: [representational] RecFlag NonRecursive, Promotable - = L :: forall a. [a] -> ListColl a Stricts: _ + = L :: [a] -> ListColl a Stricts: _ FamilyInstance: none COERCION AXIOMS axiom Foo.TFCo:R:ElemListColl :: Elem (ListColl a) = a diff --git a/testsuite/tests/roles/should_compile/Roles1.stderr b/testsuite/tests/roles/should_compile/Roles1.stderr index e1808e8..cd027f1 100644 --- a/testsuite/tests/roles/should_compile/Roles1.stderr +++ b/testsuite/tests/roles/should_compile/Roles1.stderr @@ -2,53 +2,53 @@ TYPE SIGNATURES TYPE CONSTRUCTORS T1 :: * -> * data T1 a - No C type associated - Roles: [nominal] - RecFlag NonRecursive, Promotable - = K1 :: forall a. a -> T1 a Stricts: _ - FamilyInstance: none + No C type associated + Roles: [nominal] + RecFlag NonRecursive, Promotable + = K1 :: forall a. a -> T1 a Stricts: _ + FamilyInstance: none T2 :: * -> * data T2 a - No C type associated - Roles: [representational] - RecFlag NonRecursive, Promotable - = K2 :: forall a. a -> T2 a Stricts: _ - FamilyInstance: none + No C type associated + Roles: [representational] + RecFlag NonRecursive, Promotable + = K2 :: forall a. a -> T2 a Stricts: _ + FamilyInstance: none T3 :: k -> * data T3 (k::BOX) (a::k) - No C type associated - Roles: [nominal, phantom] - RecFlag NonRecursive, Not promotable - = K3 :: forall (k::BOX) (a::k). T3 k a - FamilyInstance: none + No C type associated + Roles: [nominal, phantom] + RecFlag NonRecursive, Not promotable + = K3 :: forall (k::BOX) (a::k). T3 k a + FamilyInstance: none T4 :: (* -> *) -> * -> * data T4 (a::* -> *) b - No C type associated - Roles: [nominal, nominal] - RecFlag NonRecursive, Not promotable - = K4 :: forall (a::* -> *) b. (a b) -> T4 a b Stricts: _ - FamilyInstance: none + No C type associated + Roles: [nominal, nominal] + RecFlag NonRecursive, Not promotable + = K4 :: forall (a::* -> *) b. (a b) -> T4 a b Stricts: _ + FamilyInstance: none T5 :: * -> * data T5 a - No C type associated - Roles: [representational] - RecFlag NonRecursive, Promotable - = K5 :: forall a. a -> T5 a Stricts: _ - FamilyInstance: none + No C type associated + Roles: [representational] + RecFlag NonRecursive, Promotable + = K5 :: forall a. a -> T5 a Stricts: _ + FamilyInstance: none T6 :: k -> * data T6 (k::BOX) (a::k) - No C type associated - Roles: [nominal, phantom] - RecFlag NonRecursive, Not promotable - = K6 :: forall (k::BOX) (a::k). T6 k a - FamilyInstance: none + No C type associated + Roles: [nominal, phantom] + RecFlag NonRecursive, Not promotable + = K6 :: forall (k::BOX) (a::k). T6 k a + FamilyInstance: none T7 :: k -> * -> * data T7 (k::BOX) (a::k) b - No C type associated - Roles: [nominal, phantom, representational] - RecFlag NonRecursive, Not promotable - = K7 :: forall (k::BOX) (a::k) b. b -> T7 k a b Stricts: _ - FamilyInstance: none + No C type associated + Roles: [nominal, phantom, representational] + RecFlag NonRecursive, Not promotable + = K7 :: forall (k::BOX) (a::k) b. b -> T7 k a b Stricts: _ + FamilyInstance: none COERCION AXIOMS Dependent modules: [] Dependent packages: [base, ghc-prim, integer-gmp] diff --git a/testsuite/tests/roles/should_compile/Roles2.stderr b/testsuite/tests/roles/should_compile/Roles2.stderr index ac7a94b..f5bcbe6 100644 --- a/testsuite/tests/roles/should_compile/Roles2.stderr +++ b/testsuite/tests/roles/should_compile/Roles2.stderr @@ -2,18 +2,18 @@ TYPE SIGNATURES TYPE CONSTRUCTORS T1 :: * -> * data T1 a - No C type associated - Roles: [representational] - RecFlag NonRecursive, Not promotable - = K1 :: forall a. (IO a) -> T1 a Stricts: _ - FamilyInstance: none + No C type associated + Roles: [representational] + RecFlag NonRecursive, Not promotable + = K1 :: forall a. (IO a) -> T1 a Stricts: _ + FamilyInstance: none T2 :: * -> * data T2 a - No C type associated - Roles: [representational] - RecFlag NonRecursive, Not promotable - = K2 :: forall a. (FunPtr a) -> T2 a Stricts: _ - FamilyInstance: none + No C type associated + Roles: [representational] + RecFlag NonRecursive, Not promotable + = K2 :: forall a. (FunPtr a) -> T2 a Stricts: _ + FamilyInstance: none COERCION AXIOMS Dependent modules: [] Dependent packages: [base, ghc-prim, integer-gmp] diff --git a/testsuite/tests/roles/should_compile/all.T b/testsuite/tests/roles/should_compile/all.T index a016de3..f77e61f 100644 --- a/testsuite/tests/roles/should_compile/all.T +++ b/testsuite/tests/roles/should_compile/all.T @@ -1,5 +1,5 @@ -test('Roles1', only_ways('normal'), compile, ['-ddump-tc']) -test('Roles2', only_ways('normal'), compile, ['-ddump-tc']) +test('Roles1', only_ways('normal'), compile, ['-ddump-tc -fprint-explicit-foralls']) +test('Roles2', only_ways('normal'), compile, ['-ddump-tc -fprint-explicit-foralls']) test('Roles3', only_ways('normal'), compile, ['-ddump-tc']) test('Roles4', only_ways('normal'), compile, ['-ddump-tc']) test('Roles13', only_ways('normal'), compile, ['-ddump-simpl -dsuppress-uniques']) diff --git a/testsuite/tests/typecheck/should_compile/tc231.stderr b/testsuite/tests/typecheck/should_compile/tc231.stderr index 4334d62..16dddda 100644 --- a/testsuite/tests/typecheck/should_compile/tc231.stderr +++ b/testsuite/tests/typecheck/should_compile/tc231.stderr @@ -10,21 +10,20 @@ TYPE CONSTRUCTORS No C type associated Roles: [representational, representational, representational] RecFlag NonRecursive, Promotable - = Node :: forall s a chain. s -> a -> chain -> Q s a chain - Stricts: _ _ _ + = Node :: s -> a -> chain -> Q s a chain Stricts: _ _ _ FamilyInstance: none Z :: * -> * data Z a No C type associated Roles: [representational] RecFlag NonRecursive, Promotable - = Z :: forall a. a -> Z a Stricts: _ + = Z :: a -> Z a Stricts: _ FamilyInstance: none Zork :: * -> * -> * -> Constraint class Zork s a b | a -> b Roles: [nominal, nominal, nominal] RecFlag NonRecursive - huh :: forall chain. Q s a chain -> ST s () + huh :: Q s a chain -> ST s () COERCION AXIOMS axiom ShouldCompile.NTCo:Zork :: Zork s a b = forall chain. Q s a chain -> ST s () From git at git.haskell.org Sat Mar 22 19:38:41 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 19:38:41 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Update ghc --help references to --make and a.out (fixes #8600) (eb1d2f5) Message-ID: <20140322193841.BED962406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/eb1d2f5ca8ebad04f4101609d62317f97847150a/ghc >--------------------------------------------------------------- commit eb1d2f5ca8ebad04f4101609d62317f97847150a Author: ccatalfo Date: Tue Mar 11 22:11:11 2014 -0400 Update ghc --help references to --make and a.out (fixes #8600) Signed-off-by: Austin Seipp (cherry picked from commit 99ef27913dbe55fa57891bbf97d131e0933733e3) >--------------------------------------------------------------- eb1d2f5ca8ebad04f4101609d62317f97847150a driver/ghc-usage.txt | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/driver/ghc-usage.txt b/driver/ghc-usage.txt index 239b454..9de4090 100644 --- a/driver/ghc-usage.txt +++ b/driver/ghc-usage.txt @@ -5,12 +5,12 @@ Usage: To compile and link a complete Haskell program, run the compiler like so: - $$ --make Main + $$ Main where the module Main is in a file named Main.hs (or Main.lhs) in the current directory. The other modules in the program will be located and compiled automatically, and the linked program will be placed in -the file `a.out' (or `Main.exe' on Windows). +the file `Main' (or `Main.exe' on Windows). Alternatively, $$ can be used to compile files individually. Each input file is guided through (some of the) possible phases of a From git at git.haskell.org Sat Mar 22 19:38:44 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 19:38:44 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: linker: Fix indirect calls for x86_64 windows (#2283) (38b3e7b) Message-ID: <20140322193844.264E22406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/38b3e7b7df8ffdedb626b40ad9437aeaacc8024f/ghc >--------------------------------------------------------------- commit 38b3e7b7df8ffdedb626b40ad9437aeaacc8024f Author: Kyrill Briantsev Date: Fri Mar 21 05:42:48 2014 -0500 linker: Fix indirect calls for x86_64 windows (#2283) Signed-off-by: Austin Seipp (cherry picked from commit 7a1c85113dd082153cc07f4792216beaf34daeeb) >--------------------------------------------------------------- 38b3e7b7df8ffdedb626b40ad9437aeaacc8024f rts/Linker.c | 30 ++++++++++++++++++++++++++++-- 1 file changed, 28 insertions(+), 2 deletions(-) diff --git a/rts/Linker.c b/rts/Linker.c index 8f57873..814f930 100644 --- a/rts/Linker.c +++ b/rts/Linker.c @@ -1718,6 +1718,18 @@ typedef /* A list thereof. */ static OpenedDLL* opened_dlls = NULL; + +/* A record for storing indirectly linked functions from DLLs. */ +typedef + struct _IndirectAddr { + void* addr; + struct _IndirectAddr* next; + } + IndirectAddr; + +/* A list thereof. */ +static IndirectAddr* indirects = NULL; + #endif # if defined(OBJFORMAT_ELF) || defined(OBJFORMAT_MACHO) @@ -2189,6 +2201,15 @@ void freeObjectCode (ObjectCode *oc) stgFree(oc->image); #else VirtualFree(oc->image - PEi386_IMAGE_OFFSET, 0, MEM_RELEASE); + + IndirectAddr *ia, *ia_next; + ia = indirects; + while (ia != NULL) { + ia_next = ia->next; + stgFree(ia); + ia = ia_next; + } + #endif #if defined(powerpc_HOST_ARCH) || defined(x86_64_HOST_ARCH) || defined(arm_HOST_ARCH) @@ -3698,15 +3719,20 @@ lookupSymbolInDLLs ( UChar *lbl ) Long description: http://support.microsoft.com/kb/132044 tl;dr: If C/C++ compiler sees __declspec(dllimport) ... foo ... - it generates call __imp_foo, and __imp_foo here has exactly + it generates call *__imp_foo, and __imp_foo here has exactly the same semantics as in __imp_foo = GetProcAddress(..., "foo") */ if (sym == NULL && strncmp ((const char*)lbl, "__imp_", 6) == 0) { sym = GetProcAddress(o_dll->instance, (char*)(lbl+6)); if (sym != NULL) { + IndirectAddr* ret; + ret = stgMallocBytes( sizeof(IndirectAddr), "lookupSymbolInDLLs" ); + ret->addr = sym; + ret->next = indirects; + indirects = ret; errorBelch("warning: %s from %S is linked instead of %s", (char*)(lbl+6), o_dll->name, (char*)lbl); - return sym; + return (void*) & ret->addr; } } From git at git.haskell.org Sat Mar 22 19:38:46 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 19:38:46 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: testsuite: add test for #8831 (797737f) Message-ID: <20140322193846.BABC02406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/797737f65af7e845430685716656567c2aebb344/ghc >--------------------------------------------------------------- commit 797737f65af7e845430685716656567c2aebb344 Author: Austin Seipp Date: Fri Mar 21 04:42:32 2014 -0500 testsuite: add test for #8831 Signed-off-by: Austin Seipp (cherry picked from commit f9b6a2bb6574904ab11476d79896491b111ad7cc) Conflicts: testsuite/tests/ghci/scripts/all.T >--------------------------------------------------------------- 797737f65af7e845430685716656567c2aebb344 .../tests/{driver/recomp009/Sub1.hs => ghci/scripts/T8831.hs} | 4 ++-- testsuite/tests/ghci/scripts/T8831.script | 4 ++++ .../should_run/cgrun049.stdout => ghci/scripts/T8831.stdout} | 0 testsuite/tests/ghci/scripts/all.T | 2 +- 4 files changed, 7 insertions(+), 3 deletions(-) diff --git a/testsuite/tests/driver/recomp009/Sub1.hs b/testsuite/tests/ghci/scripts/T8831.hs similarity index 50% copy from testsuite/tests/driver/recomp009/Sub1.hs copy to testsuite/tests/ghci/scripts/T8831.hs index 25ea755..b0a3cc5 100644 --- a/testsuite/tests/driver/recomp009/Sub1.hs +++ b/testsuite/tests/ghci/scripts/T8831.hs @@ -1,3 +1,3 @@ {-# LANGUAGE TemplateHaskell #-} -module Sub where -x = [| 1 |] +module T8831 where +foo = [| 3 |] diff --git a/testsuite/tests/ghci/scripts/T8831.script b/testsuite/tests/ghci/scripts/T8831.script new file mode 100644 index 0000000..bc6ba89 --- /dev/null +++ b/testsuite/tests/ghci/scripts/T8831.script @@ -0,0 +1,4 @@ +:seti -XTemplateHaskell +:load T8831.hs +$foo + diff --git a/testsuite/tests/codeGen/should_run/cgrun049.stdout b/testsuite/tests/ghci/scripts/T8831.stdout similarity index 100% copy from testsuite/tests/codeGen/should_run/cgrun049.stdout copy to testsuite/tests/ghci/scripts/T8831.stdout diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T index 06c0716..09b03f9 100755 --- a/testsuite/tests/ghci/scripts/all.T +++ b/testsuite/tests/ghci/scripts/all.T @@ -167,4 +167,4 @@ test('T8649', normal, ghci_script, ['T8649.script']) test('T8674', normal, ghci_script, ['T8674.script']) test('T8696', normal, ghci_script, ['T8696.script']) test('T8776', normal, ghci_script, ['T8776.script']) - +test('T8831', normal, ghci_script, ['T8831.script']) From git at git.haskell.org Sat Mar 22 19:38:49 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 19:38:49 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Mark test for #8831 as known-broken (932bd92) Message-ID: <20140322193849.99E152406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/932bd920fd882059cc4654e979039a4db3b9d61f/ghc >--------------------------------------------------------------- commit 932bd920fd882059cc4654e979039a4db3b9d61f Author: Joachim Breitner Date: Sat Mar 22 11:53:03 2014 +0100 Mark test for #8831 as known-broken to keep validate working. (cherry picked from commit 4bc3c8265f988f4456664f502164f52466aab67d) Conflicts: testsuite/tests/ghci/scripts/all.T >--------------------------------------------------------------- 932bd920fd882059cc4654e979039a4db3b9d61f testsuite/tests/ghci/scripts/all.T | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T index 09b03f9..7a0e17d 100755 --- a/testsuite/tests/ghci/scripts/all.T +++ b/testsuite/tests/ghci/scripts/all.T @@ -167,4 +167,4 @@ test('T8649', normal, ghci_script, ['T8649.script']) test('T8674', normal, ghci_script, ['T8674.script']) test('T8696', normal, ghci_script, ['T8696.script']) test('T8776', normal, ghci_script, ['T8776.script']) -test('T8831', normal, ghci_script, ['T8831.script']) +test('T8831', expect_broken(8831), ghci_script, ['T8831.script']) From git at git.haskell.org Sat Mar 22 19:42:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 19:42:24 +0000 (UTC) Subject: [commit: packages/dph] ghc-7.8: Revert "Fix breaking changes due to issue #7021" (556e09c) Message-ID: <20140322194224.96E612406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/dph On branch : ghc-7.8 Link : http://git.haskell.org/packages/dph.git/commitdiff/556e09cdc9f8e1cc22dd10b703c97d0e228b483d >--------------------------------------------------------------- commit 556e09cdc9f8e1cc22dd10b703c97d0e228b483d Author: Austin Seipp Date: Sat Mar 22 13:54:56 2014 -0500 Revert "Fix breaking changes due to issue #7021" This reverts commit aeef7aad83aaa24c503fa18e321d2271829f003b. >--------------------------------------------------------------- 556e09cdc9f8e1cc22dd10b703c97d0e228b483d dph-lifted-copy/Data/Array/Parallel/Lifted/TH/Repr.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/dph-lifted-copy/Data/Array/Parallel/Lifted/TH/Repr.hs b/dph-lifted-copy/Data/Array/Parallel/Lifted/TH/Repr.hs index fb6b02b..9229723 100644 --- a/dph-lifted-copy/Data/Array/Parallel/Lifted/TH/Repr.hs +++ b/dph-lifted-copy/Data/Array/Parallel/Lifted/TH/Repr.hs @@ -367,7 +367,7 @@ wrapPRInstance :: Name -> Name -> Name -> Name -> Q [Dec] wrapPRInstance ty wrap unwrap pwrap = do methods <- genPR_methods (recursiveMethod (wrapGen wrap unwrap pwrap)) - return [InstanceD [ConT ''PA `AppT` a] + return [InstanceD [ClassP ''PA [a]] (ConT ''PR `AppT` (ConT ty `AppT` a)) methods] where @@ -437,7 +437,7 @@ instance_PR_tup :: Int -> DecQ instance_PR_tup arity = do methods <- genPR_methods (recursiveMethod (tupGen arity)) - return $ InstanceD [ConT ''PR `AppT` ty | ty <- tys] + return $ InstanceD [ClassP ''PR [ty] | ty <- tys] (ConT ''PR `AppT` (TupleT arity `mkAppTs` tys)) methods where @@ -485,3 +485,4 @@ tupGen arity = Gen { recursiveCalls = arity pvs = take arity [c : "s" | c <- ['a' ..]] tyname = "(" ++ intercalate "," vs ++ ")" + From git at git.haskell.org Sat Mar 22 20:49:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 20:49:17 +0000 (UTC) Subject: [commit: packages/vector] tag 'vector-0.10.9.1-release' created Message-ID: <20140322204917.AAC222406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/vector New tag : vector-0.10.9.1-release Referencing: 82e01ba28d83c4588b42e2c5c6c95bde0b6aeca9 From git at git.haskell.org Sat Mar 22 20:59:22 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 20:59:22 +0000 (UTC) Subject: [commit: ghc] master: Make cabal01 pass with Cabal 1.18 (#8738). (be2e0e8) Message-ID: <20140322205922.E86A72406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/be2e0e88d7ddd33eef8277c8d67f0b0f3e2874be/ghc >--------------------------------------------------------------- commit be2e0e88d7ddd33eef8277c8d67f0b0f3e2874be Author: Mikhail Glushenkov Date: Tue Mar 4 08:02:36 2014 +0100 Make cabal01 pass with Cabal 1.18 (#8738). Signed-off-by: Austin Seipp >--------------------------------------------------------------- be2e0e88d7ddd33eef8277c8d67f0b0f3e2874be testsuite/tests/cabal/cabal01/Makefile | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/testsuite/tests/cabal/cabal01/Makefile b/testsuite/tests/cabal/cabal01/Makefile index b18d8fc..f1b74b4 100644 --- a/testsuite/tests/cabal/cabal01/Makefile +++ b/testsuite/tests/cabal/cabal01/Makefile @@ -28,7 +28,7 @@ cabal01: # we get a warning if dynlibs are enabled by default that: # Warning: -rtsopts and -with-rtsopts have no effect with -shared. # so we filter the flag out - ./setup configure -v0 --prefix=$(PREFIX) --with-compiler='$(TEST_HC)' --ghc-options='$(filter-out -rtsopts,$(TEST_HC_OPTS))' --with-hc-pkg='$(GHC_PKG)' --package-db=local.db $(VANILLA) $(PROF) $(DYN) + ./setup configure -v0 --prefix=$(PREFIX) --with-compiler='$(TEST_HC)' --ghc-options='$(filter-out -rtsopts,$(TEST_HC_OPTS))' --with-hc-pkg='$(GHC_PKG)' --package-db=local.db $(VANILLA) $(PROF) $(DYN) --libsubdir='$$pkgid' ./setup build -v0 ./setup copy -v0 echo install1: @@ -42,4 +42,3 @@ cabal01: echo dist: ls -1 dist if [ "$(CLEANUP)" != "" ]; then $(MAKE) clean; fi - From git at git.haskell.org Sat Mar 22 20:59:26 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 20:59:26 +0000 (UTC) Subject: [commit: ghc] wip/T8545-ghc-7.8: Switch to relative URLs in .gitmodules (de0b1c5) Message-ID: <20140322205926.8488B2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8545-ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/de0b1c5a0749c3117320d645bf33914293eb2a29/ghc >--------------------------------------------------------------- commit de0b1c5a0749c3117320d645bf33914293eb2a29 Author: Herbert Valerio Riedel Date: Thu Feb 6 08:42:27 2014 +0100 Switch to relative URLs in .gitmodules Previously, the `http://`-protocol part was hardcoded in the URLs, causing the initial clone process to fall back to `http://` even when the ghc.git repo was cloned via one of the other 3 supported transport protocols. This is slightly related to #8545, as it will make it possible to e.g. git clone --recursive git://git.haskell.org/ghc and clone ghc.git including all submodules in one go (i.e. w/o `sync-all`), and w/o falling back to a different (hardwired) Git transport protocol for the submodules. Signed-off-by: Herbert Valerio Riedel (cherry picked from commit ad44e47542a822ac3e02cf514b5d2be52880fc95) >--------------------------------------------------------------- de0b1c5a0749c3117320d645bf33914293eb2a29 .gitmodules | 28 ++++++++++++++-------------- 1 file changed, 14 insertions(+), 14 deletions(-) diff --git a/.gitmodules b/.gitmodules index f0fd280..d83bfd0 100644 --- a/.gitmodules +++ b/.gitmodules @@ -1,56 +1,56 @@ [submodule "libraries/binary"] path = libraries/binary - url = http://git.haskell.org/packages/binary.git + url = ../packages/binary.git ignore = untracked [submodule "libraries/bytestring"] path = libraries/bytestring - url = http://git.haskell.org/packages/bytestring.git + url = ../packages/bytestring.git ignore = untracked [submodule "libraries/Cabal"] path = libraries/Cabal - url = http://git.haskell.org/packages/Cabal.git + url = ../packages/Cabal.git ignore = untracked [submodule "libraries/containers"] path = libraries/containers - url = http://git.haskell.org/packages/containers.git + url = ../packages/containers.git ignore = untracked [submodule "libraries/haskeline"] path = libraries/haskeline - url = http://git.haskell.org/packages/haskeline.git + url = ../packages/haskeline.git ignore = untracked [submodule "libraries/pretty"] path = libraries/pretty - url = http://git.haskell.org/packages/pretty.git + url = ../packages/pretty.git ignore = untracked [submodule "libraries/terminfo"] path = libraries/terminfo - url = http://git.haskell.org/packages/terminfo.git + url = ../packages/terminfo.git ignore = untracked [submodule "libraries/transformers"] path = libraries/transformers - url = http://git.haskell.org/packages/transformers.git + url = ../packages/transformers.git ignore = untracked [submodule "libraries/xhtml"] path = libraries/xhtml - url = http://git.haskell.org/packages/xhtml.git + url = ../packages/xhtml.git ignore = untracked [submodule "libraries/Win32"] path = libraries/Win32 - url = http://git.haskell.org/packages/Win32.git + url = ../packages/Win32.git ignore = untracked [submodule "libraries/primitive"] path = libraries/primitive - url = http://git.haskell.org/packages/primitive.git + url = ../packages/primitive.git ignore = untracked [submodule "libraries/vector"] path = libraries/vector - url = http://git.haskell.org/packages/vector.git + url = ../packages/vector.git ignore = untracked [submodule "libraries/time"] path = libraries/time - url = http://git.haskell.org/packages/time.git + url = ../packages/time.git ignore = untracked [submodule "libraries/random"] path = libraries/random - url = http://git.haskell.org/packages/random.git + url = ../packages/random.git ignore = untracked From git at git.haskell.org Sat Mar 22 20:59:29 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 20:59:29 +0000 (UTC) Subject: [commit: ghc] wip/T8545-ghc-7.8: Convert all sub-repos into proper submodules (re #8545) (6ff196d) Message-ID: <20140322205929.585032406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8545-ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/6ff196dbe60342c6525260a6f163b1bb27438092/ghc >--------------------------------------------------------------- commit 6ff196dbe60342c6525260a6f163b1bb27438092 Author: Herbert Valerio Riedel Date: Sat Mar 22 15:26:34 2014 +0100 Convert all sub-repos into proper submodules (re #8545) ...except for ghc-tarballs which is a waste of bandwidth Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 6ff196dbe60342c6525260a6f163b1bb27438092 .gitignore | 27 ----------------- .gitmodules | 72 ++++++++++++++++++++++++++++++++++++++++++++ libffi-tarballs | 1 + libraries/array | 1 + libraries/base | 1 + libraries/deepseq | 1 + libraries/directory | 1 + libraries/dph | 1 + libraries/filepath | 1 + libraries/ghc-prim | 1 + libraries/haskell2010 | 1 + libraries/haskell98 | 1 + libraries/hoopl | 1 + libraries/hpc | 1 + libraries/integer-gmp | 1 + libraries/integer-simple | 1 + libraries/old-locale | 1 + libraries/old-time | 1 + libraries/parallel | 1 + libraries/process | 1 + libraries/stm | 1 + libraries/template-haskell | 1 + libraries/unix | 1 + nofib | 1 + packages | 48 ++++++++++++++--------------- utils/haddock | 1 + utils/hsc2hs | 1 + 27 files changed, 120 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 6ff196dbe60342c6525260a6f163b1bb27438092 From git at git.haskell.org Sat Mar 22 20:59:31 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 20:59:31 +0000 (UTC) Subject: [commit: ghc] wip/T8545-ghc-7.8's head updated: Convert all sub-repos into proper submodules (re #8545) (6ff196d) Message-ID: <20140322205932.41BE72406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T8545-ghc-7.8' now includes: a8bf4d4 Update submodule to Win32-2.3.0.2 07d58b2 Revert ad15c2, which causes Windows seg-faults (Trac #8834) 57ec032 Add some documentation about type-level literals. 7f5d1f5 Flush after TH in #8884 test case 0bbb8dc Typos db6c7a9 Add OutputableBndr instance for OccName 8da725b pprIfaceContextArr: print a context including the "=>" arrow 2712bcd pprIfaceDecl for IfacePatSyn: use pprPatSynSig 0f51f1c Pretty-print the following TyThings via their IfaceDecl counterpart: * AnId * ACoAxiom * AConLike 0a2e5aa Honor Op_PrintExplicitForalls setting in pprIfaceForAllPart dfeca0d Use prefix notation in pprIfaceDecl for IfaceIds 8d29dbe Reinstate pretty-printing of AnIds via pprId (#8776) 171fe78 Add test case for #8776 7e6ef49 isLexVarSym: check all characters of the name, not just the first one. 5f28357 Update expected test outputs to match new format of pretty-printing interface contents eb1d2f5 Update ghc --help references to --make and a.out (fixes #8600) 38b3e7b linker: Fix indirect calls for x86_64 windows (#2283) 797737f testsuite: add test for #8831 932bd92 Mark test for #8831 as known-broken de0b1c5 Switch to relative URLs in .gitmodules 6ff196d Convert all sub-repos into proper submodules (re #8545) From git at git.haskell.org Sat Mar 22 21:25:57 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 21:25:57 +0000 (UTC) Subject: [commit: packages/stm] master: Bump to version 2.4.3 and convert changelog to markdown (fa48a38) Message-ID: <20140322212557.830BF2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/stm On branch : master Link : http://git.haskell.org/packages/stm.git/commitdiff/fa48a38bd818cd075753342365f14bd66b1d5086 >--------------------------------------------------------------- commit fa48a38bd818cd075753342365f14bd66b1d5086 Author: Herbert Valerio Riedel Date: Sat Mar 22 22:19:34 2014 +0100 Bump to version 2.4.3 and convert changelog to markdown The minor version bump is needed because new function were added since last released version 2.4.2. Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- fa48a38bd818cd075753342365f14bd66b1d5086 changelog | 38 -------------------------------------- changelog.md | 38 ++++++++++++++++++++++++++++++++++++++ stm.cabal | 6 +++--- 3 files changed, 41 insertions(+), 41 deletions(-) diff --git a/changelog b/changelog deleted file mode 100644 index 1296a41..0000000 --- a/changelog +++ /dev/null @@ -1,38 +0,0 @@ --*-changelog-*- - -2.4.2.1 Oct 2013 - - * Updated behaviour of `newBroadcastTChanIO` to match - `newBroadcastTChan` in causing an error on a read from - the broadcast channel - - * Add `mkWeakTVar` - - * Add `isFullTBQueue` - - * Fix `TChan` created via `newBroadcastTChanIO` to throw same - exception on a `readTChan` as when created via `newBroadcastTChan` - -2.4.2 Nov 2012 - - * Add "Control.Concurrent.STM.TSem" (transactional semaphore) - - * Add Applicative/Alternative instances of STM for GHC <7.0 - - * Throw proper exception when `readTChan` called on a broadcast - `TChan` - -2.4 Jul 2012 - - * Add "Control.Concurrent.STM.TQueue" (a faster `TChan`) - - * Add "Control.Concurrent.STM.TBQueue" (a bounded channel based on - `TQueue`) - - * Add `Eq` instance for `TChan` - - * Add `newBroadcastTChan` and `newBroadcastTChanIO` - - * Some performance improvements for `TChan` - - * Add `cloneTChan` diff --git a/changelog.md b/changelog.md new file mode 100644 index 0000000..8feaa2f --- /dev/null +++ b/changelog.md @@ -0,0 +1,38 @@ +# Changelog for [`stm` package](http://hackage.haskell.org/package/stm) + +## 2.4.3 *Mar 2014* + + * Update behaviour of `newBroadcastTChanIO` to match + `newBroadcastTChan` in causing an error on a read from the + broadcast channel + + * Add `mkWeakTVar` + + * Add `isFullTBQueue` + + * Fix `TChan` created via `newBroadcastTChanIO` to throw same + exception on a `readTChan` as when created via `newBroadcastTChan` + + * Update to Cabal 1.10 format + +## 2.4.2 *Nov 2012* + + * Add `Control.Concurrent.STM.TSem` (transactional semaphore) + + * Add Applicative/Alternative instances of STM for GHC <7.0 + + * Throw proper exception when `readTChan` called on a broadcast `TChan` + +## 2.4 *Jul 2012* + + * Add `Control.Concurrent.STM.TQueue` (a faster `TChan`) + + * Add `Control.Concurrent.STM.TBQueue` (a bounded channel based on `TQueue`) + + * Add `Eq` instance for `TChan` + + * Add `newBroadcastTChan` and `newBroadcastTChanIO` + + * Some performance improvements for `TChan` + + * Add `cloneTChan` diff --git a/stm.cabal b/stm.cabal index 998bb24..9313ced 100644 --- a/stm.cabal +++ b/stm.cabal @@ -1,5 +1,5 @@ name: stm -version: 2.4.2.1 +version: 2.4.3 license: BSD3 license-file: LICENSE maintainer: libraries at haskell.org @@ -12,7 +12,7 @@ cabal-version: >=1.10 tested-with: GHC==7.6.3, GHC==7.6.2, GHC==7.6.1, GHC==7.4.2, GHC==7.4.1, GHC==7.2.2, GHC==7.2.1, GHC==7.0.4, GHC==7.0.3, GHC==7.0.2, GHC==7.0.1, GHC==6.12.3 extra-source-files: - changelog + changelog.md source-repository head type: git @@ -21,7 +21,7 @@ source-repository head source-repository this type: git location: http://git.haskell.org/packages/stm.git - tag: stm-2.4.2.1-release + tag: stm-2.4.3-release library default-language: Haskell98 From git at git.haskell.org Sat Mar 22 21:26:06 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 21:26:06 +0000 (UTC) Subject: [commit: packages/stm] ghc-7.8's head updated: Bump to version 2.4.3 and convert changelog to markdown (fa48a38) Message-ID: <20140322212606.605AD2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/stm Branch 'ghc-7.8' now includes: fa48a38 Bump to version 2.4.3 and convert changelog to markdown From git at git.haskell.org Sat Mar 22 21:30:31 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 21:30:31 +0000 (UTC) Subject: [commit: packages/template-haskell] tag 'template-haskell-2.9.0.0-release' created Message-ID: <20140322213031.171C42406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/template-haskell New tag : template-haskell-2.9.0.0-release Referencing: febb9800313fbaff6c6cc702a1a45b8481b07dd6 From git at git.haskell.org Sat Mar 22 22:39:48 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 22:39:48 +0000 (UTC) Subject: [commit: ghc] master: Add test case for #8917 (4779602) Message-ID: <20140322223948.D30402406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/47796026ca35a2438f7a7dc337add2ec3b14f06c/ghc >--------------------------------------------------------------- commit 47796026ca35a2438f7a7dc337add2ec3b14f06c Author: Richard Eisenberg Date: Sat Mar 22 12:34:40 2014 -0400 Add test case for #8917 >--------------------------------------------------------------- 47796026ca35a2438f7a7dc337add2ec3b14f06c testsuite/tests/ghci/scripts/T8917.hs | 8 ++++++++ testsuite/tests/ghci/scripts/T8917.script | 4 ++++ testsuite/tests/ghci/scripts/T8917.stdout | 4 ++++ testsuite/tests/ghci/scripts/all.T | 1 + 4 files changed, 17 insertions(+) diff --git a/testsuite/tests/ghci/scripts/T8917.hs b/testsuite/tests/ghci/scripts/T8917.hs new file mode 100644 index 0000000..b16d928 --- /dev/null +++ b/testsuite/tests/ghci/scripts/T8917.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE DataKinds, PolyKinds, TypeFamilies, TypeOperators #-} + +module T8917 where + +data Nat = Zero | Succ Nat +type family a + b where + Zero + a = a + (Succ n) + m = Succ (n + m) diff --git a/testsuite/tests/ghci/scripts/T8917.script b/testsuite/tests/ghci/scripts/T8917.script new file mode 100644 index 0000000..e79ac31 --- /dev/null +++ b/testsuite/tests/ghci/scripts/T8917.script @@ -0,0 +1,4 @@ +:load T8917 +:seti -XDataKinds -XTypeOperators +:kind! Zero + Succ Zero +:kind! Succ (Zero + Zero) \ No newline at end of file diff --git a/testsuite/tests/ghci/scripts/T8917.stdout b/testsuite/tests/ghci/scripts/T8917.stdout new file mode 100644 index 0000000..8426b6a --- /dev/null +++ b/testsuite/tests/ghci/scripts/T8917.stdout @@ -0,0 +1,4 @@ +Zero + Succ Zero :: Nat += 'Succ 'Zero +Succ (Zero + Zero) :: Nat += 'Succ 'Zero diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T index 0181c2d..d41d985 100755 --- a/testsuite/tests/ghci/scripts/all.T +++ b/testsuite/tests/ghci/scripts/all.T @@ -169,3 +169,4 @@ test('T8696', normal, ghci_script, ['T8696.script']) test('T8776', normal, ghci_script, ['T8776.script']) test('ghci059', normal, ghci_script, ['ghci059.script']) test('T8831', expect_broken(8831), ghci_script, ['T8831.script']) +test('T8917', normal, ghci_script, ['T8917.script']) From git at git.haskell.org Sat Mar 22 22:39:51 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 22:39:51 +0000 (UTC) Subject: [commit: ghc] master: Comments only -- clarifying Notes around compatibility. (9b38f6a) Message-ID: <20140322223951.8C7D42406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9b38f6a12c0a9e932ed4be4758d90556f868f6bf/ghc >--------------------------------------------------------------- commit 9b38f6a12c0a9e932ed4be4758d90556f868f6bf Author: Richard Eisenberg Date: Fri Mar 21 17:22:10 2014 -0400 Comments only -- clarifying Notes around compatibility. >--------------------------------------------------------------- 9b38f6a12c0a9e932ed4be4758d90556f868f6bf compiler/iface/MkIface.lhs | 2 +- compiler/types/CoAxiom.lhs | 1 + compiler/types/FamInstEnv.lhs | 4 +++- 3 files changed, 5 insertions(+), 2 deletions(-) diff --git a/compiler/iface/MkIface.lhs b/compiler/iface/MkIface.lhs index 51df08c..bb51cda 100644 --- a/compiler/iface/MkIface.lhs +++ b/compiler/iface/MkIface.lhs @@ -1525,7 +1525,7 @@ coAxiomToIfaceDecl ax@(CoAxiom { co_ax_tc = tycon, co_ax_branches = branches -- 2nd parameter is the list of branch LHSs, for conversion from incompatible branches -- to incompatible indices --- See [Storing compatibility] in CoAxiom +-- See Note [Storing compatibility] in CoAxiom coAxBranchToIfaceBranch :: TidyEnv -> [[Type]] -> CoAxBranch -> IfaceAxBranch coAxBranchToIfaceBranch env0 lhs_s branch@(CoAxBranch { cab_incomps = incomps }) diff --git a/compiler/types/CoAxiom.lhs b/compiler/types/CoAxiom.lhs index a0a4974..d6122b2 100644 --- a/compiler/types/CoAxiom.lhs +++ b/compiler/types/CoAxiom.lhs @@ -327,6 +327,7 @@ isImplicitCoAxiom = co_ax_implicit coAxBranchIncomps :: CoAxBranch -> [CoAxBranch] coAxBranchIncomps = cab_incomps +-- See Note [Compatibility checking] in FamInstEnv placeHolderIncomps :: [CoAxBranch] placeHolderIncomps = panic "placeHolderIncomps" diff --git a/compiler/types/FamInstEnv.lhs b/compiler/types/FamInstEnv.lhs index c17668b..0421f48 100644 --- a/compiler/types/FamInstEnv.lhs +++ b/compiler/types/FamInstEnv.lhs @@ -439,7 +439,7 @@ only when we can be sure that 'a' is not Int. To achieve this, after finding a possible match within the equations, we have to go back to all previous equations and check that, under the substitution induced by the match, other branches are surely apart. (See -[Apartness].) This is similar to what happens with class +Note [Apartness].) This is similar to what happens with class instance selection, when we need to guarantee that there is only a match and no unifiers. The exact algorithm is different here because the the potentially-overlapping group is closed. @@ -475,6 +475,7 @@ irrelevant (clause 1 of compatible) or benign (clause 2 of compatible). \begin{code} +-- See Note [Compatibility] compatibleBranches :: CoAxBranch -> CoAxBranch -> Bool compatibleBranches (CoAxBranch { cab_lhs = lhs1, cab_rhs = rhs1 }) (CoAxBranch { cab_lhs = lhs2, cab_rhs = rhs2 }) @@ -487,6 +488,7 @@ compatibleBranches (CoAxBranch { cab_lhs = lhs1, cab_rhs = rhs1 }) -- takes a CoAxiom with unknown branch incompatibilities and computes -- the compatibilities +-- See Note [Storing compatibility] in CoAxiom computeAxiomIncomps :: CoAxiom br -> CoAxiom br computeAxiomIncomps ax@(CoAxiom { co_ax_branches = branches }) = ax { co_ax_branches = go [] branches } From git at git.haskell.org Sat Mar 22 22:39:53 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 22:39:53 +0000 (UTC) Subject: [commit: ghc] master: Fix #8917. (c99941c) Message-ID: <20140322223953.AE5CB2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c99941cfeee033fca2df45e9523b65c83be20d31/ghc >--------------------------------------------------------------- commit c99941cfeee033fca2df45e9523b65c83be20d31 Author: Richard Eisenberg Date: Sat Mar 22 13:13:26 2014 -0400 Fix #8917. FamInstEnv.normaliseTcApp should normalise arguments even when the top-level tycon isn't a type family. This was a regression from 7.6 -- not sure when it happened, but it was probably my fault. Fixed now, in any case. >--------------------------------------------------------------- c99941cfeee033fca2df45e9523b65c83be20d31 compiler/types/FamInstEnv.lhs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/compiler/types/FamInstEnv.lhs b/compiler/types/FamInstEnv.lhs index 0421f48..50ced7d 100644 --- a/compiler/types/FamInstEnv.lhs +++ b/compiler/types/FamInstEnv.lhs @@ -959,9 +959,9 @@ normaliseTcApp env role tc tys | otherwise -- No unique matching family instance exists; -- we do not do anything - = (Refl role ty, ty) - where - ty = mkTyConApp tc tys + = let (co, ntys) = normaliseTcArgs env role tc tys in + (co, mkTyConApp tc ntys) + --------------- normaliseTcArgs :: FamInstEnvs -- environment with family instances From git at git.haskell.org Sat Mar 22 22:39:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 22 Mar 2014 22:39:56 +0000 (UTC) Subject: [commit: ghc] master: Remove redundant compatibility check. (b0bcbc0) Message-ID: <20140322223956.1BCB32406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b0bcbc04bbc3e293aa886a7c7e5d3f2c0d6f60f4/ghc >--------------------------------------------------------------- commit b0bcbc04bbc3e293aa886a7c7e5d3f2c0d6f60f4 Author: Richard Eisenberg Date: Fri Mar 21 23:40:47 2014 -0400 Remove redundant compatibility check. Previously, the closed type family compatibility check was done even when type-checking an interface file. But interface files now store compatibility info, so this check was redundant. >--------------------------------------------------------------- b0bcbc04bbc3e293aa886a7c7e5d3f2c0d6f60f4 compiler/iface/TcIface.lhs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/compiler/iface/TcIface.lhs b/compiler/iface/TcIface.lhs index 20adfe5..cc45648 100644 --- a/compiler/iface/TcIface.lhs +++ b/compiler/iface/TcIface.lhs @@ -574,8 +574,7 @@ tc_iface_decl _ _ (IfaceAxiom { ifName = ax_occ, ifTyCon = tc = do { tc_name <- lookupIfaceTop ax_occ ; tc_tycon <- tcIfaceTyCon tc ; tc_branches <- tc_ax_branches tc_tycon branches - ; let axiom = computeAxiomIncomps $ - CoAxiom { co_ax_unique = nameUnique tc_name + ; let axiom = CoAxiom { co_ax_unique = nameUnique tc_name , co_ax_name = tc_name , co_ax_tc = tc_tycon , co_ax_role = role From git at git.haskell.org Sun Mar 23 00:40:03 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Mar 2014 00:40:03 +0000 (UTC) Subject: [commit: ghc] master: sync-all: Skip END actions on exceptions (d523f9b) Message-ID: <20140323004003.C4C872406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d523f9b3d4ce3463e8816cad2139ea397e00f8d1/ghc >--------------------------------------------------------------- commit d523f9b3d4ce3463e8816cad2139ea397e00f8d1 Author: Florian Weimer Date: Thu Mar 13 10:23:56 2014 +0100 sync-all: Skip END actions on exceptions Before this change, the END actions were executed even if the code throws an exception using "die". This resulted in very confusing error reporting when an invalid command line option was specified. Signed-off-by: Austin Seipp >--------------------------------------------------------------- d523f9b3d4ce3463e8816cad2139ea397e00f8d1 sync-all | 7 +++++++ 1 file changed, 7 insertions(+) diff --git a/sync-all b/sync-all index 4b4b7a3..70c9639 100755 --- a/sync-all +++ b/sync-all @@ -7,6 +7,7 @@ use English; $| = 1; # autoflush stdout after each print, to avoid output after die my $initial_working_directory; +my $exit_via_die; my $defaultrepo; my @packages; @@ -956,6 +957,11 @@ BEGIN { } $initial_working_directory = getcwd(); + $SIG{__DIE__} = sub { + die @_ if $^S; + $exit_via_die = 1; + }; + #message "== Checking for left-over testsuite/.git folder"; if (-d "testsuite/.git") { print < Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ac24bf45258af701cdd67423d6107357f27bbedf/ghc >--------------------------------------------------------------- commit ac24bf45258af701cdd67423d6107357f27bbedf Author: Karel Gardas Date: Sun Feb 9 21:58:05 2014 +0100 add --with-ar and --with-ranlib configure parameters Both --with-ar and --with-ranlib are usable on non-GNU/Linux systems where GNU tools are usually installed (or possible to install), but not into standard location nor with standard name. Tested on Solaris 10. Signed-off-by: Austin Seipp >--------------------------------------------------------------- ac24bf45258af701cdd67423d6107357f27bbedf configure.ac | 15 +++++++++++++++ mk/config.mk.in | 1 + 2 files changed, 16 insertions(+) diff --git a/configure.ac b/configure.ac index e7fbc7f..244fcc0 100644 --- a/configure.ac +++ b/configure.ac @@ -486,6 +486,21 @@ FP_ARG_WITH_PATH_GNU_PROG([NM], [nm], [nm]) NmCmd="$NM" AC_SUBST([NmCmd]) +dnl ** Which ar to use? +dnl -------------------------------------------------------------- +FP_ARG_WITH_PATH_GNU_PROG([AR], [ar], [ar]) +ArCmd="$AR" +fp_prog_ar="$AR" +AC_SUBST([ArCmd]) + +dnl ** Which ranlib to use? +dnl -------------------------------------------------------------- +FP_ARG_WITH_PATH_GNU_PROG([RANLIB], [ranlib], [ranlib]) +RanlibCmd="$RANLIB" +RANLIB="$RanlibCmd" +AC_SUBST([RanlibCmd]) + + # Note: we may not have objdump on OS X, and we only need it on Windows (for DLL checks) case $HostOS_CPP in cygwin32|mingw32) diff --git a/mk/config.mk.in b/mk/config.mk.in index fef1fb8..7cc7aec 100644 --- a/mk/config.mk.in +++ b/mk/config.mk.in @@ -661,6 +661,7 @@ DTRACE = @DtraceCmd@ LD = @LdCmd@ NM = @NmCmd@ +AR = @ArCmd@ OBJDUMP = @ObjdumpCmd@ LLC = @LlcCmd@ From git at git.haskell.org Sun Mar 23 00:40:09 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Mar 2014 00:40:09 +0000 (UTC) Subject: [commit: ghc] master: change deriveConstants to use nm in a POSIX way (fixes #8781) (045b280) Message-ID: <20140323004010.1D49A2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/045b28033a33a48d31951240a8cb35f2b78345dc/ghc >--------------------------------------------------------------- commit 045b28033a33a48d31951240a8cb35f2b78345dc Author: Karel Gardas Date: Sat Mar 22 22:33:05 2014 +0100 change deriveConstants to use nm in a POSIX way (fixes #8781) The patch provided by Christian Maeder Signed-off-by: Karel Gardas Signed-off-by: Austin Seipp >--------------------------------------------------------------- 045b28033a33a48d31951240a8cb35f2b78345dc utils/deriveConstants/DeriveConstants.hs | 30 ++++++++++-------------------- 1 file changed, 10 insertions(+), 20 deletions(-) diff --git a/utils/deriveConstants/DeriveConstants.hs b/utils/deriveConstants/DeriveConstants.hs index 293fe65..6344569 100644 --- a/utils/deriveConstants/DeriveConstants.hs +++ b/utils/deriveConstants/DeriveConstants.hs @@ -638,7 +638,7 @@ getWanted verbose tmpdir gccProgram gccFlags nmProgram oFile = tmpdir "tmp.o" writeFile cFile cStuff execute verbose gccProgram (gccFlags ++ ["-c", cFile, "-o", oFile]) - xs <- readProcess nmProgram [oFile] "" + xs <- readProcess nmProgram ["-P", oFile] "" let ls = lines xs ms = map parseNmLine ls m = Map.fromList $ catMaybes ms @@ -707,27 +707,17 @@ getWanted verbose tmpdir gccProgram gccFlags nmProgram doWanted (ClosurePayloadMacro {}) = [] doWanted (FieldTypeGcptrMacro {}) = [] - -- parseNmLine parses nm output that looks like - -- "0000000b C derivedConstantMAX_Vanilla_REG" + -- parseNmLine parses "nm -P" output that looks like + -- "_derivedConstantMAX_Vanilla_REG C b 0" Mac OS X + -- "derivedConstantMAX_Vanilla_REG C 0000000b 0000000b" GNU + -- "derivedConstantMAX_Vanilla_REG D 1 b" Solaris -- and returns ("MAX_Vanilla_REG", 11) - parseNmLine xs0 = case break (' ' ==) xs0 of - (x1, ' ' : xs1) -> - case break (' ' ==) xs1 of - (x2, ' ' : x3) -> - case readHex x1 of - [(size, "")] -> - case x2 of - "C" -> - let x3' = case x3 of - '_' : rest -> rest - _ -> x3 - in case stripPrefix prefix x3' of - Just name -> - Just (name, size) - _ -> Nothing - _ -> Nothing - _ -> Nothing + parseNmLine xs0 = case words xs0 of + [x0, x1, x2, x3] -> case stripPrefix prefix $ dropWhile (== '_') x0 of + Just name -> case readHex $ if x1 == "C" then x2 else x3 of + [(size, "")] -> Just (name, size) _ -> Nothing + _ -> Nothing _ -> Nothing -- If an Int value is larger than 2^28 or smaller From git at git.haskell.org Sun Mar 23 00:40:12 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Mar 2014 00:40:12 +0000 (UTC) Subject: [commit: ghc] master: Add a simplistic Vagrantfile with bootstrapping (ace7477) Message-ID: <20140323004013.2F4982406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ace7477690752d85defd71c083863f14db241350/ghc >--------------------------------------------------------------- commit ace7477690752d85defd71c083863f14db241350 Author: Austin Seipp Date: Sat Mar 22 15:21:40 2014 -0500 Add a simplistic Vagrantfile with bootstrapping This adds a simple Vagrantfile to the root directory, which you can use to easily spin up RHEL/Debian/Ubuntu virtual machine in seconds to test GHC. For example, from the root of the GHC tree, you can say: $ vagrant up ubuntu1204-amd64 $ vagrant ssh ubuntu1204-amd64 This will give you access to a provisioned Ubuntu 12.04 virtual machine with all the necessary GHC dependencies installed (modulo a few things). Debian 7/CentOS 6.5/Ubuntu 12.04 only for now, in amd64/i386 configurations. In the future I plan to at least add FreeBSD and NixOS boxes where possible. Improvements are necessary of course. By default a box is given 4GB of RAM and 2 cores, and resolves DNS entries by routing through the host DNS configuration. Do not run 'vagrant up' unless you have lots of RAM as it will spawn *every* virtual machine. Hopefully, this should make it far easier for contributors to get started eventually. Signed-off-by: Austin Seipp >--------------------------------------------------------------- ace7477690752d85defd71c083863f14db241350 Vagrantfile | 50 +++++++++++++++++++++++++++++++++++++++++++++ vagrant/bootstrap-deb.sh | 3 +++ vagrant/bootstrap-rhel.sh | 4 ++++ 3 files changed, 57 insertions(+) diff --git a/Vagrantfile b/Vagrantfile new file mode 100644 index 0000000..9c11601 --- /dev/null +++ b/Vagrantfile @@ -0,0 +1,50 @@ +# -*- mode: ruby -*- +# vi: set ft=ruby : + +MACHINES = + { "ubuntu1204-i386" => + { :box => "chef/ubuntu-12.04-i386", + :provision => "vagrant/bootstrap-deb.sh" + }, + "ubuntu1204-amd64" => + { :box => "chef/ubuntu-12.04", + :provision => "vagrant/bootstrap-deb.sh" + }, + "centos65-i386" => + { :box => "chef/centos-6.5-i386", + :provision => "vagrant/bootstrap-rhel.sh" + }, + "centos65-amd64" => + { :box => "chef/centos-6.5", + :provision => "vagrant/bootstrap-rhel.sh" + }, + "debian74-i386" => + { :box => "chef/debian-7.4-i386", + :provision => "vagrant/bootstrap-deb.sh" + }, + "debian74-amd64" => + { :box => "chef/debian-7.4", + :provision => "vagrant/bootstrap-deb.sh" + } + } + +VAGRANTFILE_API_VERSION = "2" +Vagrant.configure(VAGRANTFILE_API_VERSION) do |config| + MACHINES.each_pair do |name, opts| + config.vm.define name do |c| + c.vm.box = opts[:box] + c.vm.network "public_network" + c.vm.provision :shell, :path => opts[:provision] + c.vm.provider "virtualbox" do |vb| + vb.gui = false; vb.memory = 4096; vb.cpus = 2 + vb.customize ["modifyvm", :id, "--natdnshostresolver1", "on"] + end + c.vm.provider "vmware_workstation" do |vb| + vb.gui = false; vb.vmx["memsize"] = "4096"; vb.vmx["numvcpus"] = "2" + end + c.vm.provider "vmware_fusion" do |vb| + vb.gui = false; vb.vmx["memsize"] = "4096"; vb.vmx["numvcpus"] = "2" + end + end + end +end diff --git a/vagrant/bootstrap-deb.sh b/vagrant/bootstrap-deb.sh new file mode 100755 index 0000000..b9ba957 --- /dev/null +++ b/vagrant/bootstrap-deb.sh @@ -0,0 +1,3 @@ +#!/bin/sh +apt-get update +apt-get build-dep -y ghc diff --git a/vagrant/bootstrap-rhel.sh b/vagrant/bootstrap-rhel.sh new file mode 100755 index 0000000..5086279 --- /dev/null +++ b/vagrant/bootstrap-rhel.sh @@ -0,0 +1,4 @@ +#!/bin/sh +yum update -y +yum install -y glibc-devel ncurses-devel gmp-devel autoconf automake libtool \ + gcc make perl python ghc git docbook-utils docbook-utils-pdf docbook-style-xsl From git at git.haskell.org Sun Mar 23 00:50:12 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Mar 2014 00:50:12 +0000 (UTC) Subject: [commit: ghc] branch 'wip/recurs-compat' created Message-ID: <20140323005012.EAA8F2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/recurs-compat Referencing: 2cc3a262e96518486dbaacfaa879d7d3e259b729 From git at git.haskell.org Sun Mar 23 00:50:16 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Mar 2014 00:50:16 +0000 (UTC) Subject: [commit: ghc] wip/recurs-compat: Implement recursive compatibility check for closed type families. (2cc3a26) Message-ID: <20140323005016.10F172406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/recurs-compat Link : http://ghc.haskell.org/trac/ghc/changeset/2cc3a262e96518486dbaacfaa879d7d3e259b729/ghc >--------------------------------------------------------------- commit 2cc3a262e96518486dbaacfaa879d7d3e259b729 Author: Richard Eisenberg Date: Sat Mar 22 13:16:26 2014 -0400 Implement recursive compatibility check for closed type families. Now, on a closed type family, two branches are considered compatible if their RHSs **normalize** to the same type. Previously, the RHSs had to be identical (under the unifying substitution). This allows more reductions -- yay. CAVEAT: This is probably not type-safe with UndecidableInstances. Someone (er... me) has to Think Hard about this before merging. It might be unsafe even with imported non-terminating instances (so, without UndecidableInstances in the same module). There's a change this isn't type-safe even without UndecidableInstances, but I'm not too worried about that possibility. >--------------------------------------------------------------- 2cc3a262e96518486dbaacfaa879d7d3e259b729 compiler/typecheck/TcSMonad.lhs | 11 +- compiler/types/FamInstEnv.lhs | 217 ++++++++++++++++++++++++++++++--------- 2 files changed, 177 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 2cc3a262e96518486dbaacfaa879d7d3e259b729 From git at git.haskell.org Sun Mar 23 02:01:45 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Mar 2014 02:01:45 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Add test case for #8917 (9055d6b) Message-ID: <20140323020145.2AC022406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/9055d6b66ca93c3a576320286863c93d9f1996c5/ghc >--------------------------------------------------------------- commit 9055d6b66ca93c3a576320286863c93d9f1996c5 Author: Richard Eisenberg Date: Sat Mar 22 12:34:40 2014 -0400 Add test case for #8917 (cherry picked from commit 47796026ca35a2438f7a7dc337add2ec3b14f06c) >--------------------------------------------------------------- 9055d6b66ca93c3a576320286863c93d9f1996c5 testsuite/tests/ghci/scripts/T8917.hs | 8 ++++++++ testsuite/tests/ghci/scripts/T8917.script | 4 ++++ testsuite/tests/ghci/scripts/T8917.stdout | 4 ++++ testsuite/tests/ghci/scripts/all.T | 1 + 4 files changed, 17 insertions(+) diff --git a/testsuite/tests/ghci/scripts/T8917.hs b/testsuite/tests/ghci/scripts/T8917.hs new file mode 100644 index 0000000..b16d928 --- /dev/null +++ b/testsuite/tests/ghci/scripts/T8917.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE DataKinds, PolyKinds, TypeFamilies, TypeOperators #-} + +module T8917 where + +data Nat = Zero | Succ Nat +type family a + b where + Zero + a = a + (Succ n) + m = Succ (n + m) diff --git a/testsuite/tests/ghci/scripts/T8917.script b/testsuite/tests/ghci/scripts/T8917.script new file mode 100644 index 0000000..e79ac31 --- /dev/null +++ b/testsuite/tests/ghci/scripts/T8917.script @@ -0,0 +1,4 @@ +:load T8917 +:seti -XDataKinds -XTypeOperators +:kind! Zero + Succ Zero +:kind! Succ (Zero + Zero) \ No newline at end of file diff --git a/testsuite/tests/ghci/scripts/T8917.stdout b/testsuite/tests/ghci/scripts/T8917.stdout new file mode 100644 index 0000000..8426b6a --- /dev/null +++ b/testsuite/tests/ghci/scripts/T8917.stdout @@ -0,0 +1,4 @@ +Zero + Succ Zero :: Nat += 'Succ 'Zero +Succ (Zero + Zero) :: Nat += 'Succ 'Zero diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T index 7a0e17d..59a29ed 100755 --- a/testsuite/tests/ghci/scripts/all.T +++ b/testsuite/tests/ghci/scripts/all.T @@ -168,3 +168,4 @@ test('T8674', normal, ghci_script, ['T8674.script']) test('T8696', normal, ghci_script, ['T8696.script']) test('T8776', normal, ghci_script, ['T8776.script']) test('T8831', expect_broken(8831), ghci_script, ['T8831.script']) +test('T8917', normal, ghci_script, ['T8917.script']) From git at git.haskell.org Sun Mar 23 02:01:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Mar 2014 02:01:47 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Fix #8917. (3dbbe12) Message-ID: <20140323020147.A6C0F2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/3dbbe12dba3ae95d7215164dbdc751c051a0be08/ghc >--------------------------------------------------------------- commit 3dbbe12dba3ae95d7215164dbdc751c051a0be08 Author: Richard Eisenberg Date: Sat Mar 22 13:13:26 2014 -0400 Fix #8917. FamInstEnv.normaliseTcApp should normalise arguments even when the top-level tycon isn't a type family. This was a regression from 7.6 -- not sure when it happened, but it was probably my fault. Fixed now, in any case. (cherry picked from commit c99941cfeee033fca2df45e9523b65c83be20d31) >--------------------------------------------------------------- 3dbbe12dba3ae95d7215164dbdc751c051a0be08 compiler/types/FamInstEnv.lhs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/compiler/types/FamInstEnv.lhs b/compiler/types/FamInstEnv.lhs index c17668b..bf89484 100644 --- a/compiler/types/FamInstEnv.lhs +++ b/compiler/types/FamInstEnv.lhs @@ -957,9 +957,9 @@ normaliseTcApp env role tc tys | otherwise -- No unique matching family instance exists; -- we do not do anything - = (Refl role ty, ty) - where - ty = mkTyConApp tc tys + = let (co, ntys) = normaliseTcArgs env role tc tys in + (co, mkTyConApp tc ntys) + --------------- normaliseTcArgs :: FamInstEnvs -- environment with family instances From git at git.haskell.org Sun Mar 23 02:01:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Mar 2014 02:01:50 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: change deriveConstants to use nm in a POSIX way (fixes #8781) (e7563ec) Message-ID: <20140323020150.1DCE82406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/e7563ec2e03740074903036bf129fc972b623c23/ghc >--------------------------------------------------------------- commit e7563ec2e03740074903036bf129fc972b623c23 Author: Karel Gardas Date: Sat Mar 22 22:33:05 2014 +0100 change deriveConstants to use nm in a POSIX way (fixes #8781) The patch provided by Christian Maeder Signed-off-by: Karel Gardas Signed-off-by: Austin Seipp (cherry picked from commit 045b28033a33a48d31951240a8cb35f2b78345dc) >--------------------------------------------------------------- e7563ec2e03740074903036bf129fc972b623c23 utils/deriveConstants/DeriveConstants.hs | 30 ++++++++++-------------------- 1 file changed, 10 insertions(+), 20 deletions(-) diff --git a/utils/deriveConstants/DeriveConstants.hs b/utils/deriveConstants/DeriveConstants.hs index 10df61c..54ee6a1 100644 --- a/utils/deriveConstants/DeriveConstants.hs +++ b/utils/deriveConstants/DeriveConstants.hs @@ -638,7 +638,7 @@ getWanted verbose tmpdir gccProgram gccFlags nmProgram oFile = tmpdir "tmp.o" writeFile cFile cStuff execute verbose gccProgram (gccFlags ++ ["-c", cFile, "-o", oFile]) - xs <- readProcess nmProgram [oFile] "" + xs <- readProcess nmProgram ["-P", oFile] "" let ls = lines xs ms = map parseNmLine ls m = Map.fromList $ catMaybes ms @@ -707,27 +707,17 @@ getWanted verbose tmpdir gccProgram gccFlags nmProgram doWanted (ClosurePayloadMacro {}) = [] doWanted (FieldTypeGcptrMacro {}) = [] - -- parseNmLine parses nm output that looks like - -- "0000000b C derivedConstantMAX_Vanilla_REG" + -- parseNmLine parses "nm -P" output that looks like + -- "_derivedConstantMAX_Vanilla_REG C b 0" Mac OS X + -- "derivedConstantMAX_Vanilla_REG C 0000000b 0000000b" GNU + -- "derivedConstantMAX_Vanilla_REG D 1 b" Solaris -- and returns ("MAX_Vanilla_REG", 11) - parseNmLine xs0 = case break (' ' ==) xs0 of - (x1, ' ' : xs1) -> - case break (' ' ==) xs1 of - (x2, ' ' : x3) -> - case readHex x1 of - [(size, "")] -> - case x2 of - "C" -> - let x3' = case x3 of - '_' : rest -> rest - _ -> x3 - in case stripPrefix prefix x3' of - Just name -> - Just (name, size) - _ -> Nothing - _ -> Nothing - _ -> Nothing + parseNmLine xs0 = case words xs0 of + [x0, x1, x2, x3] -> case stripPrefix prefix $ dropWhile (== '_') x0 of + Just name -> case readHex $ if x1 == "C" then x2 else x3 of + [(size, "")] -> Just (name, size) _ -> Nothing + _ -> Nothing _ -> Nothing -- If an Int value is larger than 2^28 or smaller From git at git.haskell.org Sun Mar 23 02:01:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Mar 2014 02:01:52 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: add --with-ar and --with-ranlib configure parameters (05e160e) Message-ID: <20140323020152.AD5A32406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/05e160e36527f6f36f997d7aa56f0cbe4cbb50a3/ghc >--------------------------------------------------------------- commit 05e160e36527f6f36f997d7aa56f0cbe4cbb50a3 Author: Karel Gardas Date: Sun Feb 9 21:58:05 2014 +0100 add --with-ar and --with-ranlib configure parameters Both --with-ar and --with-ranlib are usable on non-GNU/Linux systems where GNU tools are usually installed (or possible to install), but not into standard location nor with standard name. Tested on Solaris 10. Signed-off-by: Austin Seipp (cherry picked from commit ac24bf45258af701cdd67423d6107357f27bbedf) >--------------------------------------------------------------- 05e160e36527f6f36f997d7aa56f0cbe4cbb50a3 configure.ac | 15 +++++++++++++++ mk/config.mk.in | 1 + 2 files changed, 16 insertions(+) diff --git a/configure.ac b/configure.ac index 1c58da0..d32fd20 100644 --- a/configure.ac +++ b/configure.ac @@ -486,6 +486,21 @@ FP_ARG_WITH_PATH_GNU_PROG([NM], [nm], [nm]) NmCmd="$NM" AC_SUBST([NmCmd]) +dnl ** Which ar to use? +dnl -------------------------------------------------------------- +FP_ARG_WITH_PATH_GNU_PROG([AR], [ar], [ar]) +ArCmd="$AR" +fp_prog_ar="$AR" +AC_SUBST([ArCmd]) + +dnl ** Which ranlib to use? +dnl -------------------------------------------------------------- +FP_ARG_WITH_PATH_GNU_PROG([RANLIB], [ranlib], [ranlib]) +RanlibCmd="$RANLIB" +RANLIB="$RanlibCmd" +AC_SUBST([RanlibCmd]) + + # Note: we may not have objdump on OS X, and we only need it on Windows (for DLL checks) case $HostOS_CPP in cygwin32|mingw32) diff --git a/mk/config.mk.in b/mk/config.mk.in index fef1fb8..7cc7aec 100644 --- a/mk/config.mk.in +++ b/mk/config.mk.in @@ -661,6 +661,7 @@ DTRACE = @DtraceCmd@ LD = @LdCmd@ NM = @NmCmd@ +AR = @ArCmd@ OBJDUMP = @ObjdumpCmd@ LLC = @LlcCmd@ From git at git.haskell.org Sun Mar 23 07:46:06 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Mar 2014 07:46:06 +0000 (UTC) Subject: [commit: ghc] wip/T8545-ghc-7.8: Switch to relative URLs in .gitmodules (28923eb) Message-ID: <20140323074606.D24E12406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8545-ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/28923eb17d1e46c0b7a017f672c8ecb5862d8531/ghc >--------------------------------------------------------------- commit 28923eb17d1e46c0b7a017f672c8ecb5862d8531 Author: Herbert Valerio Riedel Date: Thu Feb 6 08:42:27 2014 +0100 Switch to relative URLs in .gitmodules Previously, the `http://`-protocol part was hardcoded in the URLs, causing the initial clone process to fall back to `http://` even when the ghc.git repo was cloned via one of the other 3 supported transport protocols. This is slightly related to #8545, as it will make it possible to e.g. git clone --recursive git://git.haskell.org/ghc and clone ghc.git including all submodules in one go (i.e. w/o `sync-all`), and w/o falling back to a different (hardwired) Git transport protocol for the submodules. Signed-off-by: Herbert Valerio Riedel (cherry picked from commit ad44e47542a822ac3e02cf514b5d2be52880fc95) >--------------------------------------------------------------- 28923eb17d1e46c0b7a017f672c8ecb5862d8531 .gitmodules | 28 ++++++++++++++-------------- 1 file changed, 14 insertions(+), 14 deletions(-) diff --git a/.gitmodules b/.gitmodules index f0fd280..d83bfd0 100644 --- a/.gitmodules +++ b/.gitmodules @@ -1,56 +1,56 @@ [submodule "libraries/binary"] path = libraries/binary - url = http://git.haskell.org/packages/binary.git + url = ../packages/binary.git ignore = untracked [submodule "libraries/bytestring"] path = libraries/bytestring - url = http://git.haskell.org/packages/bytestring.git + url = ../packages/bytestring.git ignore = untracked [submodule "libraries/Cabal"] path = libraries/Cabal - url = http://git.haskell.org/packages/Cabal.git + url = ../packages/Cabal.git ignore = untracked [submodule "libraries/containers"] path = libraries/containers - url = http://git.haskell.org/packages/containers.git + url = ../packages/containers.git ignore = untracked [submodule "libraries/haskeline"] path = libraries/haskeline - url = http://git.haskell.org/packages/haskeline.git + url = ../packages/haskeline.git ignore = untracked [submodule "libraries/pretty"] path = libraries/pretty - url = http://git.haskell.org/packages/pretty.git + url = ../packages/pretty.git ignore = untracked [submodule "libraries/terminfo"] path = libraries/terminfo - url = http://git.haskell.org/packages/terminfo.git + url = ../packages/terminfo.git ignore = untracked [submodule "libraries/transformers"] path = libraries/transformers - url = http://git.haskell.org/packages/transformers.git + url = ../packages/transformers.git ignore = untracked [submodule "libraries/xhtml"] path = libraries/xhtml - url = http://git.haskell.org/packages/xhtml.git + url = ../packages/xhtml.git ignore = untracked [submodule "libraries/Win32"] path = libraries/Win32 - url = http://git.haskell.org/packages/Win32.git + url = ../packages/Win32.git ignore = untracked [submodule "libraries/primitive"] path = libraries/primitive - url = http://git.haskell.org/packages/primitive.git + url = ../packages/primitive.git ignore = untracked [submodule "libraries/vector"] path = libraries/vector - url = http://git.haskell.org/packages/vector.git + url = ../packages/vector.git ignore = untracked [submodule "libraries/time"] path = libraries/time - url = http://git.haskell.org/packages/time.git + url = ../packages/time.git ignore = untracked [submodule "libraries/random"] path = libraries/random - url = http://git.haskell.org/packages/random.git + url = ../packages/random.git ignore = untracked From git at git.haskell.org Sun Mar 23 07:46:09 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Mar 2014 07:46:09 +0000 (UTC) Subject: [commit: ghc] wip/T8545-ghc-7.8: Convert all sub-repos into proper submodules (re #8545) (ed9b7ea) Message-ID: <20140323074610.6E9B82406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8545-ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/ed9b7ea6f13d51fa5d2718c1463891f0cf5184b0/ghc >--------------------------------------------------------------- commit ed9b7ea6f13d51fa5d2718c1463891f0cf5184b0 Author: Herbert Valerio Riedel Date: Sat Mar 22 15:26:34 2014 +0100 Convert all sub-repos into proper submodules (re #8545) ...except for ghc-tarballs which is a waste of bandwidth Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- ed9b7ea6f13d51fa5d2718c1463891f0cf5184b0 .gitignore | 27 ----------------- .gitmodules | 72 ++++++++++++++++++++++++++++++++++++++++++++ libffi-tarballs | 1 + libraries/array | 1 + libraries/base | 1 + libraries/deepseq | 1 + libraries/directory | 1 + libraries/dph | 1 + libraries/filepath | 1 + libraries/ghc-prim | 1 + libraries/haskell2010 | 1 + libraries/haskell98 | 1 + libraries/hoopl | 1 + libraries/hpc | 1 + libraries/integer-gmp | 1 + libraries/integer-simple | 1 + libraries/old-locale | 1 + libraries/old-time | 1 + libraries/parallel | 1 + libraries/process | 1 + libraries/stm | 1 + libraries/template-haskell | 1 + libraries/unix | 1 + nofib | 1 + packages | 48 ++++++++++++++--------------- utils/haddock | 1 + utils/hsc2hs | 1 + 27 files changed, 120 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 ed9b7ea6f13d51fa5d2718c1463891f0cf5184b0 From git at git.haskell.org Sun Mar 23 07:46:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Mar 2014 07:46:11 +0000 (UTC) Subject: [commit: ghc] wip/T8545-ghc-7.8's head updated: Convert all sub-repos into proper submodules (re #8545) (ed9b7ea) Message-ID: <20140323074611.A37BD2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T8545-ghc-7.8' now includes: 9055d6b Add test case for #8917 3dbbe12 Fix #8917. e7563ec change deriveConstants to use nm in a POSIX way (fixes #8781) 05e160e add --with-ar and --with-ranlib configure parameters 28923eb Switch to relative URLs in .gitmodules ed9b7ea Convert all sub-repos into proper submodules (re #8545) From git at git.haskell.org Sun Mar 23 09:35:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Mar 2014 09:35:11 +0000 (UTC) Subject: [commit: packages/template-haskell] master: Bump to 2.10.0.0 (9bcc122) Message-ID: <20140323093511.E8C182406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/template-haskell On branch : master Link : http://git.haskell.org/packages/template-haskell.git/commitdiff/9bcc122819a6f4a2ae7ad569717324b8368e801c >--------------------------------------------------------------- commit 9bcc122819a6f4a2ae7ad569717324b8368e801c Author: Herbert Valerio Riedel Date: Sun Mar 23 10:02:44 2014 +0100 Bump to 2.10.0.0 Due to backward-incompat changes in 57b662c (re #7021) Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 9bcc122819a6f4a2ae7ad569717324b8368e801c template-haskell.cabal | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/template-haskell.cabal b/template-haskell.cabal index ada86b8..d3cf0cc 100644 --- a/template-haskell.cabal +++ b/template-haskell.cabal @@ -1,6 +1,6 @@ name: template-haskell -version: 2.9.0.0 --- GHC 7.6.1 released with 2.8.0.0 +version: 2.10.0.0 +-- GHC 7.8.1 released with 2.9.0.0 license: BSD3 license-file: LICENSE category: Template Haskell @@ -23,7 +23,7 @@ source-repository head source-repository this type: git location: http://git.haskell.org/packages/template-haskell.git - tag: template-haskell-2.9.0.0-release + tag: template-haskell-2.10.0.0-release Library default-language: Haskell2010 From git at git.haskell.org Sun Mar 23 09:36:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Mar 2014 09:36:17 +0000 (UTC) Subject: [commit: packages/dph] master: Follow template-haskell version bump (2984641) Message-ID: <20140323093618.2E3E92406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/dph On branch : master Link : http://git.haskell.org/packages/dph.git/commitdiff/2984641ae0c4739b168ee1fb956fd54f741f30e7 >--------------------------------------------------------------- commit 2984641ae0c4739b168ee1fb956fd54f741f30e7 Author: Herbert Valerio Riedel Date: Sun Mar 23 10:34:40 2014 +0100 Follow template-haskell version bump Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 2984641ae0c4739b168ee1fb956fd54f741f30e7 dph-lifted-base/dph-lifted-base.cabal | 2 +- dph-lifted-copy/dph-lifted-copy.cabal | 2 +- dph-lifted-vseg/dph-lifted-vseg.cabal | 2 +- 3 files changed, 3 insertions(+), 3 deletions(-) diff --git a/dph-lifted-base/dph-lifted-base.cabal b/dph-lifted-base/dph-lifted-base.cabal index f4dd94a..591b4be 100644 --- a/dph-lifted-base/dph-lifted-base.cabal +++ b/dph-lifted-base/dph-lifted-base.cabal @@ -57,7 +57,7 @@ Library ghc == 7.*, array == 0.5.*, random == 1.0.*, - template-haskell == 2.9.*, + template-haskell == 2.10.*, dph-base == 0.8.*, dph-prim-par == 0.8.*, vector == 0.10.*, diff --git a/dph-lifted-copy/dph-lifted-copy.cabal b/dph-lifted-copy/dph-lifted-copy.cabal index 211ca3c..fbda5a3 100644 --- a/dph-lifted-copy/dph-lifted-copy.cabal +++ b/dph-lifted-copy/dph-lifted-copy.cabal @@ -66,7 +66,7 @@ Library ghc == 7.*, array == 0.5.*, random == 1.0.*, - template-haskell == 2.9.*, + template-haskell == 2.10.*, dph-base == 0.8.*, dph-prim-par == 0.8.*, vector == 0.10.* diff --git a/dph-lifted-vseg/dph-lifted-vseg.cabal b/dph-lifted-vseg/dph-lifted-vseg.cabal index ca7573b..3657890 100644 --- a/dph-lifted-vseg/dph-lifted-vseg.cabal +++ b/dph-lifted-vseg/dph-lifted-vseg.cabal @@ -97,7 +97,7 @@ Library ghc == 7.*, array == 0.5.*, random == 1.0.*, - template-haskell == 2.9.*, + template-haskell == 2.10.*, dph-base == 0.8.*, dph-prim-par == 0.8.*, dph-lifted-base == 0.8.*, From git at git.haskell.org Sun Mar 23 09:49:34 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Mar 2014 09:49:34 +0000 (UTC) Subject: [commit: ghc] master: Convert haddock into a proper submodule (re #8545) (34b0721) Message-ID: <20140323094934.5E7D52406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/34b072177b687c8fcc24f87293beae0752e82d32/ghc >--------------------------------------------------------------- commit 34b072177b687c8fcc24f87293beae0752e82d32 Author: Herbert Valerio Riedel Date: Thu Mar 20 09:20:06 2014 +0100 Convert haddock into a proper submodule (re #8545) This should help contribute content to https://ghc.haskell.org/trac/ghc/wiki/WorkingConventions/Git/Submodules Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 34b072177b687c8fcc24f87293beae0752e82d32 .gitignore | 1 - .gitmodules | 3 +++ packages | 2 +- utils/haddock | 1 + 4 files changed, 5 insertions(+), 2 deletions(-) diff --git a/.gitignore b/.gitignore index 93feea3..e60382b 100644 --- a/.gitignore +++ b/.gitignore @@ -71,7 +71,6 @@ _darcs/ /libraries/unix/ /libraries/utf8-string/ /nofib/ -/utils/haddock/ /utils/hsc2hs/ # ----------------------------------------------------------------------------- diff --git a/.gitmodules b/.gitmodules index d83bfd0..99893a4 100644 --- a/.gitmodules +++ b/.gitmodules @@ -54,3 +54,6 @@ path = libraries/random url = ../packages/random.git ignore = untracked +[submodule "utils/haddock"] + path = utils/haddock + url = ../haddock.git diff --git a/packages b/packages index 616dfc1..2683c99 100644 --- a/packages +++ b/packages @@ -47,7 +47,7 @@ ghc-tarballs windows ghc-tarballs.git - libffi-tarballs - libffi-tarballs.git - utils/hsc2hs - hsc2hs.git - -utils/haddock - haddock.git - +utils/haddock - - - libraries/array - packages/array.git - libraries/base - packages/base.git - libraries/binary - - https://github.com/kolmodin/binary.git diff --git a/utils/haddock b/utils/haddock new file mode 160000 index 0000000..725faca --- /dev/null +++ b/utils/haddock @@ -0,0 +1 @@ +Subproject commit 725faca5ee670f80359321adc112408880e9c073 From git at git.haskell.org Sun Mar 23 11:06:57 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Mar 2014 11:06:57 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Switch to relative URLs in .gitmodules (999fdb0) Message-ID: <20140323110657.85FDD2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/999fdb032be15bf415809ce82f9f5c908981d9d1/ghc >--------------------------------------------------------------- commit 999fdb032be15bf415809ce82f9f5c908981d9d1 Author: Herbert Valerio Riedel Date: Thu Feb 6 08:42:27 2014 +0100 Switch to relative URLs in .gitmodules Previously, the `http://`-protocol part was hardcoded in the URLs, causing the initial clone process to fall back to `http://` even when the ghc.git repo was cloned via one of the other 3 supported transport protocols. This is slightly related to #8545, as it will make it possible to e.g. git clone --recursive git://git.haskell.org/ghc and clone ghc.git including all submodules in one go (i.e. w/o `sync-all`), and w/o falling back to a different (hardwired) Git transport protocol for the submodules. Signed-off-by: Herbert Valerio Riedel (cherry picked from commit ad44e47542a822ac3e02cf514b5d2be52880fc95) >--------------------------------------------------------------- 999fdb032be15bf415809ce82f9f5c908981d9d1 .gitmodules | 28 ++++++++++++++-------------- 1 file changed, 14 insertions(+), 14 deletions(-) diff --git a/.gitmodules b/.gitmodules index f0fd280..d83bfd0 100644 --- a/.gitmodules +++ b/.gitmodules @@ -1,56 +1,56 @@ [submodule "libraries/binary"] path = libraries/binary - url = http://git.haskell.org/packages/binary.git + url = ../packages/binary.git ignore = untracked [submodule "libraries/bytestring"] path = libraries/bytestring - url = http://git.haskell.org/packages/bytestring.git + url = ../packages/bytestring.git ignore = untracked [submodule "libraries/Cabal"] path = libraries/Cabal - url = http://git.haskell.org/packages/Cabal.git + url = ../packages/Cabal.git ignore = untracked [submodule "libraries/containers"] path = libraries/containers - url = http://git.haskell.org/packages/containers.git + url = ../packages/containers.git ignore = untracked [submodule "libraries/haskeline"] path = libraries/haskeline - url = http://git.haskell.org/packages/haskeline.git + url = ../packages/haskeline.git ignore = untracked [submodule "libraries/pretty"] path = libraries/pretty - url = http://git.haskell.org/packages/pretty.git + url = ../packages/pretty.git ignore = untracked [submodule "libraries/terminfo"] path = libraries/terminfo - url = http://git.haskell.org/packages/terminfo.git + url = ../packages/terminfo.git ignore = untracked [submodule "libraries/transformers"] path = libraries/transformers - url = http://git.haskell.org/packages/transformers.git + url = ../packages/transformers.git ignore = untracked [submodule "libraries/xhtml"] path = libraries/xhtml - url = http://git.haskell.org/packages/xhtml.git + url = ../packages/xhtml.git ignore = untracked [submodule "libraries/Win32"] path = libraries/Win32 - url = http://git.haskell.org/packages/Win32.git + url = ../packages/Win32.git ignore = untracked [submodule "libraries/primitive"] path = libraries/primitive - url = http://git.haskell.org/packages/primitive.git + url = ../packages/primitive.git ignore = untracked [submodule "libraries/vector"] path = libraries/vector - url = http://git.haskell.org/packages/vector.git + url = ../packages/vector.git ignore = untracked [submodule "libraries/time"] path = libraries/time - url = http://git.haskell.org/packages/time.git + url = ../packages/time.git ignore = untracked [submodule "libraries/random"] path = libraries/random - url = http://git.haskell.org/packages/random.git + url = ../packages/random.git ignore = untracked From git at git.haskell.org Sun Mar 23 11:07:00 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Mar 2014 11:07:00 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Correctly clone submodules from github (b20e946) Message-ID: <20140323110700.115FF2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/b20e9462072ff1998fff5a8e81e176b6941a1769/ghc >--------------------------------------------------------------- commit b20e9462072ff1998fff5a8e81e176b6941a1769 Author: Joachim Breitner Date: Thu Feb 6 09:55:30 2014 +0000 Correctly clone submodules from github (cherry picked from commit b755c7bd6af9f2bee47427b1eaa6c29c72b2b17a) >--------------------------------------------------------------- b20e9462072ff1998fff5a8e81e176b6941a1769 sync-all | 48 ++++++++++++++++++++++++++++++++++-------------- 1 file changed, 34 insertions(+), 14 deletions(-) diff --git a/sync-all b/sync-all index f88ad2b..469dabe 100755 --- a/sync-all +++ b/sync-all @@ -123,7 +123,7 @@ sub git { }); } -sub readgit { +sub readgitline { my $dir = shift; my @args = @_; @@ -138,12 +138,26 @@ sub readgit { }); } +sub readgit { + my $dir = shift; + my @args = @_; + + &inDir($dir, sub { + open my $fh, '-|', 'git', @args + or die "Executing git @args failed: $!"; + my $ret; + $ret .= $_ while <$fh>; + close $fh; + return $ret; + }); +} + sub configure_repository { my $localpath = shift; &git($localpath, "config", "--local", "core.ignorecase", "true"); - my $autocrlf = &readgit($localpath, 'config', '--get', 'core.autocrlf'); + my $autocrlf = &readgitline($localpath, 'config', '--get', 'core.autocrlf'); if ($autocrlf eq "true") { &git($localpath, "config", "--local", "core.autocrlf", "false"); &git($localpath, "reset", "--hard"); @@ -161,17 +175,17 @@ sub getrepo { # Figure out where to get the other repositories from, # based on where this GHC repo came from. my $git_dir = $bare_flag ? "ghc.git" : "."; - my $branch = &readgit($git_dir, "rev-parse", "--abbrev-ref", "HEAD"); + my $branch = &readgitline($git_dir, "rev-parse", "--abbrev-ref", "HEAD"); die "Bad branch: $branch" unless $branch =~ m!^[a-zA-Z][a-zA-Z0-9./-]*$!; - my $remote = &readgit($git_dir, "config", "branch.$branch.remote"); + my $remote = &readgitline($git_dir, "config", "branch.$branch.remote"); if ($remote eq "") { # remotes are not mandatory for branches (e.g. not recorded by default for bare repos) $remote = "origin"; } die "Bad remote: $remote" unless $remote =~ m!^[a-zA-Z][a-zA-Z0-9./-]*$!; - $repo = &readgit($git_dir, "config", "remote.$remote.url"); + $repo = &readgitline($git_dir, "config", "remote.$remote.url"); } my $repo_base; @@ -402,7 +416,7 @@ sub gitall { } close($lsremote); - my $myhead = &readgit('.', 'rev-parse', '--verify', 'HEAD'); + my $myhead = &readgitline('.', 'rev-parse', '--verify', 'HEAD'); if (not defined($remote_heads{$myhead})) { die "Sub module $localpath needs to be pushed; see http://ghc.haskell.org/trac/ghc/wiki/Repositories/Upstream"; @@ -539,11 +553,11 @@ sub gitall { } print "$localpath"; print (' ' x (40 - length($localpath))); - my $branch = &readgit($localpath, "rev-parse", "--abbrev-ref", "HEAD"); + my $branch = &readgitline($localpath, "rev-parse", "--abbrev-ref", "HEAD"); die "Bad branch: $branch" unless $branch =~ m!^[a-zA-Z][a-zA-Z0-9./-]*$!; - my $us = &readgit(".", "ls-remote", $localpath, "refs/heads/$branch"); - my $them = &readgit(".", "ls-remote", $compareto, "refs/heads/$branch"); + my $us = &readgitline(".", "ls-remote", $localpath, "refs/heads/$branch"); + my $them = &readgitline(".", "ls-remote", $compareto, "refs/heads/$branch"); $us =~ s/[[:space:]].*//; $them =~ s/[[:space:]].*//; die "Bad commit of mine: $us" unless (length($us) eq 40); @@ -567,13 +581,19 @@ sub gitInitSubmodules { &git(".", "submodule", "init", @_); my ($repo_base, $checked_out_tree, $repo_local) = getrepo(); + + my $submodulespaths = &readgit(".", "config", "--get-regexp", "^submodule[.].*[.]url"); + # if we came from github, change the urls appropriately + while ($submodulespaths =~ m!^(submodule.libraries/[a-zA-Z0-9]+.url) git://github.com/ghc/packages/([a-zA-Z0-9]+).git$!gm) { + &git(".", "config", $1, "git://github.com/ghc/packages-$2"); + } + # if we came from a local repository, grab our submodules from their # checkouts over there, if they exist. if ($repo_local) { - my $gitConfig = &tryReadFile(".git/config"); - foreach $_ (split /^/, $gitConfig) { - if ($_ =~ /^\[submodule "(.*)"\]$/ and -e "$repo_base/$1/.git") { - &git(".", "config", "submodule.$1.url", "$repo_base/$1"); + while ($submodulespaths =~ m!^(submodule.(libraries/[a-zA-Z0-9]+).url) .*$!gm) { + if (-e "$repo_base/$2/.git") { + &git(".", "config", $1, "$repo_base/$2"); } } } @@ -1043,7 +1063,7 @@ EOF } message "== Checking for obsolete Git repo URL"; - my $repo_url = &readgit(".", 'config', '--get', 'remote.origin.url'); + my $repo_url = &readgitline(".", 'config', '--get', 'remote.origin.url'); if ($repo_url =~ /^http:\/\/darcs.haskell.org/) { print < Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/cf54407b36fd98c3688e39c9ad8a1973f9f93550/ghc >--------------------------------------------------------------- commit cf54407b36fd98c3688e39c9ad8a1973f9f93550 Author: Joachim Breitner Date: Fri Mar 7 16:50:43 2014 +0100 Make sync-all handle all github protocols correctly This fixes #8824. (cherry picked from commit 3efcb0a7d147e05f86501783144bcd0ad3757e93) >--------------------------------------------------------------- cf54407b36fd98c3688e39c9ad8a1973f9f93550 sync-all | 8 +++++--- 1 file changed, 5 insertions(+), 3 deletions(-) diff --git a/sync-all b/sync-all index 469dabe..a585e9a 100755 --- a/sync-all +++ b/sync-all @@ -19,6 +19,8 @@ my $bare_flag = ""; # NOT the opposite of checked_out_flag (describes local repo my %tags; +my $GITHUB = qr!(?:git@|git://|https://)github.com!; + sub inDir { my $dir = shift; my $code = shift; @@ -262,7 +264,7 @@ sub gitall { my ($repo_base, $checked_out_tree, $repo_local) = getrepo(); - my $is_github_repo = $repo_base =~ m/(git@|git:\/\/|https:\/\/)github.com/; + my $is_github_repo = $repo_base =~ $GITHUB; @args = (); @@ -584,8 +586,8 @@ sub gitInitSubmodules { my $submodulespaths = &readgit(".", "config", "--get-regexp", "^submodule[.].*[.]url"); # if we came from github, change the urls appropriately - while ($submodulespaths =~ m!^(submodule.libraries/[a-zA-Z0-9]+.url) git://github.com/ghc/packages/([a-zA-Z0-9]+).git$!gm) { - &git(".", "config", $1, "git://github.com/ghc/packages-$2"); + while ($submodulespaths =~ m!^(submodule.libraries/[a-zA-Z0-9]+.url) ($GITHUB)/ghc/packages/([a-zA-Z0-9]+).git$!gm) { + &git(".", "config", $1, "$2/ghc/packages-$3"); } # if we came from a local repository, grab our submodules from their From git at git.haskell.org Sun Mar 23 11:07:04 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Mar 2014 11:07:04 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Also allow http://github.com (#8824) (282f361) Message-ID: <20140323110705.114D12406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/282f3619e15a25ef7693cdd7d01b7550a1fa220f/ghc >--------------------------------------------------------------- commit 282f3619e15a25ef7693cdd7d01b7550a1fa220f Author: Joachim Breitner Date: Sat Mar 8 01:11:42 2014 +0100 Also allow http://github.com (#8824) (cherry picked from commit d246c62afd7312185aee9433b065ea99e4fa4054) >--------------------------------------------------------------- 282f3619e15a25ef7693cdd7d01b7550a1fa220f sync-all | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/sync-all b/sync-all index a585e9a..4b4b7a3 100755 --- a/sync-all +++ b/sync-all @@ -19,7 +19,7 @@ my $bare_flag = ""; # NOT the opposite of checked_out_flag (describes local repo my %tags; -my $GITHUB = qr!(?:git@|git://|https://)github.com!; +my $GITHUB = qr!(?:git@|git://|https://|http://)github.com!; sub inDir { my $dir = shift; From git at git.haskell.org Sun Mar 23 11:09:09 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Mar 2014 11:09:09 +0000 (UTC) Subject: [commit: ghc] wip/T8545-ghc-7.8: Convert all sub-repos into proper submodules (re #8545) (25c5f2e) Message-ID: <20140323110909.C78B62406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8545-ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/25c5f2e833e3695b0730260e7682da034ba18db2/ghc >--------------------------------------------------------------- commit 25c5f2e833e3695b0730260e7682da034ba18db2 Author: Herbert Valerio Riedel Date: Sat Mar 22 15:26:34 2014 +0100 Convert all sub-repos into proper submodules (re #8545) ...except for ghc-tarballs which is a waste of bandwidth Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 25c5f2e833e3695b0730260e7682da034ba18db2 .gitignore | 27 ----------------- .gitmodules | 72 ++++++++++++++++++++++++++++++++++++++++++++ libffi-tarballs | 1 + libraries/array | 1 + libraries/base | 1 + libraries/deepseq | 1 + libraries/directory | 1 + libraries/dph | 1 + libraries/filepath | 1 + libraries/ghc-prim | 1 + libraries/haskell2010 | 1 + libraries/haskell98 | 1 + libraries/hoopl | 1 + libraries/hpc | 1 + libraries/integer-gmp | 1 + libraries/integer-simple | 1 + libraries/old-locale | 1 + libraries/old-time | 1 + libraries/parallel | 1 + libraries/process | 1 + libraries/stm | 1 + libraries/template-haskell | 1 + libraries/unix | 1 + nofib | 1 + packages | 48 ++++++++++++++--------------- utils/haddock | 1 + utils/hsc2hs | 1 + 27 files changed, 120 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 25c5f2e833e3695b0730260e7682da034ba18db2 From git at git.haskell.org Sun Mar 23 11:09:11 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Mar 2014 11:09:11 +0000 (UTC) Subject: [commit: ghc] wip/T8545-ghc-7.8's head updated: Convert all sub-repos into proper submodules (re #8545) (25c5f2e) Message-ID: <20140323110913.A03232406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T8545-ghc-7.8' now includes: 999fdb0 Switch to relative URLs in .gitmodules b20e946 Correctly clone submodules from github cf54407 Make sync-all handle all github protocols correctly 282f361 Also allow http://github.com (#8824) 25c5f2e Convert all sub-repos into proper submodules (re #8545) From git at git.haskell.org Sun Mar 23 12:40:05 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Mar 2014 12:40:05 +0000 (UTC) Subject: [commit: ghc] master: ghc-cabal: force use of UTF8 when writing out `haddock-prologue.txt` (8f26728) Message-ID: <20140323124005.969522406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8f26728a44be395a41d9dd9cb933e8006f5a6dc4/ghc >--------------------------------------------------------------- commit 8f26728a44be395a41d9dd9cb933e8006f5a6dc4 Author: Herbert Valerio Riedel Date: Sun Mar 23 13:33:03 2014 +0100 ghc-cabal: force use of UTF8 when writing out `haddock-prologue.txt` This unbreaks the GHC build if a non-UTF8 locale such as LANG=C is active See also haskell/cabal#1721 and haskell/haddock#286 Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 8f26728a44be395a41d9dd9cb933e8006f5a6dc4 utils/ghc-cabal/Main.hs | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/utils/ghc-cabal/Main.hs b/utils/ghc-cabal/Main.hs index 8fa2c29..a7d9e60 100644 --- a/utils/ghc-cabal/Main.hs +++ b/utils/ghc-cabal/Main.hs @@ -452,7 +452,8 @@ generate directory distdir dll0Modules config_args "$(eval $(" ++ directory ++ "_PACKAGE_MAGIC))" ] writeFile (distdir ++ "/package-data.mk") $ unlines xs - writeFile (distdir ++ "/haddock-prologue.txt") $ + + writeFileUtf8 (distdir ++ "/haddock-prologue.txt") $ if null (description pd) then synopsis pd else description pd unless (null dll0Modules) $ @@ -475,3 +476,8 @@ generate directory distdir dll0Modules config_args mkSearchPath = intercalate [searchPathSeparator] boolToYesNo True = "YES" boolToYesNo False = "NO" + + -- | Version of 'writeFile' that always uses UTF8 encoding + writeFileUtf8 f txt = withFile f WriteMode $ \hdl -> do + hSetEncoding hdl utf8 + hPutStr hdl txt From git at git.haskell.org Sun Mar 23 17:09:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Mar 2014 17:09:43 +0000 (UTC) Subject: [commit: haddock] master: Fix a few typos (f3c7cd3) Message-ID: <20140323170943.9661C2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : master Link : http://git.haskell.org/haddock.git/commitdiff/f3c7cd34d066cd40cb4983893165de038974fd95 >--------------------------------------------------------------- commit f3c7cd34d066cd40cb4983893165de038974fd95 Author: Herbert Valerio Riedel Date: Sun Mar 23 18:01:01 2014 +0100 Fix a few typos Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- f3c7cd34d066cd40cb4983893165de038974fd95 CHANGES | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/CHANGES b/CHANGES index c59051a..be2de82 100644 --- a/CHANGES +++ b/CHANGES @@ -100,7 +100,7 @@ Changes in version 2.11.0 * Improved --qual option (no crashes, proper error messages) - * A new --qual option "aliased" which qualifies identifers by the module alias + * A new --qual option "aliased" which qualifies identifiers by the module alias used in the source code * The Haddock API restores GHC's static flags after invocation @@ -279,7 +279,7 @@ Changed in version 2.5.0: * Add --use-unicode flag for displaying prettier versions of common symbols - * Mutiple verbosity levels: remove --verbose and add --verbosity=n + * Multiple verbosity levels: remove --verbose and add --verbosity=n ----------------------------------------------------------------------------- @@ -308,7 +308,7 @@ Changed in version 2.4.2: * Do not indicate that a constructor argument is unboxed - * Fix problem with with non-working links to ghc-prim + * Fix problem with non-working links to ghc-prim * Allow referring to a specific section within a module in a module link (#65) @@ -404,7 +404,7 @@ Changes in version 2.0.0.0: * Haddock can generate documentation for some of the language extensions in GHC 6.8.2 - * Format of module attributes has changed. The only way of specifiying + * Format of module attributes has changed. The only way of specifying module attributes is via a new OPTIONS_HADDOCK pragma. Example: {-# OPTIONS_HADDOCK hide, prune #-} From git at git.haskell.org Sun Mar 23 18:49:41 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Mar 2014 18:49:41 +0000 (UTC) Subject: [commit: ghc] master: Apply the kind subst to the (kinds of the) quanitifed tyvars in deriveTyData (ffed708) Message-ID: <20140323184941.1C52A2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ffed708c30f2d1d4b4c5cd08d9c19aeb0bb623ec/ghc >--------------------------------------------------------------- commit ffed708c30f2d1d4b4c5cd08d9c19aeb0bb623ec Author: Simon Peyton Jones Date: Sat Mar 22 23:11:10 2014 +0000 Apply the kind subst to the (kinds of the) quanitifed tyvars in deriveTyData I've elaboated Note [Unify kinds in deriving] to explain what is going on here. The change fixes Trac #8893. >--------------------------------------------------------------- ffed708c30f2d1d4b4c5cd08d9c19aeb0bb623ec compiler/typecheck/TcDeriv.lhs | 56 ++++++++++++++++++++++++++++++---------- 1 file changed, 43 insertions(+), 13 deletions(-) diff --git a/compiler/typecheck/TcDeriv.lhs b/compiler/typecheck/TcDeriv.lhs index a89adda..4cec134 100644 --- a/compiler/typecheck/TcDeriv.lhs +++ b/compiler/typecheck/TcDeriv.lhs @@ -685,13 +685,19 @@ deriveTyData tvs tc tc_args (L loc deriv_pred) tc_args_to_keep = take n_args_to_keep tc_args inst_ty_kind = typeKind (mkTyConApp tc tc_args_to_keep) dropped_tvs = tyVarsOfTypes args_to_drop - mb_match = tcUnifyTy inst_ty_kind cls_arg_kind - Just subst = mb_match -- See Note [Unify kinds in deriving] - -- We are assuming the tycon tyvars and the class tyvars are distinct - final_tc_args = substTys subst tc_args_to_keep - final_cls_tys = substTys subst cls_tys - univ_tvs = mkVarSet deriv_tvs `unionVarSet` tyVarsOfTypes final_tc_args + -- Match up the kinds, and apply the resulting kind substitution + -- to the types. See Note [Unify kinds in deriving] + -- We are assuming the tycon tyvars and the class tyvars are distinct + mb_match = tcUnifyTy inst_ty_kind cls_arg_kind + Just kind_subst = mb_match + (univ_kvs, univ_tvs) = partition isKindVar $ varSetElems $ + mkVarSet deriv_tvs `unionVarSet` + tyVarsOfTypes tc_args_to_keep + univ_kvs' = filter (`notElemTvSubst` kind_subst) univ_kvs + (subst', univ_tvs') = mapAccumL substTyVarBndr kind_subst univ_tvs + final_tc_args = substTys subst' tc_args_to_keep + final_cls_tys = substTys subst' cls_tys ; traceTc "derivTyData1" (vcat [ pprTvBndrs tvs, ppr tc, ppr tc_args, ppr deriv_pred , pprTvBndrs (varSetElems $ tyVarsOfTypes tc_args) @@ -705,9 +711,9 @@ deriveTyData tvs tc tc_args (L loc deriv_pred) ; traceTc "derivTyData2" (vcat [ ppr univ_tvs ]) - ; checkTc (allDistinctTyVars args_to_drop && -- (a) and (b) - univ_tvs `disjointVarSet` dropped_tvs) -- (c) - (derivingEtaErr cls cls_tys (mkTyConApp tc final_tc_args)) + ; checkTc (allDistinctTyVars args_to_drop && -- (a) and (b) + not (any (`elemVarSet` dropped_tvs) univ_tvs)) -- (c) + (derivingEtaErr cls final_cls_tys (mkTyConApp tc final_tc_args)) -- Check that -- (a) The args to drop are all type variables; eg reject: -- data instance T a Int = .... deriving( Monad ) @@ -719,7 +725,7 @@ deriveTyData tvs tc tc_args (L loc deriv_pred) -- newtype T a s = ... deriving( ST s ) -- newtype K a a = ... deriving( Monad ) - ; mkEqnHelp (varSetElemsKvsFirst univ_tvs) + ; mkEqnHelp (univ_kvs' ++ univ_tvs') cls final_cls_tys tc final_tc_args Nothing } } derivePolyKindedTypeable :: Class -> [Type] @@ -775,10 +781,34 @@ So we need to kind arguments. In the two examples, - * we unify ( T k (a:k) ) ~ (* -> *) to find k:=*. - * we unify ( Either ~ (k -> k -> k) ) to find k:=*. + * we unify kind-of( T k (a:k) ) ~ kind-of( Functor ) + i.e. (k -> *) ~ (* -> *) to find k:=*. + yielding k:=* + + * we unify kind-of( Either ) ~ kind-of( Category ) + i.e. (* -> * -> *) ~ (k -> k -> k) + yielding k:=* + +Now we get a kind substition. We then need to: + + 1. Remove the substituted-out kind variables from the quantifed kind vars + + 2. Apply the substitution to the kinds of quantified *type* vars + (and extend the substitution to reflect this change) + + 3. Apply that extended substitution to the non-dropped args (types and + kinds) of the type and class + +Forgetting step (2) caused Trac #8893: + data V a = V [a] deriving Functor + data P (x::k->*) (a:k) = P (x a) deriving Functor + data C (x::k->*) (a:k) = C (V (P x a)) deriving Functor + +When deriving Functor for P, we unify k to *, but we then want +an instance $df :: forall (x:*->*). Functor x => Functor (P * (x:*->*)) +and similarly for C. Notice the modifed kind of x, both at binding +and occurrence sites. -Tricky stuff. \begin{code} mkEqnHelp :: [TyVar] From git at git.haskell.org Sun Mar 23 18:49:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Mar 2014 18:49:43 +0000 (UTC) Subject: [commit: ghc] master: Simplify handling of the interactive package; fixes Trac #8831 (28e8d87) Message-ID: <20140323184943.EFE6E2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/28e8d878b63d06824001ac3a631254679e0f1960/ghc >--------------------------------------------------------------- commit 28e8d878b63d06824001ac3a631254679e0f1960 Author: Simon Peyton Jones Date: Sat Mar 22 23:18:14 2014 +0000 Simplify handling of the interactive package; fixes Trac #8831 This patch is really a fix to the big commint 73c08ab10e4077e18e459a1325996bff110360c3 Re-work the naming story for the GHCi prompt (Trac #8649) which introduced the 'interactive' package See Note [The interactive package] in HscTypes The original commit set both (a) The tcg_mod field of TcGblEnv to 'interactive:Ghci4' (say) (b) The thisPackage field of DynFlags to 'interactive' But the second step interacts badly with linking. :loaded modules are in the package set by 'thisPackage' (usually 'main'); if you change that, then we try to link package 'main', but can't find it, and that is what happened in #8831. The fix was simple: do (a) but not (b). I changed Note [The interactive package] in HscTypes to describe this. >--------------------------------------------------------------- 28e8d878b63d06824001ac3a631254679e0f1960 compiler/main/HscMain.hs | 11 ++--------- compiler/main/HscTypes.lhs | 11 +++++++---- 2 files changed, 9 insertions(+), 13 deletions(-) diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs index 04b0823..748f748 100644 --- a/compiler/main/HscMain.hs +++ b/compiler/main/HscMain.hs @@ -1357,11 +1357,7 @@ hscStmtWithLocation hsc_env0 stmt source linenumber = Just parsed_stmt -> do -- Rename and typecheck it hsc_env <- getHscEnv - let interactive_hsc_env = setInteractivePackage hsc_env - -- Bindings created here belong to the interactive package - -- See Note [The interactive package] in HscTypes - -- (NB: maybe not necessary, since Stmts bind only Ids) - (ids, tc_expr, fix_env) <- ioMsgMaybe $ tcRnStmt interactive_hsc_env parsed_stmt + (ids, tc_expr, fix_env) <- ioMsgMaybe $ tcRnStmt hsc_env parsed_stmt -- Desugar it ds_expr <- ioMsgMaybe $ deSugarExpr hsc_env tc_expr @@ -1397,10 +1393,7 @@ hscDeclsWithLocation hsc_env0 str source linenumber = {- Rename and typecheck it -} hsc_env <- getHscEnv - let interactive_hsc_env = setInteractivePackage hsc_env - -- Bindings created here belong to the interactive package - -- See Note [The interactive package] in HscTypes - tc_gblenv <- ioMsgMaybe $ tcRnDeclsi interactive_hsc_env decls + tc_gblenv <- ioMsgMaybe $ tcRnDeclsi hsc_env decls {- Grab the new instances -} -- We grab the whole environment because of the overlapping that may have diff --git a/compiler/main/HscTypes.lhs b/compiler/main/HscTypes.lhs index c4c5efd..6fcf8e2 100644 --- a/compiler/main/HscTypes.lhs +++ b/compiler/main/HscTypes.lhs @@ -1140,10 +1140,13 @@ The details are a bit tricky though: package to which :load'ed modules are added to. * So how do we arrange that declarations at the command prompt get - to be in the 'interactive' package? By setting 'thisPackage' just - before the typecheck/rename step for command-line processing; - see the calls to HscTypes.setInteractivePackage in - HscMain.hscDeclsWithLocation and hscStmtWithLocation. + to be in the 'interactive' package? Simply by setting the tcg_mod + field of the TcGblEnv to "interactive:Ghci1". This is done by the + call to initTc in initTcInteractive, initTcForLookup, which in + turn get the module from it 'icInteractiveModule' field of the + interactive context. + + The 'thisPackage' field stays as 'main' (or whatever -package-name says. * The main trickiness is that the type environment (tcg_type_env and fixity envt (tcg_fix_env) now contains entities from all the From git at git.haskell.org Sun Mar 23 18:49:45 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Mar 2014 18:49:45 +0000 (UTC) Subject: [commit: ghc] master: Trac #8831 is fixed (1a7709e) Message-ID: <20140323184945.EBAE42406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1a7709ef9b25175566bc040a34b3d479ea8566ed/ghc >--------------------------------------------------------------- commit 1a7709ef9b25175566bc040a34b3d479ea8566ed Author: Simon Peyton Jones Date: Sun Mar 23 18:46:22 2014 +0000 Trac #8831 is fixed >--------------------------------------------------------------- 1a7709ef9b25175566bc040a34b3d479ea8566ed testsuite/tests/ghci/scripts/all.T | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T index d41d985..6c6923d 100755 --- a/testsuite/tests/ghci/scripts/all.T +++ b/testsuite/tests/ghci/scripts/all.T @@ -168,5 +168,5 @@ test('T8674', normal, ghci_script, ['T8674.script']) test('T8696', normal, ghci_script, ['T8696.script']) test('T8776', normal, ghci_script, ['T8776.script']) test('ghci059', normal, ghci_script, ['ghci059.script']) -test('T8831', expect_broken(8831), ghci_script, ['T8831.script']) +test('T8831', normal, ghci_script, ['T8831.script']) test('T8917', normal, ghci_script, ['T8917.script']) From git at git.haskell.org Sun Mar 23 18:49:48 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Mar 2014 18:49:48 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #8893 (7973bfb) Message-ID: <20140323184949.2BCC92406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7973bfb87fdbe6e980e64ed5d7b2a90a469effd4/ghc >--------------------------------------------------------------- commit 7973bfb87fdbe6e980e64ed5d7b2a90a469effd4 Author: Simon Peyton Jones Date: Sun Mar 23 18:44:43 2014 +0000 Test Trac #8893 >--------------------------------------------------------------- 7973bfb87fdbe6e980e64ed5d7b2a90a469effd4 testsuite/tests/deriving/should_compile/T8893.hs | 11 +++++++++++ testsuite/tests/deriving/should_compile/all.T | 1 + 2 files changed, 12 insertions(+) diff --git a/testsuite/tests/deriving/should_compile/T8893.hs b/testsuite/tests/deriving/should_compile/T8893.hs new file mode 100644 index 0000000..2ebcc94 --- /dev/null +++ b/testsuite/tests/deriving/should_compile/T8893.hs @@ -0,0 +1,11 @@ +{-# OPTIONS_GHC -Wall #-} +{-# Language DeriveFunctor #-} +{-# Language PolyKinds #-} + +module T8893 where + +data V a = V [a] deriving Functor + +data C x a = C (V (P x a)) deriving Functor + +data P x a = P (x a) deriving Functor diff --git a/testsuite/tests/deriving/should_compile/all.T b/testsuite/tests/deriving/should_compile/all.T index cc4115c..a0e70eb 100644 --- a/testsuite/tests/deriving/should_compile/all.T +++ b/testsuite/tests/deriving/should_compile/all.T @@ -46,3 +46,4 @@ test('T8631', normal, compile, ['']) test('T8758', extra_clean(['T8758a.o', 'T8758a.hi']), multimod_compile, ['T8758a', '-v0']) test('T8678', normal, compile, ['']) test('T8865', normal, compile, ['']) +test('T8893', normal, compile, ['']) From git at git.haskell.org Sun Mar 23 19:27:23 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Mar 2014 19:27:23 +0000 (UTC) Subject: [commit: packages/hpc] master: Fix some typos (d6ac0c5) Message-ID: <20140323192723.474B02406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hpc On branch : master Link : http://git.haskell.org/packages/hpc.git/commitdiff/d6ac0c532f12d30af778eeb285da9031bb06fddb >--------------------------------------------------------------- commit d6ac0c532f12d30af778eeb285da9031bb06fddb Author: Gabor Greif Date: Sun Mar 23 20:19:52 2014 +0100 Fix some typos >--------------------------------------------------------------- d6ac0c532f12d30af778eeb285da9031bb06fddb Trace/Hpc/Mix.hs | 2 +- Trace/Hpc/Tix.hs | 2 +- Trace/Hpc/Util.hs | 4 ++-- 3 files changed, 4 insertions(+), 4 deletions(-) diff --git a/Trace/Hpc/Mix.hs b/Trace/Hpc/Mix.hs index e5396b2..5be919d 100644 --- a/Trace/Hpc/Mix.hs +++ b/Trace/Hpc/Mix.hs @@ -35,7 +35,7 @@ import Trace.Hpc.Tix -- | 'Mix' is the information about a modules static properties, like -- location of Tix's in a file. -- --- Tab stops are the size of a tab in the provided /line:colunm/ values. +-- Tab stops are the size of a tab in the provided /line:column/ values. -- -- * In GHC, this is 1 (a tab is just a character) -- * With @hpc-tracer@, this is 8 (a tab represents several spaces). diff --git a/Trace/Hpc/Tix.hs b/Trace/Hpc/Tix.hs index 512c6c5..2b03e0a 100644 --- a/Trace/Hpc/Tix.hs +++ b/Trace/Hpc/Tix.hs @@ -15,7 +15,7 @@ module Trace.Hpc.Tix(Tix(..), TixModule(..), import Data.List (isSuffixOf) import Trace.Hpc.Util (Hash, catchIO) --- | 'Tix' is the storage format for our dynamic imformation about +-- | 'Tix' is the storage format for our dynamic information about -- what boxes are ticked. data Tix = Tix [TixModule] deriving (Read, Show, Eq) diff --git a/Trace/Hpc/Util.hs b/Trace/Hpc/Util.hs index 6846b2f..7aa1fba 100644 --- a/Trace/Hpc/Util.hs +++ b/Trace/Hpc/Util.hs @@ -27,11 +27,11 @@ import Data.Word -- | 'HpcPos' is an Hpc local rendition of a Span. data HpcPos = P !Int !Int !Int !Int deriving (Eq, Ord) --- | 'fromHpcPos' explodes the HpcPos into /line:column/-/line:colunm/ +-- | 'fromHpcPos' explodes the HpcPos into /line:column/-/line:column/ fromHpcPos :: HpcPos -> (Int,Int,Int,Int) fromHpcPos (P l1 c1 l2 c2) = (l1,c1,l2,c2) --- | 'toHpcPos' implodes to HpcPos, from /line:column/-/line:colunm/ +-- | 'toHpcPos' implodes to HpcPos, from /line:column/-/line:column/ toHpcPos :: (Int,Int,Int,Int) -> HpcPos toHpcPos (l1,c1,l2,c2) = P l1 c1 l2 c2 From git at git.haskell.org Sun Mar 23 19:36:07 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Mar 2014 19:36:07 +0000 (UTC) Subject: [commit: packages/haskell2010] master: Fix typo (c0c87ad) Message-ID: <20140323193607.885002406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskell2010 On branch : master Link : http://git.haskell.org/packages/haskell2010.git/commitdiff/c0c87ad53e377aa00f4897bc729c261459b6048a >--------------------------------------------------------------- commit c0c87ad53e377aa00f4897bc729c261459b6048a Author: Gabor Greif Date: Sun Mar 23 20:35:04 2014 +0100 Fix typo >--------------------------------------------------------------- c0c87ad53e377aa00f4897bc729c261459b6048a changelog.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/changelog.md b/changelog.md index 87acfc5..87d0012 100644 --- a/changelog.md +++ b/changelog.md @@ -8,6 +8,6 @@ - Remove NHC98-specific code - - Adapt to changes in GHC 7.8's core-libaries + - Adapt to changes in GHC 7.8's core-libraries - Update to Cabal format 1.10 From git at git.haskell.org Sun Mar 23 19:39:04 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Mar 2014 19:39:04 +0000 (UTC) Subject: [commit: packages/haskell98] master: Fix typo (cc6bbbf) Message-ID: <20140323193904.7A3E72406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskell98 On branch : master Link : http://git.haskell.org/packages/haskell98.git/commitdiff/cc6bbbf2bf4eaea57062043cbb6e7c5d6c2f42a9 >--------------------------------------------------------------- commit cc6bbbf2bf4eaea57062043cbb6e7c5d6c2f42a9 Author: Gabor Greif Date: Sun Mar 23 20:36:37 2014 +0100 Fix typo >--------------------------------------------------------------- cc6bbbf2bf4eaea57062043cbb6e7c5d6c2f42a9 changelog.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/changelog.md b/changelog.md index d3a71ec..4509de5 100644 --- a/changelog.md +++ b/changelog.md @@ -6,6 +6,6 @@ - Remove NHC98-specific code - - Adapt to changes in GHC 7.8's core-libaries + - Adapt to changes in GHC 7.8's core-libraries - Update to Cabal format 1.10 From git at git.haskell.org Sun Mar 23 19:42:02 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Mar 2014 19:42:02 +0000 (UTC) Subject: [commit: ghc] master: Fix typo (90142be) Message-ID: <20140323194202.D02862406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/90142beab88127892e384c8275ac5757a7d467e7/ghc >--------------------------------------------------------------- commit 90142beab88127892e384c8275ac5757a7d467e7 Author: Gabor Greif Date: Sun Mar 23 20:33:48 2014 +0100 Fix typo >--------------------------------------------------------------- 90142beab88127892e384c8275ac5757a7d467e7 distrib/compare/FilenameDescr.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/distrib/compare/FilenameDescr.hs b/distrib/compare/FilenameDescr.hs index a0f53fd..bf2a50e 100644 --- a/distrib/compare/FilenameDescr.hs +++ b/distrib/compare/FilenameDescr.hs @@ -10,7 +10,7 @@ import Utils import Tar -- We can't just compare plain filenames, because versions numbers of GHC --- and the libaries will vary. So we use FilenameDescr instead, which +-- and the libraries will vary. So we use FilenameDescr instead, which -- abstracts out the version numbers. type FilenameDescr = [FilenameDescrBit] data FilenameDescrBit = VersionOf String From git at git.haskell.org Sun Mar 23 20:09:26 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Mar 2014 20:09:26 +0000 (UTC) Subject: [commit: ghc] master: Catch a bunch of typos in comments (4b4fc7d) Message-ID: <20140323200926.780F82406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4b4fc7d968e5acebb2e5da5f978a3b44c6b27e87/ghc >--------------------------------------------------------------- commit 4b4fc7d968e5acebb2e5da5f978a3b44c6b27e87 Author: Gabor Greif Date: Sun Mar 23 21:05:10 2014 +0100 Catch a bunch of typos in comments >--------------------------------------------------------------- 4b4fc7d968e5acebb2e5da5f978a3b44c6b27e87 compiler/coreSyn/CoreSubst.lhs | 12 ++++++------ compiler/typecheck/TcDeriv.lhs | 6 +++--- compiler/typecheck/TcTyClsDecls.lhs | 2 +- compiler/types/TypeRep.lhs | 8 ++++---- 4 files changed, 14 insertions(+), 14 deletions(-) diff --git a/compiler/coreSyn/CoreSubst.lhs b/compiler/coreSyn/CoreSubst.lhs index 95dccc2..ff24e2e 100644 --- a/compiler/coreSyn/CoreSubst.lhs +++ b/compiler/coreSyn/CoreSubst.lhs @@ -355,7 +355,7 @@ instance Outputable Subst where %************************************************************************ \begin{code} --- | Apply a substititon to an entire 'CoreExpr'. Rememeber, you may only +-- | Apply a substitution to an entire 'CoreExpr'. Remember, you may only -- apply the substitution /once/: see "CoreSubst#apply_once" -- -- Do *not* attempt to short-cut in the case of an empty substitution! @@ -402,8 +402,8 @@ subst_expr subst expr where (subst', bndrs') = substBndrs subst bndrs --- | Apply a substititon to an entire 'CoreBind', additionally returning an updated 'Subst' --- that should be used by subsequent substitutons. +-- | Apply a substitution to an entire 'CoreBind', additionally returning an updated 'Subst' +-- that should be used by subsequent substitutions. substBind, substBindSC :: Subst -> CoreBind -> (Subst, CoreBind) substBindSC subst bind -- Short-cut if the substitution is empty @@ -460,7 +460,7 @@ preserve occ info in rules. \begin{code} -- | Substitutes a 'Var' for another one according to the 'Subst' given, returning --- the result and an updated 'Subst' that should be used by subsequent substitutons. +-- the result and an updated 'Subst' that should be used by subsequent substitutions. -- 'IdInfo' is preserved by this process, although it is substituted into appropriately. substBndr :: Subst -> Var -> (Subst, Var) substBndr subst bndr @@ -484,7 +484,7 @@ substRecBndrs subst bndrs \begin{code} substIdBndr :: SDoc -> Subst -- ^ Substitution to use for the IdInfo - -> Subst -> Id -- ^ Substitition and Id to transform + -> Subst -> Id -- ^ Substitution and Id to transform -> (Subst, Id) -- ^ Transformed pair -- NB: unfolding may be zapped @@ -555,7 +555,7 @@ cloneRecIdBndrs subst us ids -- Just like substIdBndr, except that it always makes a new unique -- It is given the unique to use clone_id :: Subst -- Substitution for the IdInfo - -> Subst -> (Id, Unique) -- Substitition and Id to transform + -> Subst -> (Id, Unique) -- Substitution and Id to transform -> (Subst, Id) -- Transformed pair clone_id rec_subst subst@(Subst in_scope idvs tvs cvs) (old_id, uniq) diff --git a/compiler/typecheck/TcDeriv.lhs b/compiler/typecheck/TcDeriv.lhs index 4cec134..9cd2cf1 100644 --- a/compiler/typecheck/TcDeriv.lhs +++ b/compiler/typecheck/TcDeriv.lhs @@ -789,9 +789,9 @@ In the two examples, i.e. (* -> * -> *) ~ (k -> k -> k) yielding k:=* -Now we get a kind substition. We then need to: +Now we get a kind substitution. We then need to: - 1. Remove the substituted-out kind variables from the quantifed kind vars + 1. Remove the substituted-out kind variables from the quantified kind vars 2. Apply the substitution to the kinds of quantified *type* vars (and extend the substitution to reflect this change) @@ -806,7 +806,7 @@ Forgetting step (2) caused Trac #8893: When deriving Functor for P, we unify k to *, but we then want an instance $df :: forall (x:*->*). Functor x => Functor (P * (x:*->*)) -and similarly for C. Notice the modifed kind of x, both at binding +and similarly for C. Notice the modified kind of x, both at binding and occurrence sites. diff --git a/compiler/typecheck/TcTyClsDecls.lhs b/compiler/typecheck/TcTyClsDecls.lhs index 05dc029..d0f7814 100644 --- a/compiler/typecheck/TcTyClsDecls.lhs +++ b/compiler/typecheck/TcTyClsDecls.lhs @@ -1155,7 +1155,7 @@ tcConDecl new_or_data rep_tycon tmpl_tvs res_tmpl -- Data types (arg_tys, stricts) = unzip btys ; return (ctxt, arg_tys, res_ty, is_infix, field_lbls, stricts) } - -- Generalise the kind variables (returning quantifed TcKindVars) + -- Generalise the kind variables (returning quantified TcKindVars) -- and quantify the type variables (substituting their kinds) -- REMEMBER: 'tkvs' are: -- ResTyH98: the *existential* type variables only diff --git a/compiler/types/TypeRep.lhs b/compiler/types/TypeRep.lhs index 906989a..bea67b4 100644 --- a/compiler/types/TypeRep.lhs +++ b/compiler/types/TypeRep.lhs @@ -415,7 +415,7 @@ instance NamedThing TyThing where -- Can't put this with the type -- 2. In particular, the /kind/ of the type variables in -- the in-scope set is not relevant -- --- 3. The substition is only applied ONCE! This is because +-- 3. The substitution is only applied ONCE! This is because -- in general such application will not reached a fixed point. data TvSubst = TvSubst InScopeSet -- The in-scope type and kind variables @@ -423,7 +423,7 @@ data TvSubst -- See Note [Apply Once] -- and Note [Extending the TvSubstEnv] --- | A substitition of 'Type's for 'TyVar's +-- | A substitution of 'Type's for 'TyVar's -- and 'Kind's for 'KindVar's type TvSubstEnv = TyVarEnv Type -- A TvSubstEnv is used both inside a TvSubst (with the apply-once @@ -439,10 +439,10 @@ We use TvSubsts to instantiate things, and we might instantiate forall a b. ty \with the types [a, b], or [b, a]. -So the substition might go [a->b, b->a]. A similar situation arises in Core +So the substitution might go [a->b, b->a]. A similar situation arises in Core when we find a beta redex like (/\ a /\ b -> e) b a -Then we also end up with a substition that permutes type variables. Other +Then we also end up with a substitution that permutes type variables. Other variations happen to; for example [a -> (a, b)]. *************************************************** From git at git.haskell.org Sun Mar 23 20:28:51 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Mar 2014 20:28:51 +0000 (UTC) Subject: [commit: packages/unix] master: Typo in comment (cdc3ae7) Message-ID: <20140323202852.8F0B82406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/unix On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cdc3ae7b087ac7451298a5b87fe2548fb74c2fdc/unix >--------------------------------------------------------------- commit cdc3ae7b087ac7451298a5b87fe2548fb74c2fdc Author: Gabor Greif Date: Sun Mar 23 21:27:14 2014 +0100 Typo in comment >--------------------------------------------------------------- cdc3ae7b087ac7451298a5b87fe2548fb74c2fdc System/Posix/Env.hsc | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/System/Posix/Env.hsc b/System/Posix/Env.hsc index fbe5c79..557bc57 100644 --- a/System/Posix/Env.hsc +++ b/System/Posix/Env.hsc @@ -132,7 +132,7 @@ putEnv :: String -> IO () putEnv keyvalue = do s <- newFilePath keyvalue -- Do not free `s` after calling putenv. -- According to SUSv2, the string passed to putenv - -- becomes part of the enviroment. #7342 + -- becomes part of the environment. #7342 throwErrnoIfMinus1_ "putenv" (c_putenv s) #if !MIN_VERSION_base(4,7,0) where From git at git.haskell.org Sun Mar 23 20:37:32 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Mar 2014 20:37:32 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Simplify handling of the interactive package; fixes Trac #8831 (8ea3d18) Message-ID: <20140323203732.7DBD82406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/8ea3d18bea9021035f8cfb0693469f2db682638a/ghc >--------------------------------------------------------------- commit 8ea3d18bea9021035f8cfb0693469f2db682638a Author: Simon Peyton Jones Date: Sat Mar 22 23:18:14 2014 +0000 Simplify handling of the interactive package; fixes Trac #8831 This patch is really a fix to the big commint 73c08ab10e4077e18e459a1325996bff110360c3 Re-work the naming story for the GHCi prompt (Trac #8649) which introduced the 'interactive' package See Note [The interactive package] in HscTypes The original commit set both (a) The tcg_mod field of TcGblEnv to 'interactive:Ghci4' (say) (b) The thisPackage field of DynFlags to 'interactive' But the second step interacts badly with linking. :loaded modules are in the package set by 'thisPackage' (usually 'main'); if you change that, then we try to link package 'main', but can't find it, and that is what happened in #8831. The fix was simple: do (a) but not (b). I changed Note [The interactive package] in HscTypes to describe this. (cherry picked from commit 28e8d878b63d06824001ac3a631254679e0f1960) >--------------------------------------------------------------- 8ea3d18bea9021035f8cfb0693469f2db682638a compiler/main/HscMain.hs | 11 ++--------- compiler/main/HscTypes.lhs | 11 +++++++---- 2 files changed, 9 insertions(+), 13 deletions(-) diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs index 04b0823..748f748 100644 --- a/compiler/main/HscMain.hs +++ b/compiler/main/HscMain.hs @@ -1357,11 +1357,7 @@ hscStmtWithLocation hsc_env0 stmt source linenumber = Just parsed_stmt -> do -- Rename and typecheck it hsc_env <- getHscEnv - let interactive_hsc_env = setInteractivePackage hsc_env - -- Bindings created here belong to the interactive package - -- See Note [The interactive package] in HscTypes - -- (NB: maybe not necessary, since Stmts bind only Ids) - (ids, tc_expr, fix_env) <- ioMsgMaybe $ tcRnStmt interactive_hsc_env parsed_stmt + (ids, tc_expr, fix_env) <- ioMsgMaybe $ tcRnStmt hsc_env parsed_stmt -- Desugar it ds_expr <- ioMsgMaybe $ deSugarExpr hsc_env tc_expr @@ -1397,10 +1393,7 @@ hscDeclsWithLocation hsc_env0 str source linenumber = {- Rename and typecheck it -} hsc_env <- getHscEnv - let interactive_hsc_env = setInteractivePackage hsc_env - -- Bindings created here belong to the interactive package - -- See Note [The interactive package] in HscTypes - tc_gblenv <- ioMsgMaybe $ tcRnDeclsi interactive_hsc_env decls + tc_gblenv <- ioMsgMaybe $ tcRnDeclsi hsc_env decls {- Grab the new instances -} -- We grab the whole environment because of the overlapping that may have diff --git a/compiler/main/HscTypes.lhs b/compiler/main/HscTypes.lhs index c4c5efd..6fcf8e2 100644 --- a/compiler/main/HscTypes.lhs +++ b/compiler/main/HscTypes.lhs @@ -1140,10 +1140,13 @@ The details are a bit tricky though: package to which :load'ed modules are added to. * So how do we arrange that declarations at the command prompt get - to be in the 'interactive' package? By setting 'thisPackage' just - before the typecheck/rename step for command-line processing; - see the calls to HscTypes.setInteractivePackage in - HscMain.hscDeclsWithLocation and hscStmtWithLocation. + to be in the 'interactive' package? Simply by setting the tcg_mod + field of the TcGblEnv to "interactive:Ghci1". This is done by the + call to initTc in initTcInteractive, initTcForLookup, which in + turn get the module from it 'icInteractiveModule' field of the + interactive context. + + The 'thisPackage' field stays as 'main' (or whatever -package-name says. * The main trickiness is that the type environment (tcg_type_env and fixity envt (tcg_fix_env) now contains entities from all the From git at git.haskell.org Sun Mar 23 20:37:35 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Mar 2014 20:37:35 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Trac #8831 is fixed (878dee3) Message-ID: <20140323203735.6C6DF2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/878dee3aad802c2d36c024ef4aa9fb1ae0895819/ghc >--------------------------------------------------------------- commit 878dee3aad802c2d36c024ef4aa9fb1ae0895819 Author: Simon Peyton Jones Date: Sun Mar 23 18:46:22 2014 +0000 Trac #8831 is fixed (cherry picked from commit 1a7709ef9b25175566bc040a34b3d479ea8566ed) Conflicts: testsuite/tests/ghci/scripts/all.T >--------------------------------------------------------------- 878dee3aad802c2d36c024ef4aa9fb1ae0895819 testsuite/tests/ghci/scripts/all.T | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T index 59a29ed..e985ce1 100755 --- a/testsuite/tests/ghci/scripts/all.T +++ b/testsuite/tests/ghci/scripts/all.T @@ -167,5 +167,5 @@ test('T8649', normal, ghci_script, ['T8649.script']) test('T8674', normal, ghci_script, ['T8674.script']) test('T8696', normal, ghci_script, ['T8696.script']) test('T8776', normal, ghci_script, ['T8776.script']) -test('T8831', expect_broken(8831), ghci_script, ['T8831.script']) +test('T8831', normal, ghci_script, ['T8831.script']) test('T8917', normal, ghci_script, ['T8917.script']) From git at git.haskell.org Sun Mar 23 20:37:39 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Mar 2014 20:37:39 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Fix the treatment of lexically scoped kind variables (Trac #8856) (935dc72) Message-ID: <20140323203739.708EE2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/935dc721cf02e3778615d3a40d04bdae17bfef0e/ghc >--------------------------------------------------------------- commit 935dc721cf02e3778615d3a40d04bdae17bfef0e Author: Simon Peyton Jones Date: Fri Mar 7 16:50:17 2014 +0000 Fix the treatment of lexically scoped kind variables (Trac #8856) The issue here is described in Note [Binding scoped type variables] in TcPat. When implementing this fix I was able to make things quite a bit simpler: * The type variables in a type signature now never unify with each other, and so can be straightfoward skolems. * We only need the SigTv stuff for signatures in patterns, and for kind variables. (cherry picked from commit cf1a0f971966af633fbd932ad012ce716680465b) >--------------------------------------------------------------- 935dc721cf02e3778615d3a40d04bdae17bfef0e compiler/typecheck/FamInst.lhs | 2 +- compiler/typecheck/TcBinds.lhs | 45 +++------------ compiler/typecheck/TcExpr.lhs | 9 ++- compiler/typecheck/TcMType.lhs | 49 ++++++---------- compiler/typecheck/TcPat.lhs | 60 ++++++++++++++++---- compiler/typecheck/TcPatSyn.lhs | 2 +- compiler/typecheck/TcType.lhs | 36 +++++------- compiler/vectorise/Vectorise/Generic/PData.hs | 2 +- testsuite/tests/typecheck/should_compile/MutRec.hs | 11 ++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 10 files changed, 107 insertions(+), 110 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 935dc721cf02e3778615d3a40d04bdae17bfef0e From git at git.haskell.org Sun Mar 23 20:37:42 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Mar 2014 20:37:42 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Test Trac #8856 (b95b3fb) Message-ID: <20140323203742.2776B2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/b95b3fbd402d53525948df03c82b774adfe7f13f/ghc >--------------------------------------------------------------- commit b95b3fbd402d53525948df03c82b774adfe7f13f Author: Simon Peyton Jones Date: Fri Mar 7 17:15:15 2014 +0000 Test Trac #8856 (cherry picked from commit 062391be4f06aa408187582c4a40f1cea80429c3) >--------------------------------------------------------------- b95b3fbd402d53525948df03c82b774adfe7f13f testsuite/tests/typecheck/should_compile/T8856.hs | 6 ++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 2 files changed, 7 insertions(+) diff --git a/testsuite/tests/typecheck/should_compile/T8856.hs b/testsuite/tests/typecheck/should_compile/T8856.hs new file mode 100644 index 0000000..6605e47 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T8856.hs @@ -0,0 +1,6 @@ +{-# LANGUAGE ScopedTypeVariables, RankNTypes, PolyKinds #-} +module T8856 where + +import Data.Proxy + +foo = (undefined :: Proxy a) :: forall a. Proxy a diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index 35b5dd2..373e739 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -417,3 +417,4 @@ test('T8565', normal, compile, ['']) test('T8644', normal, compile, ['']) test('T8762', normal, compile, ['']) test('MutRec', normal, compile, ['']) +test('T8856', normal, compile, ['']) From git at git.haskell.org Sun Mar 23 20:37:44 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Mar 2014 20:37:44 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Unflatten the constraints of an inferred types (Trac #8889) (924f749) Message-ID: <20140323203744.A36612406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/924f749433e171cc92d5d4b97701381d2ef75726/ghc >--------------------------------------------------------------- commit 924f749433e171cc92d5d4b97701381d2ef75726 Author: Simon Peyton Jones Date: Fri Mar 14 22:51:20 2014 +0000 Unflatten the constraints of an inferred types (Trac #8889) There was even a comment to warn about this possiblity, and it finally showed up in practice! This patch fixes it quite nicely, with commens to explain. (cherry picked from commit 7a7af1ffc48f605cf365faf8fcef31ef4f13822b) >--------------------------------------------------------------- 924f749433e171cc92d5d4b97701381d2ef75726 compiler/typecheck/TcMType.lhs | 2 +- compiler/typecheck/TcSimplify.lhs | 44 +++++++++++++++++++++++-------------- 2 files changed, 29 insertions(+), 17 deletions(-) diff --git a/compiler/typecheck/TcMType.lhs b/compiler/typecheck/TcMType.lhs index 2bed04c..b9f3d25 100644 --- a/compiler/typecheck/TcMType.lhs +++ b/compiler/typecheck/TcMType.lhs @@ -56,7 +56,7 @@ module TcMType ( zonkTcTyVarBndr, zonkTcType, zonkTcTypes, zonkTcThetaType, zonkTcKind, defaultKindVarToStar, - zonkEvVar, zonkWC, zonkId, zonkCt, zonkCts, zonkSkolemInfo, + zonkEvVar, zonkWC, zonkFlats, zonkId, zonkCt, zonkCts, zonkSkolemInfo, tcGetGlobalTyVars, ) where diff --git a/compiler/typecheck/TcSimplify.lhs b/compiler/typecheck/TcSimplify.lhs index 0fdd2ba..af57729 100644 --- a/compiler/typecheck/TcSimplify.lhs +++ b/compiler/typecheck/TcSimplify.lhs @@ -253,39 +253,50 @@ simplifyInfer _top_lvl apply_mr name_taus wanteds ; ev_binds_var <- newTcEvBinds ; wanted_transformed_incl_derivs <- solveWantedsTcMWithEvBinds ev_binds_var wanteds solve_wanteds - -- Post: wanted_transformed are zonked + -- Post: wanted_transformed_incl_derivs are zonked -- Step 4) Candidates for quantification are an approximation of wanted_transformed -- NB: Already the fixpoint of any unifications that may have happened -- NB: We do not do any defaulting when inferring a type, this can lead -- to less polymorphic types, see Note [Default while Inferring] - -- Step 5) Minimize the quantification candidates - -- Step 6) Final candidates for quantification - -- We discard bindings, insolubles etc, because all we are - -- care aout it - ; tc_lcl_env <- TcRnMonad.getLclEnv ; let untch = tcl_untch tc_lcl_env wanted_transformed = dropDerivedWC wanted_transformed_incl_derivs ; quant_pred_candidates -- Fully zonked <- if insolubleWC wanted_transformed_incl_derivs then return [] -- See Note [Quantification with errors] - -- NB: must include derived errors - else do { gbl_tvs <- tcGetGlobalTyVars - ; let quant_cand = approximateWC wanted_transformed + -- 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)) - ; ((flats, _insols), _extra_binds) <- runTcS $ + ; gbl_tvs <- tcGetGlobalTyVars + ; null_ev_binds_var <- newTcEvBinds + -- Miminise quant_cand. We are not interested in any evidence + -- produced, because we are going to simplify wanted_transformed + -- again later. All we want here is the predicates over which to + -- quantify. + -- + -- If any meta-tyvar unifications take place (unlikely), we'll + -- pick that up later. + + ; (flats, _insols) <- runTcSWithEvBinds null_ev_binds_var $ do { mapM_ (promoteAndDefaultTyVar untch gbl_tvs) meta_tvs -- See Note [Promote _and_ default when inferring] ; _implics <- solveInteract quant_cand ; getInertUnsolved } - ; return (map ctPred $ filter isWantedCt (bagToList flats)) } - -- NB: Dimitrios is slightly worried that we will get - -- family equalities (F Int ~ alpha) in the quantification - -- candidates, as we have performed no further unflattening - -- at this point. Nothing bad, but inferred contexts might - -- look complicated. + + ; flats' <- zonkFlats null_ev_binds_var untch $ + filterBag isWantedCt flats + -- The quant_cand were already fully zonked, so this zonkFlats + -- really only unflattens the flattening that solveInteract + -- may have done (Trac #8889). + -- E.g. quant_cand = F a, where F :: * -> Constraint + -- We'll flatten to (alpha, F a ~ alpha) + -- fail to make any further progress and must unflatten again + + ; return (map ctPred $ bagToList flats') } -- NB: quant_pred_candidates is already the fixpoint of any -- unifications that may have happened @@ -326,6 +337,7 @@ simplifyInfer _top_lvl apply_mr name_taus wanteds { -- Step 7) Emit an implication let minimal_flat_preds = mkMinimalBySCs bound + -- See Note [Minimize by Superclasses] skol_info = InferSkol [ (name, mkSigmaTy [] minimal_flat_preds ty) | (name, ty) <- name_taus ] -- Don't add the quantified variables here, because From git at git.haskell.org Sun Mar 23 20:37:47 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Mar 2014 20:37:47 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Test Trac #8889 (85bc454) Message-ID: <20140323203747.937702406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/85bc454267ba45091e560e62571a83409170646e/ghc >--------------------------------------------------------------- commit 85bc454267ba45091e560e62571a83409170646e Author: Simon Peyton Jones Date: Mon Mar 17 13:50:54 2014 +0000 Test Trac #8889 (cherry picked from commit 0e2155ddb10f4ccf53e50064756cbc3ce7dd8832) >--------------------------------------------------------------- 85bc454267ba45091e560e62571a83409170646e testsuite/tests/indexed-types/should_compile/T8889.hs | 12 ++++++++++++ testsuite/tests/indexed-types/should_compile/T8889.stderr | 6 ++++++ testsuite/tests/indexed-types/should_compile/all.T | 1 + 3 files changed, 19 insertions(+) diff --git a/testsuite/tests/indexed-types/should_compile/T8889.hs b/testsuite/tests/indexed-types/should_compile/T8889.hs new file mode 100644 index 0000000..45c88a6 --- /dev/null +++ b/testsuite/tests/indexed-types/should_compile/T8889.hs @@ -0,0 +1,12 @@ +{-# LANGUAGE TypeFamilies, ConstraintKinds #-} +{-# OPTIONS_GHC -fwarn-missing-signatures #-} -- Report f's inferred type + +module T8889 where + +import GHC.Exts + +class C f where + type C_fmap f a :: Constraint + foo :: C_fmap f a => (a -> b) -> f a -> f b + +f x = foo x diff --git a/testsuite/tests/indexed-types/should_compile/T8889.stderr b/testsuite/tests/indexed-types/should_compile/T8889.stderr new file mode 100644 index 0000000..77e05d7 --- /dev/null +++ b/testsuite/tests/indexed-types/should_compile/T8889.stderr @@ -0,0 +1,6 @@ + +T8889.hs:12:1: Warning: + Top-level binding with no type signature: + f :: forall (f :: * -> *) a b. + (C_fmap f a, C f) => + (a -> b) -> f a -> f b diff --git a/testsuite/tests/indexed-types/should_compile/all.T b/testsuite/tests/indexed-types/should_compile/all.T index f722ea3..5c156ec 100644 --- a/testsuite/tests/indexed-types/should_compile/all.T +++ b/testsuite/tests/indexed-types/should_compile/all.T @@ -239,3 +239,4 @@ test('ClosedFam1', extra_clean(['ClosedFam1.o-boot', 'ClosedFam1.hi-boot']), test('ClosedFam2', extra_clean(['ClosedFam2.o-boot', 'ClosedFam2.hi-boot']), multimod_compile, ['ClosedFam2', '-v0']) test('T8651', normal, compile, ['']) +test('T8889', normal, compile, ['']) From git at git.haskell.org Sun Mar 23 20:37:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Mar 2014 20:37:50 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Make sure we occurrence-analyse unfoldings (fixes Trac #8892) (632956d) Message-ID: <20140323203750.7EBAF2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/632956d089071969e52de65f27c810dd926e3a79/ghc >--------------------------------------------------------------- commit 632956d089071969e52de65f27c810dd926e3a79 Author: Simon Peyton Jones Date: Tue Mar 18 17:10:18 2014 +0000 Make sure we occurrence-analyse unfoldings (fixes Trac #8892) For DFunUnfoldings we were failing to occurrence-analyse the unfolding, and that meant that a loop breaker wasn't marked as such, which in turn meant it was inlined away when it still had occurrence sites. See Note [Occurrrence analysis of unfoldings] in CoreUnfold. This is a pretty long-standing bug, happily nailed by John Lato. (cherry picked from commit 87bbc69c40d36046492d754c8d7ff02c3be6ce43) >--------------------------------------------------------------- 632956d089071969e52de65f27c810dd926e3a79 compiler/coreSyn/CoreUnfold.lhs | 25 ++++++++++++- compiler/simplCore/Simplify.lhs | 78 +++++++++++++++++++-------------------- 2 files changed, 62 insertions(+), 41 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 632956d089071969e52de65f27c810dd926e3a79 From git at git.haskell.org Sun Mar 23 20:37:53 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Mar 2014 20:37:53 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Apply the kind subst to the (kinds of the) quanitifed tyvars in deriveTyData (c63af7a) Message-ID: <20140323203753.77B752406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/c63af7a0c599e9a090b38a7c3a51c56b8eea49ee/ghc >--------------------------------------------------------------- commit c63af7a0c599e9a090b38a7c3a51c56b8eea49ee Author: Simon Peyton Jones Date: Sat Mar 22 23:11:10 2014 +0000 Apply the kind subst to the (kinds of the) quanitifed tyvars in deriveTyData I've elaboated Note [Unify kinds in deriving] to explain what is going on here. The change fixes Trac #8893. (cherry picked from commit ffed708c30f2d1d4b4c5cd08d9c19aeb0bb623ec) >--------------------------------------------------------------- c63af7a0c599e9a090b38a7c3a51c56b8eea49ee compiler/typecheck/TcDeriv.lhs | 56 ++++++++++++++++++++++++++++++---------- 1 file changed, 43 insertions(+), 13 deletions(-) diff --git a/compiler/typecheck/TcDeriv.lhs b/compiler/typecheck/TcDeriv.lhs index bb858be..8d5a3a1 100644 --- a/compiler/typecheck/TcDeriv.lhs +++ b/compiler/typecheck/TcDeriv.lhs @@ -684,13 +684,19 @@ deriveTyData tvs tc tc_args (L loc deriv_pred) tc_args_to_keep = take n_args_to_keep tc_args inst_ty_kind = typeKind (mkTyConApp tc tc_args_to_keep) dropped_tvs = tyVarsOfTypes args_to_drop - mb_match = tcUnifyTy inst_ty_kind cls_arg_kind - Just subst = mb_match -- See Note [Unify kinds in deriving] - -- We are assuming the tycon tyvars and the class tyvars are distinct - final_tc_args = substTys subst tc_args_to_keep - final_cls_tys = substTys subst cls_tys - univ_tvs = mkVarSet deriv_tvs `unionVarSet` tyVarsOfTypes final_tc_args + -- Match up the kinds, and apply the resulting kind substitution + -- to the types. See Note [Unify kinds in deriving] + -- We are assuming the tycon tyvars and the class tyvars are distinct + mb_match = tcUnifyTy inst_ty_kind cls_arg_kind + Just kind_subst = mb_match + (univ_kvs, univ_tvs) = partition isKindVar $ varSetElems $ + mkVarSet deriv_tvs `unionVarSet` + tyVarsOfTypes tc_args_to_keep + univ_kvs' = filter (`notElemTvSubst` kind_subst) univ_kvs + (subst', univ_tvs') = mapAccumL substTyVarBndr kind_subst univ_tvs + final_tc_args = substTys subst' tc_args_to_keep + final_cls_tys = substTys subst' cls_tys ; traceTc "derivTyData1" (vcat [ pprTvBndrs tvs, ppr tc, ppr tc_args , pprTvBndrs (varSetElems $ tyVarsOfTypes tc_args) @@ -703,9 +709,9 @@ deriveTyData tvs tc tc_args (L loc deriv_pred) ; traceTc "derivTyData2" (vcat [ ppr univ_tvs ]) - ; checkTc (allDistinctTyVars args_to_drop && -- (a) and (b) - univ_tvs `disjointVarSet` dropped_tvs) -- (c) - (derivingEtaErr cls cls_tys (mkTyConApp tc final_tc_args)) + ; checkTc (allDistinctTyVars args_to_drop && -- (a) and (b) + not (any (`elemVarSet` dropped_tvs) univ_tvs)) -- (c) + (derivingEtaErr cls final_cls_tys (mkTyConApp tc final_tc_args)) -- Check that -- (a) The args to drop are all type variables; eg reject: -- data instance T a Int = .... deriving( Monad ) @@ -717,7 +723,7 @@ deriveTyData tvs tc tc_args (L loc deriv_pred) -- newtype T a s = ... deriving( ST s ) -- newtype K a a = ... deriving( Monad ) - ; mkEqnHelp (varSetElemsKvsFirst univ_tvs) + ; mkEqnHelp (univ_kvs' ++ univ_tvs') cls final_cls_tys tc final_tc_args Nothing } } derivePolyKindedTypeable :: Class -> [Type] @@ -773,10 +779,34 @@ So we need to kind arguments. In the two examples, - * we unify ( T k (a:k) ) ~ (* -> *) to find k:=*. - * we unify ( Either ~ (k -> k -> k) ) to find k:=*. + * we unify kind-of( T k (a:k) ) ~ kind-of( Functor ) + i.e. (k -> *) ~ (* -> *) to find k:=*. + yielding k:=* + + * we unify kind-of( Either ) ~ kind-of( Category ) + i.e. (* -> * -> *) ~ (k -> k -> k) + yielding k:=* + +Now we get a kind substition. We then need to: + + 1. Remove the substituted-out kind variables from the quantifed kind vars + + 2. Apply the substitution to the kinds of quantified *type* vars + (and extend the substitution to reflect this change) + + 3. Apply that extended substitution to the non-dropped args (types and + kinds) of the type and class + +Forgetting step (2) caused Trac #8893: + data V a = V [a] deriving Functor + data P (x::k->*) (a:k) = P (x a) deriving Functor + data C (x::k->*) (a:k) = C (V (P x a)) deriving Functor + +When deriving Functor for P, we unify k to *, but we then want +an instance $df :: forall (x:*->*). Functor x => Functor (P * (x:*->*)) +and similarly for C. Notice the modifed kind of x, both at binding +and occurrence sites. -Tricky stuff. \begin{code} mkEqnHelp :: [TyVar] From git at git.haskell.org Sun Mar 23 20:37:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Mar 2014 20:37:56 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Test Trac #8893 (11d3f6b) Message-ID: <20140323203756.96D2B2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/11d3f6b9868affa17f023c84f71e6f13642fcf91/ghc >--------------------------------------------------------------- commit 11d3f6b9868affa17f023c84f71e6f13642fcf91 Author: Simon Peyton Jones Date: Sun Mar 23 18:44:43 2014 +0000 Test Trac #8893 (cherry picked from commit 7973bfb87fdbe6e980e64ed5d7b2a90a469effd4) >--------------------------------------------------------------- 11d3f6b9868affa17f023c84f71e6f13642fcf91 testsuite/tests/deriving/should_compile/T8893.hs | 11 +++++++++++ testsuite/tests/deriving/should_compile/all.T | 1 + 2 files changed, 12 insertions(+) diff --git a/testsuite/tests/deriving/should_compile/T8893.hs b/testsuite/tests/deriving/should_compile/T8893.hs new file mode 100644 index 0000000..2ebcc94 --- /dev/null +++ b/testsuite/tests/deriving/should_compile/T8893.hs @@ -0,0 +1,11 @@ +{-# OPTIONS_GHC -Wall #-} +{-# Language DeriveFunctor #-} +{-# Language PolyKinds #-} + +module T8893 where + +data V a = V [a] deriving Functor + +data C x a = C (V (P x a)) deriving Functor + +data P x a = P (x a) deriving Functor diff --git a/testsuite/tests/deriving/should_compile/all.T b/testsuite/tests/deriving/should_compile/all.T index 257a9b2..b649ff6 100644 --- a/testsuite/tests/deriving/should_compile/all.T +++ b/testsuite/tests/deriving/should_compile/all.T @@ -45,3 +45,4 @@ test('T8138', reqlib('primitive'), compile, ['-O2']) test('T8631', normal, compile, ['']) test('T8758', extra_clean(['T8758a.o', 'T8758a.hi']), multimod_compile, ['T8758a', '-v0']) test('T8865', normal, compile, ['']) +test('T8893', normal, compile, ['']) From git at git.haskell.org Sun Mar 23 22:29:10 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 23 Mar 2014 22:29:10 +0000 (UTC) Subject: [commit: ghc] master: The substitution is never needed, so don't prepare it (61654e5) Message-ID: <20140323222910.337792406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/61654e55e9e7f65b876adf7416388134058b0d9a/ghc >--------------------------------------------------------------- commit 61654e55e9e7f65b876adf7416388134058b0d9a Author: Gabor Greif Date: Sun Mar 23 23:27:47 2014 +0100 The substitution is never needed, so don't prepare it >--------------------------------------------------------------- 61654e55e9e7f65b876adf7416388134058b0d9a configure.ac | 1 - 1 file changed, 1 deletion(-) diff --git a/configure.ac b/configure.ac index 244fcc0..9d55194 100644 --- a/configure.ac +++ b/configure.ac @@ -498,7 +498,6 @@ dnl -------------------------------------------------------------- FP_ARG_WITH_PATH_GNU_PROG([RANLIB], [ranlib], [ranlib]) RanlibCmd="$RANLIB" RANLIB="$RanlibCmd" -AC_SUBST([RanlibCmd]) # Note: we may not have objdump on OS X, and we only need it on Windows (for DLL checks) From git at git.haskell.org Mon Mar 24 00:10:45 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Mar 2014 00:10:45 +0000 (UTC) Subject: [commit: packages/base] master: Comments only. (5edb063) Message-ID: <20140324001045.D39972406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/base On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5edb063688e73ec00fd1f61ac0e8317dd122f44a/base >--------------------------------------------------------------- commit 5edb063688e73ec00fd1f61ac0e8317dd122f44a Author: Iavor S. Diatchki Date: Sun Mar 23 17:10:38 2014 -0700 Comments only. Fix the documentation on CmpSymbol and CmpNat; add a note on (<=?). >--------------------------------------------------------------- 5edb063688e73ec00fd1f61ac0e8317dd122f44a GHC/TypeLits.hs | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/GHC/TypeLits.hs b/GHC/TypeLits.hs index ac0f1ae..4a6c7b9 100644 --- a/GHC/TypeLits.hs +++ b/GHC/TypeLits.hs @@ -153,13 +153,16 @@ infixr 8 ^ -- | Comparison of type-level naturals, as a constraint. type x <= y = (x <=? y) ~ True --- | Comparison of type-level naturals, as a function. +-- | Comparison of type-level symbols, as a function. type family CmpSymbol (m :: Symbol) (n :: Symbol) :: Ordering --- | Comparison of type-level symbols, as a function. +-- | Comparison of type-level naturals, as a function. type family CmpNat (m :: Nat) (n :: Nat) :: Ordering --- | Comparison of type-level naturals, as a function. +{- | Comparison of type-level naturals, as a function. +NOTE: The functionality for this function should be subsumed +by 'CmpNat', so this might go away in the future. +Please let us know, if you encounter discrepancies between the two. -} type family (m :: Nat) <=? (n :: Nat) :: Bool -- | Addition of type-level naturals. From git at git.haskell.org Mon Mar 24 05:52:13 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Mar 2014 05:52:13 +0000 (UTC) Subject: [commit: ghc] master: Revert "Fix #8745 - GND is now -XSafe compatible." (8f73037) Message-ID: <20140324055213.2A1142406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8f7303774237a8b0787d98c5ab6f605e3e897f19/ghc >--------------------------------------------------------------- commit 8f7303774237a8b0787d98c5ab6f605e3e897f19 Author: Austin Seipp Date: Sun Mar 23 23:45:22 2014 -0500 Revert "Fix #8745 - GND is now -XSafe compatible." See #8827 - for now, we're making GND unsafe again. This also fixes the tests since they were originally not using the new unicode quote style we're using. This reverts commit a8a01e742434df11b830ab99af12d9045dfcbc4b. >--------------------------------------------------------------- 8f7303774237a8b0787d98c5ab6f605e3e897f19 compiler/main/DynFlags.hs | 5 ++- testsuite/tests/safeHaskell/ghci/p1.stderr | 3 ++ testsuite/tests/safeHaskell/ghci/p16.stderr | 15 +++++++ testsuite/tests/safeHaskell/ghci/p16.stdout | 1 - .../safeHaskell/safeInfered/UnsafeInfered03_A.hs | 2 +- .../tests/safeHaskell/safeLanguage/SafeLang02.hs | 2 +- .../safeHaskell/safeLanguage/SafeLang02.stderr | 2 +- .../tests/safeHaskell/safeLanguage/SafeLang07.hs | 41 ++++++++++++++++++++ .../safeHaskell/safeLanguage/SafeLang07.stderr | 7 ++++ .../tests/safeHaskell/safeLanguage/SafeLang07_A.hs | 24 ++++++++++++ testsuite/tests/safeHaskell/safeLanguage/all.T | 7 ++-- 11 files changed, 101 insertions(+), 8 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 8f7303774237a8b0787d98c5ab6f605e3e897f19 From git at git.haskell.org Mon Mar 24 05:53:10 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Mar 2014 05:53:10 +0000 (UTC) Subject: [commit: packages/base] master: Mark Data.Coerce as Unsafe (#8827) (2dbde34) Message-ID: <20140324055310.426512406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/base On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2dbde340fae8122342a4d7c13fea7890ab963d11/base >--------------------------------------------------------------- commit 2dbde340fae8122342a4d7c13fea7890ab963d11 Author: Austin Seipp Date: Mon Mar 24 00:40:33 2014 -0500 Mark Data.Coerce as Unsafe (#8827) Signed-off-by: Austin Seipp >--------------------------------------------------------------- 2dbde340fae8122342a4d7c13fea7890ab963d11 Data/Coerce.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Data/Coerce.hs b/Data/Coerce.hs index b00144b..bf269f5 100644 --- a/Data/Coerce.hs +++ b/Data/Coerce.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE Trustworthy #-} +{-# LANGUAGE Unsafe #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE StandaloneDeriving #-} From git at git.haskell.org Mon Mar 24 07:14:40 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Mar 2014 07:14:40 +0000 (UTC) Subject: [commit: ghc] master: Revert "change deriveConstants to use nm in a POSIX way (fixes #8781)" (15b1eb7) Message-ID: <20140324071441.4DD322406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/15b1eb7c67e29c4ad6f6859f89d220b33493fd46/ghc >--------------------------------------------------------------- commit 15b1eb7c67e29c4ad6f6859f89d220b33493fd46 Author: Austin Seipp Date: Mon Mar 24 02:14:09 2014 -0500 Revert "change deriveConstants to use nm in a POSIX way (fixes #8781)" It causes a failure on Windows right now. This reverts commit 045b28033a33a48d31951240a8cb35f2b78345dc. >--------------------------------------------------------------- 15b1eb7c67e29c4ad6f6859f89d220b33493fd46 utils/deriveConstants/DeriveConstants.hs | 30 ++++++++++++++++++++---------- 1 file changed, 20 insertions(+), 10 deletions(-) diff --git a/utils/deriveConstants/DeriveConstants.hs b/utils/deriveConstants/DeriveConstants.hs index 6344569..293fe65 100644 --- a/utils/deriveConstants/DeriveConstants.hs +++ b/utils/deriveConstants/DeriveConstants.hs @@ -638,7 +638,7 @@ getWanted verbose tmpdir gccProgram gccFlags nmProgram oFile = tmpdir "tmp.o" writeFile cFile cStuff execute verbose gccProgram (gccFlags ++ ["-c", cFile, "-o", oFile]) - xs <- readProcess nmProgram ["-P", oFile] "" + xs <- readProcess nmProgram [oFile] "" let ls = lines xs ms = map parseNmLine ls m = Map.fromList $ catMaybes ms @@ -707,17 +707,27 @@ getWanted verbose tmpdir gccProgram gccFlags nmProgram doWanted (ClosurePayloadMacro {}) = [] doWanted (FieldTypeGcptrMacro {}) = [] - -- parseNmLine parses "nm -P" output that looks like - -- "_derivedConstantMAX_Vanilla_REG C b 0" Mac OS X - -- "derivedConstantMAX_Vanilla_REG C 0000000b 0000000b" GNU - -- "derivedConstantMAX_Vanilla_REG D 1 b" Solaris + -- parseNmLine parses nm output that looks like + -- "0000000b C derivedConstantMAX_Vanilla_REG" -- and returns ("MAX_Vanilla_REG", 11) - parseNmLine xs0 = case words xs0 of - [x0, x1, x2, x3] -> case stripPrefix prefix $ dropWhile (== '_') x0 of - Just name -> case readHex $ if x1 == "C" then x2 else x3 of - [(size, "")] -> Just (name, size) + parseNmLine xs0 = case break (' ' ==) xs0 of + (x1, ' ' : xs1) -> + case break (' ' ==) xs1 of + (x2, ' ' : x3) -> + case readHex x1 of + [(size, "")] -> + case x2 of + "C" -> + let x3' = case x3 of + '_' : rest -> rest + _ -> x3 + in case stripPrefix prefix x3' of + Just name -> + Just (name, size) + _ -> Nothing + _ -> Nothing + _ -> Nothing _ -> Nothing - _ -> Nothing _ -> Nothing -- If an Int value is larger than 2^28 or smaller From git at git.haskell.org Mon Mar 24 08:10:07 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Mar 2014 08:10:07 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Revert "Fix #8745 - GND is now -XSafe compatible." (46cfa8e) Message-ID: <20140324081007.98BE22406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/46cfa8ebd3f7a9b93afcf5e0e9b7e4a5a973a25d/ghc >--------------------------------------------------------------- commit 46cfa8ebd3f7a9b93afcf5e0e9b7e4a5a973a25d Author: Austin Seipp Date: Sun Mar 23 23:45:22 2014 -0500 Revert "Fix #8745 - GND is now -XSafe compatible." See #8827 - for now, we're making GND unsafe again. This also fixes the tests since they were originally not using the new unicode quote style we're using. This reverts commit a8a01e742434df11b830ab99af12d9045dfcbc4b. (cherry picked from commit 8f7303774237a8b0787d98c5ab6f605e3e897f19) >--------------------------------------------------------------- 46cfa8ebd3f7a9b93afcf5e0e9b7e4a5a973a25d compiler/main/DynFlags.hs | 5 ++- testsuite/tests/safeHaskell/ghci/p1.stderr | 3 ++ testsuite/tests/safeHaskell/ghci/p16.stderr | 15 +++++++ testsuite/tests/safeHaskell/ghci/p16.stdout | 1 - .../safeHaskell/safeInfered/UnsafeInfered03_A.hs | 2 +- .../tests/safeHaskell/safeLanguage/SafeLang02.hs | 2 +- .../safeHaskell/safeLanguage/SafeLang02.stderr | 2 +- .../tests/safeHaskell/safeLanguage/SafeLang07.hs | 41 ++++++++++++++++++++ .../safeHaskell/safeLanguage/SafeLang07.stderr | 7 ++++ .../tests/safeHaskell/safeLanguage/SafeLang07_A.hs | 24 ++++++++++++ testsuite/tests/safeHaskell/safeLanguage/all.T | 7 ++-- 11 files changed, 101 insertions(+), 8 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 46cfa8ebd3f7a9b93afcf5e0e9b7e4a5a973a25d From git at git.haskell.org Mon Mar 24 08:10:09 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Mar 2014 08:10:09 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Follow hs_popcntX changes in ghc-prim (0e3a551) Message-ID: <20140324081010.6BE342406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/0e3a5514288ee37da185b58199f4684c6f2efa01/ghc >--------------------------------------------------------------- commit 0e3a5514288ee37da185b58199f4684c6f2efa01 Author: Johan Tibell Date: Sat Mar 22 18:29:29 2014 +0100 Follow hs_popcntX changes in ghc-prim (cherry picked from commit 1a63f17f19a6c83980efe453966eac1cf441b277) >--------------------------------------------------------------- 0e3a5514288ee37da185b58199f4684c6f2efa01 includes/stg/Prim.h | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/includes/stg/Prim.h b/includes/stg/Prim.h index 2b23c3d..7d94d18 100644 --- a/includes/stg/Prim.h +++ b/includes/stg/Prim.h @@ -22,14 +22,14 @@ StgWord64 hs_bswap64(StgWord64 x); /* TODO: longlong.c */ /* libraries/ghc-prim/cbits/popcnt.c */ -StgWord hs_popcnt8(StgWord8 x); -StgWord hs_popcnt16(StgWord16 x); -StgWord hs_popcnt32(StgWord32 x); +StgWord hs_popcnt8(StgWord x); +StgWord hs_popcnt16(StgWord x); +StgWord hs_popcnt32(StgWord x); StgWord hs_popcnt64(StgWord64 x); #ifdef i386_HOST_ARCH -StgWord hs_popcnt(StgWord32 x); +StgWord hs_popcnt(StgWord x); #else -StgWord hs_popcnt(StgWord64 x); +StgWord hs_popcnt(StgWord x); #endif /* libraries/ghc-prim/cbits/word2float.c */ From git at git.haskell.org Mon Mar 24 08:10:12 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Mar 2014 08:10:12 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Enable popcnt test now when segfault is fixed (bca03d9) Message-ID: <20140324081012.4D4C72406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/bca03d95b6005afa9167410c6ca9ddee6c185aa1/ghc >--------------------------------------------------------------- commit bca03d95b6005afa9167410c6ca9ddee6c185aa1 Author: Johan Tibell Date: Sat Mar 22 18:30:36 2014 +0100 Enable popcnt test now when segfault is fixed The fix was to ghc-prim. (cherry picked from commit 16d04d902d4720b3137e07a503fbf72c90b9e164) >--------------------------------------------------------------- bca03d95b6005afa9167410c6ca9ddee6c185aa1 testsuite/tests/codeGen/should_run/all.T | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/codeGen/should_run/all.T b/testsuite/tests/codeGen/should_run/all.T index 768d320..421d71c 100644 --- a/testsuite/tests/codeGen/should_run/all.T +++ b/testsuite/tests/codeGen/should_run/all.T @@ -75,7 +75,7 @@ test('cgrun068', reqlib('random'), compile_and_run, ['']) test('cgrun069', omit_ways(['ghci']), multi_compile_and_run, ['cgrun069', [('cgrun069_cmm.cmm', '')], '']) test('cgrun070', normal, compile_and_run, ['']) -test('cgrun071', when(opsys('darwin'), expect_broken(7684)), compile_and_run, ['']) +test('cgrun071', normal, compile_and_run, ['']) test('cgrun072', normal, compile_and_run, ['']) test('T1852', normal, compile_and_run, ['']) From git at git.haskell.org Mon Mar 24 08:10:14 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Mar 2014 08:10:14 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Revert "change deriveConstants to use nm in a POSIX way (fixes #8781)" (a617888) Message-ID: <20140324081014.A9FDD2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/a6178886f184dcc2fc4b15f45708d53295a77271/ghc >--------------------------------------------------------------- commit a6178886f184dcc2fc4b15f45708d53295a77271 Author: Austin Seipp Date: Mon Mar 24 02:14:09 2014 -0500 Revert "change deriveConstants to use nm in a POSIX way (fixes #8781)" It causes a failure on Windows right now. This reverts commit 045b28033a33a48d31951240a8cb35f2b78345dc. (cherry picked from commit 15b1eb7c67e29c4ad6f6859f89d220b33493fd46) >--------------------------------------------------------------- a6178886f184dcc2fc4b15f45708d53295a77271 utils/deriveConstants/DeriveConstants.hs | 30 ++++++++++++++++++++---------- 1 file changed, 20 insertions(+), 10 deletions(-) diff --git a/utils/deriveConstants/DeriveConstants.hs b/utils/deriveConstants/DeriveConstants.hs index 54ee6a1..10df61c 100644 --- a/utils/deriveConstants/DeriveConstants.hs +++ b/utils/deriveConstants/DeriveConstants.hs @@ -638,7 +638,7 @@ getWanted verbose tmpdir gccProgram gccFlags nmProgram oFile = tmpdir "tmp.o" writeFile cFile cStuff execute verbose gccProgram (gccFlags ++ ["-c", cFile, "-o", oFile]) - xs <- readProcess nmProgram ["-P", oFile] "" + xs <- readProcess nmProgram [oFile] "" let ls = lines xs ms = map parseNmLine ls m = Map.fromList $ catMaybes ms @@ -707,17 +707,27 @@ getWanted verbose tmpdir gccProgram gccFlags nmProgram doWanted (ClosurePayloadMacro {}) = [] doWanted (FieldTypeGcptrMacro {}) = [] - -- parseNmLine parses "nm -P" output that looks like - -- "_derivedConstantMAX_Vanilla_REG C b 0" Mac OS X - -- "derivedConstantMAX_Vanilla_REG C 0000000b 0000000b" GNU - -- "derivedConstantMAX_Vanilla_REG D 1 b" Solaris + -- parseNmLine parses nm output that looks like + -- "0000000b C derivedConstantMAX_Vanilla_REG" -- and returns ("MAX_Vanilla_REG", 11) - parseNmLine xs0 = case words xs0 of - [x0, x1, x2, x3] -> case stripPrefix prefix $ dropWhile (== '_') x0 of - Just name -> case readHex $ if x1 == "C" then x2 else x3 of - [(size, "")] -> Just (name, size) + parseNmLine xs0 = case break (' ' ==) xs0 of + (x1, ' ' : xs1) -> + case break (' ' ==) xs1 of + (x2, ' ' : x3) -> + case readHex x1 of + [(size, "")] -> + case x2 of + "C" -> + let x3' = case x3 of + '_' : rest -> rest + _ -> x3 + in case stripPrefix prefix x3' of + Just name -> + Just (name, size) + _ -> Nothing + _ -> Nothing + _ -> Nothing _ -> Nothing - _ -> Nothing _ -> Nothing -- If an Int value is larger than 2^28 or smaller From git at git.haskell.org Mon Mar 24 08:10:26 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Mar 2014 08:10:26 +0000 (UTC) Subject: [commit: packages/base] ghc-7.8: Mark Data.Coerce as Unsafe (#8827) (963e353) Message-ID: <20140324081026.E3B582406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/base On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/963e35391b8d0e44987ed693967a42dd0d4426bd/base >--------------------------------------------------------------- commit 963e35391b8d0e44987ed693967a42dd0d4426bd Author: Austin Seipp Date: Mon Mar 24 00:40:33 2014 -0500 Mark Data.Coerce as Unsafe (#8827) Signed-off-by: Austin Seipp (cherry picked from commit 2dbde340fae8122342a4d7c13fea7890ab963d11) >--------------------------------------------------------------- 963e35391b8d0e44987ed693967a42dd0d4426bd Data/Coerce.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Data/Coerce.hs b/Data/Coerce.hs index 2065159..ab47138 100644 --- a/Data/Coerce.hs +++ b/Data/Coerce.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE Trustworthy #-} +{-# LANGUAGE Unsafe #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE StandaloneDeriving #-} From git at git.haskell.org Mon Mar 24 08:10:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Mar 2014 08:10:50 +0000 (UTC) Subject: [commit: packages/ghc-prim] ghc-7.8: Make argument types in popcnt.c match declared primop types (84d7b7d) Message-ID: <20140324081050.56EE82406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc-prim On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/84d7b7dd2d91ec9cce154602669b97a084412cf2/ghc-prim >--------------------------------------------------------------- commit 84d7b7dd2d91ec9cce154602669b97a084412cf2 Author: Reid Barton Date: Fri Sep 6 19:22:38 2013 -0400 Make argument types in popcnt.c match declared primop types On 64-bit Mac OS, gcc 4.2 (which comes with Xcode 4.6) generates code that assumes that an argument that is smaller than the register it is passed in has been sign- or zero-extended. But ghc thinks the types of the PopCnt*Op primops are Word# -> Word#, so it passes the entire argument word to the hs_popcnt* function as though it was declared to have an argument of type StgWord. Segfaults ensue. The easiest fix is to sidestep all this zero-extension business by declaring the hs_popcnt* functions to take a whole StgWord (when their argument would fit in a register), thereby matching the list of primops. Fixes #7684. (cherry picked from commit ad9bf96815cb5a9bb4acc51c99eff20be3e50da3) >--------------------------------------------------------------- 84d7b7dd2d91ec9cce154602669b97a084412cf2 cbits/popcnt.c | 20 ++++++++++---------- 1 file changed, 10 insertions(+), 10 deletions(-) diff --git a/cbits/popcnt.c b/cbits/popcnt.c index b17b624..fc44ee7 100644 --- a/cbits/popcnt.c +++ b/cbits/popcnt.c @@ -12,24 +12,24 @@ static const unsigned char popcount_tab[] = 3,4,4,5,4,5,5,6,4,5,5,6,5,6,6,7,4,5,5,6,5,6,6,7,5,6,6,7,6,7,7,8, }; -extern StgWord hs_popcnt8(StgWord8 x); +extern StgWord hs_popcnt8(StgWord x); StgWord -hs_popcnt8(StgWord8 x) +hs_popcnt8(StgWord x) { return popcount_tab[(unsigned char)x]; } -extern StgWord hs_popcnt16(StgWord16 x); +extern StgWord hs_popcnt16(StgWord x); StgWord -hs_popcnt16(StgWord16 x) +hs_popcnt16(StgWord x) { return popcount_tab[(unsigned char)x] + popcount_tab[(unsigned char)(x >> 8)]; } -extern StgWord hs_popcnt32(StgWord32 x); +extern StgWord hs_popcnt32(StgWord x); StgWord -hs_popcnt32(StgWord32 x) +hs_popcnt32(StgWord x) { return popcount_tab[(unsigned char)x] + popcount_tab[(unsigned char)(x >> 8)] + @@ -53,9 +53,9 @@ hs_popcnt64(StgWord64 x) #ifdef i386_HOST_ARCH -extern StgWord hs_popcnt(StgWord32 x); +extern StgWord hs_popcnt(StgWord x); StgWord -hs_popcnt(StgWord32 x) +hs_popcnt(StgWord x) { return popcount_tab[(unsigned char)x] + popcount_tab[(unsigned char)(x >> 8)] + @@ -65,9 +65,9 @@ hs_popcnt(StgWord32 x) #else -extern StgWord hs_popcnt(StgWord64 x); +extern StgWord hs_popcnt(StgWord x); StgWord -hs_popcnt(StgWord64 x) +hs_popcnt(StgWord x) { return popcount_tab[(unsigned char)x] + popcount_tab[(unsigned char)(x >> 8)] + From git at git.haskell.org Mon Mar 24 09:45:58 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Mar 2014 09:45:58 +0000 (UTC) Subject: [commit: ghc] wip/T8545-ghc-7.8: Convert all sub-repos into proper submodules (re #8545) (830f231) Message-ID: <20140324094559.206FF2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8545-ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/830f2314b237ed25dcbc5ae7bff17122aaed3b95/ghc >--------------------------------------------------------------- commit 830f2314b237ed25dcbc5ae7bff17122aaed3b95 Author: Herbert Valerio Riedel Date: Sat Mar 22 15:26:34 2014 +0100 Convert all sub-repos into proper submodules (re #8545) ...except for ghc-tarballs which is a waste of bandwidth Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 830f2314b237ed25dcbc5ae7bff17122aaed3b95 .gitignore | 27 ----------------- .gitmodules | 72 ++++++++++++++++++++++++++++++++++++++++++++ libffi-tarballs | 1 + libraries/array | 1 + libraries/base | 1 + libraries/deepseq | 1 + libraries/directory | 1 + libraries/dph | 1 + libraries/filepath | 1 + libraries/ghc-prim | 1 + libraries/haskell2010 | 1 + libraries/haskell98 | 1 + libraries/hoopl | 1 + libraries/hpc | 1 + libraries/integer-gmp | 1 + libraries/integer-simple | 1 + libraries/old-locale | 1 + libraries/old-time | 1 + libraries/parallel | 1 + libraries/process | 1 + libraries/stm | 1 + libraries/template-haskell | 1 + libraries/unix | 1 + nofib | 1 + packages | 48 ++++++++++++++--------------- utils/haddock | 1 + utils/hsc2hs | 1 + 27 files changed, 120 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 830f2314b237ed25dcbc5ae7bff17122aaed3b95 From git at git.haskell.org Mon Mar 24 09:46:00 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Mar 2014 09:46:00 +0000 (UTC) Subject: [commit: ghc] wip/T8545-ghc-7.8's head updated: Convert all sub-repos into proper submodules (re #8545) (830f231) Message-ID: <20140324094600.679E32406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T8545-ghc-7.8' now includes: 8ea3d18 Simplify handling of the interactive package; fixes Trac #8831 878dee3 Trac #8831 is fixed 935dc72 Fix the treatment of lexically scoped kind variables (Trac #8856) b95b3fb Test Trac #8856 924f749 Unflatten the constraints of an inferred types (Trac #8889) 85bc454 Test Trac #8889 632956d Make sure we occurrence-analyse unfoldings (fixes Trac #8892) c63af7a Apply the kind subst to the (kinds of the) quanitifed tyvars in deriveTyData 11d3f6b Test Trac #8893 46cfa8e Revert "Fix #8745 - GND is now -XSafe compatible." 0e3a551 Follow hs_popcntX changes in ghc-prim bca03d9 Enable popcnt test now when segfault is fixed a617888 Revert "change deriveConstants to use nm in a POSIX way (fixes #8781)" 830f231 Convert all sub-repos into proper submodules (re #8545) From git at git.haskell.org Mon Mar 24 10:02:38 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Mar 2014 10:02:38 +0000 (UTC) Subject: [commit: packages/directory] tag 'directory-1.2.1.0-release' created Message-ID: <20140324100238.B1C762406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/directory New tag : directory-1.2.1.0-release Referencing: ebf3e6e06649832ef6f2cbd38b523408847ae4b4 From git at git.haskell.org Mon Mar 24 10:26:52 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Mar 2014 10:26:52 +0000 (UTC) Subject: [commit: ghc] master: Add missing kind-check for tcEqType on forall-types (74894e0) Message-ID: <20140324102652.4EBE92406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/74894e0bc405247092e865b9541f5f18d26aa015/ghc >--------------------------------------------------------------- commit 74894e0bc405247092e865b9541f5f18d26aa015 Author: Simon Peyton Jones Date: Fri Mar 21 15:24:49 2014 +0000 Add missing kind-check for tcEqType on forall-types This wasn't showing up as a bug, but it was definitely wrong. >--------------------------------------------------------------- 74894e0bc405247092e865b9541f5f18d26aa015 compiler/typecheck/TcType.lhs | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/compiler/typecheck/TcType.lhs b/compiler/typecheck/TcType.lhs index 9b58b4c..08c7a62 100644 --- a/compiler/typecheck/TcType.lhs +++ b/compiler/typecheck/TcType.lhs @@ -245,7 +245,6 @@ checking. It's attached to mutable type variables only. It's knot-tied back to Var.lhs. There is no reason in principle why Var.lhs shouldn't actually have the definition, but it "belongs" here. - Note [Signature skolems] ~~~~~~~~~~~~~~~~~~~~~~~~ Consider this @@ -1008,7 +1007,8 @@ tcEqType ty1 ty2 | Just t2' <- tcView t2 = go env t1 t2' go env (TyVarTy tv1) (TyVarTy tv2) = rnOccL env tv1 == rnOccR env tv2 go _ (LitTy lit1) (LitTy lit2) = lit1 == lit2 - go env (ForAllTy tv1 t1) (ForAllTy tv2 t2) = go (rnBndr2 env tv1 tv2) t1 t2 + go env (ForAllTy tv1 t1) (ForAllTy tv2 t2) = go env (tyVarKind tv1) (tyVarKind tv2) + && go (rnBndr2 env tv1 tv2) t1 t2 go env (AppTy s1 t1) (AppTy s2 t2) = go env s1 s2 && go env t1 t2 go env (FunTy s1 t1) (FunTy s2 t2) = go env s1 s2 && go env t1 t2 go env (TyConApp tc1 ts1) (TyConApp tc2 ts2) = (tc1 == tc2) && gos env ts1 ts2 @@ -1027,7 +1027,8 @@ pickyEqType ty1 ty2 init_env = mkRnEnv2 (mkInScopeSet (tyVarsOfType ty1 `unionVarSet` tyVarsOfType ty2)) go env (TyVarTy tv1) (TyVarTy tv2) = rnOccL env tv1 == rnOccR env tv2 go _ (LitTy lit1) (LitTy lit2) = lit1 == lit2 - go env (ForAllTy tv1 t1) (ForAllTy tv2 t2) = go (rnBndr2 env tv1 tv2) t1 t2 + go env (ForAllTy tv1 t1) (ForAllTy tv2 t2) = go env (tyVarKind tv1) (tyVarKind tv2) + && go (rnBndr2 env tv1 tv2) t1 t2 go env (AppTy s1 t1) (AppTy s2 t2) = go env s1 s2 && go env t1 t2 go env (FunTy s1 t1) (FunTy s2 t2) = go env s1 s2 && go env t1 t2 go env (TyConApp tc1 ts1) (TyConApp tc2 ts2) = (tc1 == tc2) && gos env ts1 ts2 From git at git.haskell.org Mon Mar 24 10:26:54 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Mar 2014 10:26:54 +0000 (UTC) Subject: [commit: ghc] master: Don't export isTcReflCo_maybe (unused) (3f59647) Message-ID: <20140324102654.91C9E2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3f5964770ac20790741638e23f798f0ff8e9e2da/ghc >--------------------------------------------------------------- commit 3f5964770ac20790741638e23f798f0ff8e9e2da Author: Simon Peyton Jones Date: Fri Mar 21 15:25:30 2014 +0000 Don't export isTcReflCo_maybe (unused) >--------------------------------------------------------------- 3f5964770ac20790741638e23f798f0ff8e9e2da compiler/typecheck/TcEvidence.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/typecheck/TcEvidence.lhs b/compiler/typecheck/TcEvidence.lhs index 3471b32..0ad4456 100644 --- a/compiler/typecheck/TcEvidence.lhs +++ b/compiler/typecheck/TcEvidence.lhs @@ -25,7 +25,7 @@ module TcEvidence ( mkTcSymCo, mkTcTransCo, mkTcNthCo, mkTcLRCo, mkTcSubCo, mkTcAxiomRuleCo, tcCoercionKind, coVarsOfTcCo, isEqVar, mkTcCoVarCo, - isTcReflCo, isTcReflCo_maybe, getTcCoVar_maybe, + isTcReflCo, getTcCoVar_maybe, tcCoercionRole, eqVarRole, coercionToTcCoercion ) where From git at git.haskell.org Mon Mar 24 10:26:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Mar 2014 10:26:56 +0000 (UTC) Subject: [commit: ghc] master: For equalities with incompatible kinds, new IrredCan goes in the inert set, not work list (c89c57e) Message-ID: <20140324102657.9E3252406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c89c57e3b72a8f3de9f35e1bd6e0f70d2b18a941/ghc >--------------------------------------------------------------- commit c89c57e3b72a8f3de9f35e1bd6e0f70d2b18a941 Author: Simon Peyton Jones Date: Fri Mar 21 15:32:58 2014 +0000 For equalities with incompatible kinds, new IrredCan goes in the inert set, not work list This change makes the code for canIrred markedly simpler (and more efficient) See Note [Equalities with incompatible kinds]. I don't think there was really a bug here, but I came across it when fixing Trac #8913 >--------------------------------------------------------------- c89c57e3b72a8f3de9f35e1bd6e0f70d2b18a941 compiler/typecheck/TcCanonical.lhs | 41 ++++++++++++++---------------------- 1 file changed, 16 insertions(+), 25 deletions(-) diff --git a/compiler/typecheck/TcCanonical.lhs b/compiler/typecheck/TcCanonical.lhs index 77e48c2..030f9c9 100644 --- a/compiler/typecheck/TcCanonical.lhs +++ b/compiler/typecheck/TcCanonical.lhs @@ -385,22 +385,9 @@ canIrred old_ev ; case classifyPredType (ctEvPred new_ev) of ClassPred cls tys -> canClassNC new_ev cls tys TuplePred tys -> canTuple new_ev tys - EqPred ty1 ty2 - | something_changed old_ty ty1 ty2 -> canEqNC new_ev ty1 ty2 - _ -> continueWith $ - CIrredEvCan { cc_ev = new_ev } } } } - where - -- If the constraint was a kind-mis-matched equality, we must - -- retry canEqNC only if something has changed, otherwise we - -- get an infinite loop - something_changed old_ty new_ty1 new_ty2 - | EqPred old_ty1 old_ty2 <- classifyPredType old_ty - = not ( new_ty1 `tcEqType` old_ty1 - && typeKind new_ty1 `tcEqKind` typeKind old_ty1 - && new_ty2 `tcEqType` old_ty2 - && typeKind new_ty2 `tcEqKind` typeKind old_ty2) - | otherwise - = True + EqPred ty1 ty2 -> canEqNC new_ev ty1 ty2 + _ -> continueWith $ + CIrredEvCan { cc_ev = new_ev } } } } canHole :: CtEvidence -> OccName -> TcS StopOrContinue canHole ev occ @@ -1216,7 +1203,7 @@ canEqTyVarTyVar ev swapped tv1 tv2 co2 -> continueWith (CTyEqCan { cc_ev = new_ev , cc_tyvar = tv1, cc_rhs = xi2 }) | otherwise - -> checkKind ev xi1 k1 xi2 k2 } + -> checkKind new_ev xi1 k1 xi2 k2 } where reorient_me | k1 `tcEqKind` k2 = tv2 `better_than` tv1 @@ -1250,15 +1237,14 @@ checkKind new_ev s1 k1 s2 k2 -- See Note [Equalities with incompatible kinds] = ASSERT( isKind k1 && isKind k2 ) do { traceTcS "canEqLeaf: incompatible kinds" (vcat [ppr k1, ppr k2]) - -- Put the not-currently-soluble thing back onto the work list - ; updWorkListTcS $ extendWorkListNonEq $ - CIrredEvCan { cc_ev = new_ev } - -- Create a derived kind-equality, and solve it ; mw <- newDerived kind_co_loc (mkEqPred k1 k2) ; case mw of - Nothing -> return Stop - Just kev -> canEqNC kev k1 k2 } + Nothing -> return () + Just kev -> emitWorkNC [kev] + + -- Put the not-currently-soluble thing into the inert set + ; continueWith (CIrredEvCan { cc_ev = new_ev }) } where loc = ctev_loc new_ev kind_co_loc = setCtLocOrigin loc (KindEqOrigin s1 s2 (ctLocOrigin loc)) @@ -1298,8 +1284,8 @@ a well-kinded type ill-kinded; and that is bad (eg typeKind can crash, see Trac #7696). So instead for these ill-kinded equalities we generate a CIrredCan, -which keeps it out of the way until a subsequent substitution (on kind -variables, say) re-activates it. +and put it in the inert set, which keeps it out of the way until a +subsequent substitution (on kind variables, say) re-activates it. NB: it is important that the types s1,s2 are flattened and zonked so that their kinds k1, k2 are inert wrt the substitution. That @@ -1308,6 +1294,11 @@ NB: it is important that the types s1,s2 are flattened and zonked E.g. it is WRONG to make an irred (a:k1)~(b:k2) if we already have a substitution k1:=k2 +NB: it's important that the new CIrredCan goes in the inert set rather +than back into the work list. We used to do the latter, but that led +to an infinite loop when we encountered it again, and put it back it +the work list again. + See also Note [Kind orientation for CTyEqCan] and Note [Kind orientation for CFunEqCan] in TcRnTypes From git at git.haskell.org Mon Mar 24 10:27:00 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Mar 2014 10:27:00 +0000 (UTC) Subject: [commit: ghc] master: Comments only (5a51b69) Message-ID: <20140324102700.3BF852406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5a51b6969132b7c31da21c24a063a993b98b51ed/ghc >--------------------------------------------------------------- commit 5a51b6969132b7c31da21c24a063a993b98b51ed Author: Simon Peyton Jones Date: Fri Mar 21 15:26:11 2014 +0000 Comments only >--------------------------------------------------------------- 5a51b6969132b7c31da21c24a063a993b98b51ed compiler/typecheck/TcEvidence.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/typecheck/TcEvidence.lhs b/compiler/typecheck/TcEvidence.lhs index 0ad4456..a31f66a 100644 --- a/compiler/typecheck/TcEvidence.lhs +++ b/compiler/typecheck/TcEvidence.lhs @@ -82,7 +82,7 @@ differences * The kind of a TcCoercion is t1 ~ t2 (resp. Coercible t1 t2) of a Coercion is t1 ~# t2 (resp. t1 ~#R t2) - * UnsafeCo aren't required, but we do have TcPhandomCo + * UnsafeCo aren't required, but we do have TcPhantomCo * Representation invariants are weaker: - we are allowed to have type synonyms in TcTyConAppCo From git at git.haskell.org Mon Mar 24 10:27:02 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Mar 2014 10:27:02 +0000 (UTC) Subject: [commit: ghc] master: Debug tracing only (9f9b10f) Message-ID: <20140324102702.97C012406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9f9b10f65d09823c21bc19a79e14cf27cfe56ea5/ghc >--------------------------------------------------------------- commit 9f9b10f65d09823c21bc19a79e14cf27cfe56ea5 Author: Simon Peyton Jones Date: Fri Mar 21 15:33:10 2014 +0000 Debug tracing only >--------------------------------------------------------------- 9f9b10f65d09823c21bc19a79e14cf27cfe56ea5 compiler/typecheck/TcCanonical.lhs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcCanonical.lhs b/compiler/typecheck/TcCanonical.lhs index 030f9c9..a906270 100644 --- a/compiler/typecheck/TcCanonical.lhs +++ b/compiler/typecheck/TcCanonical.lhs @@ -611,12 +611,14 @@ flattenTyVar f ctxt tv = do { mb_yes <- flattenTyVarOuter f ctxt tv ; case mb_yes of Left tv' -> -- Done - return (ty, mkTcNomReflCo ty) + do { traceTcS "flattenTyVar1" (ppr tv $$ ppr (tyVarKind tv')) + ; return (ty', mkTcNomReflCo ty') } where - ty = mkTyVarTy tv' + ty' = mkTyVarTy tv' Right (ty1, co1) -> -- Recurse do { (ty2, co2) <- flatten f ctxt ty1 + ; traceTcS "flattenTyVar2" (ppr tv $$ ppr ty2) ; return (ty2, co2 `mkTcTransCo` co1) } } From git at git.haskell.org Mon Mar 24 10:27:05 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Mar 2014 10:27:05 +0000 (UTC) Subject: [commit: ghc] master: Flattener preserves synonyms, rewriteEvidence can drop buggy "optimisation" (6ae678e) Message-ID: <20140324102705.606782406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6ae678e31a5fdd3b0bd1f8613fe164012bb630f4/ghc >--------------------------------------------------------------- commit 6ae678e31a5fdd3b0bd1f8613fe164012bb630f4 Author: Simon Peyton Jones Date: Fri Mar 21 15:37:27 2014 +0000 Flattener preserves synonyms, rewriteEvidence can drop buggy "optimisation" There was a special case in rewriteEvidence, looking like: = return (Just (if ctEvPred old_ev `tcEqType` new_pred then old_ev else old_ev { ctev_pred = new_pred })) But this was wrong: old_pred and new_pred might differ in the kind of a TyVar occurrence, in which case tcEqType would not notice, but we really, really want new_pred. This caused Trac #8913. I solved this by dropping the whole test, and instead making the flattener preserve type synonyms. This was easy because TcEvidence has TcTyConAppCo which (unlike) Coercion, handles synonyms. >--------------------------------------------------------------- 6ae678e31a5fdd3b0bd1f8613fe164012bb630f4 compiler/typecheck/TcCanonical.lhs | 23 +++++++++------ compiler/typecheck/TcSMonad.lhs | 31 ++++++++++---------- .../tests/indexed-types/should_compile/T8913.hs | 16 ++++++++++ testsuite/tests/indexed-types/should_compile/all.T | 1 + .../tests/simplCore/should_compile/simpl017.stderr | 14 +++------ 5 files changed, 51 insertions(+), 34 deletions(-) diff --git a/compiler/typecheck/TcCanonical.lhs b/compiler/typecheck/TcCanonical.lhs index a906270..3e23756 100644 --- a/compiler/typecheck/TcCanonical.lhs +++ b/compiler/typecheck/TcCanonical.lhs @@ -475,14 +475,6 @@ flatten :: FlattenMode -- -- Postcondition: Coercion :: Xi ~ TcType -flatten f ctxt ty - | Just ty' <- tcView ty - = do { (xi, co) <- flatten f ctxt ty' - ; if xi `tcEqType` ty' then return (ty,co) - else return (xi,co) } - -- Small tweak for better error messages - -- by preserving type synonyms where possible - flatten _ _ xi@(LitTy {}) = return (xi, mkTcNomReflCo xi) flatten f ctxt (TyVarTy tv) @@ -500,7 +492,9 @@ flatten f ctxt (FunTy ty1 ty2) ; return (mkFunTy xi1 xi2, mkTcFunCo Nominal co1 co2) } flatten f ctxt (TyConApp tc tys) - -- For a normal type constructor or data family application, + -- For * a normal data type application + -- * type synonym application See Note [Flattening synonyms] + -- * data family application -- we just recursively flatten the arguments. | not (isSynFamilyTyCon tc) = do { (xis,cos) <- flattenMany f ctxt tys @@ -538,6 +532,17 @@ flatten _f ctxt ty@(ForAllTy {}) ; return (mkForAllTys tvs rho', foldr mkTcForAllCo co tvs) } \end{code} +Note [Flattening synonyms] +~~~~~~~~~~~~~~~~~~~~~~~~~~ +Suppose + type T a = a -> a +and we want to flatten the type (T (F a)). Then we can safely flatten +the (F a) to a skolem, and return (T fsk). We don't need to expand the +synonym. This works because TcTyConAppCo can deal with synonyms +(unlike TyConAppCo), see Note [TcCoercions] in TcEvidence. + +Not expanding synonyms aggressively improves error messages. + Note [Flattening under a forall] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Under a forall, we diff --git a/compiler/typecheck/TcSMonad.lhs b/compiler/typecheck/TcSMonad.lhs index a92bc95..b7faf15 100644 --- a/compiler/typecheck/TcSMonad.lhs +++ b/compiler/typecheck/TcSMonad.lhs @@ -1724,7 +1724,18 @@ Main purpose: create new evidence for new_pred; Given Already in inert Nothing Not Just new_evidence --} + +Note [Rewriting with Refl] +~~~~~~~~~~~~~~~~~~~~~~~~~~ +If the coercion is just reflexivity then you may re-use the same +variable. But be careful! Although the coercion is Refl, new_pred +may reflect the result of unification alpha := ty, so new_pred might +not _look_ the same as old_pred, and it's vital to proceed from now on +using new_pred. + +The flattener preserves type synonyms, so they should appear in new_pred +as well as in old_pred; that is important for good error messages. + -} rewriteEvidence (CtDerived { ctev_loc = loc }) new_pred _co @@ -1738,15 +1749,8 @@ rewriteEvidence (CtDerived { ctev_loc = loc }) new_pred _co newDerived loc new_pred rewriteEvidence old_ev new_pred co - | isTcReflCo co -- If just reflexivity then you may re-use the same variable - = return (Just (if ctEvPred old_ev `tcEqType` new_pred - then old_ev - else old_ev { ctev_pred = new_pred })) - -- Even if the coercion is Refl, it might reflect the result of unification alpha := ty - -- so old_pred and new_pred might not *look* the same, and it's vital to proceed from - -- now on using new_pred. - -- However, if they *do* look the same, we'd prefer to stick with old_pred - -- then retain the old type, so that error messages come out mentioning synonyms + | isTcReflCo co -- See Note [Rewriting with Refl] + = return (Just (old_ev { ctev_pred = new_pred })) rewriteEvidence (CtGiven { ctev_evtm = old_tm , ctev_loc = loc }) new_pred co = do { new_ev <- newGivenEvVar loc (new_pred, new_tm) -- See Note [Bind new Givens immediately] @@ -1789,12 +1793,9 @@ rewriteEqEvidence old_ev swapped nlhs nrhs lhs_co rhs_co = newDerived loc (mkEqPred nlhs nrhs) | NotSwapped <- swapped - , isTcReflCo lhs_co + , isTcReflCo lhs_co -- See Note [Rewriting with Refl] , isTcReflCo rhs_co - , let new_pred = mkTcEqPred nlhs nrhs - = return (Just (if ctEvPred old_ev `tcEqType` new_pred - then old_ev - else old_ev { ctev_pred = new_pred })) + = return (Just (old_ev { ctev_pred = new_pred })) | CtGiven { ctev_evtm = old_tm , ctev_loc = loc } <- old_ev = do { let new_tm = EvCoercion (lhs_co diff --git a/testsuite/tests/indexed-types/should_compile/T8913.hs b/testsuite/tests/indexed-types/should_compile/T8913.hs new file mode 100644 index 0000000..062a252 --- /dev/null +++ b/testsuite/tests/indexed-types/should_compile/T8913.hs @@ -0,0 +1,16 @@ +{-# OPTIONS_GHC -Wall #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE PolyKinds #-} + +module T8913 where + +class GCat f where + gcat :: f p -> Int + +cat :: (GCat (MyRep a), MyGeneric a) => a -> Int +cat x = gcat (from x) + +class MyGeneric a where + type MyRep a :: * -> * + from :: a -> (MyRep a) p diff --git a/testsuite/tests/indexed-types/should_compile/all.T b/testsuite/tests/indexed-types/should_compile/all.T index 5c156ec..76682ad 100644 --- a/testsuite/tests/indexed-types/should_compile/all.T +++ b/testsuite/tests/indexed-types/should_compile/all.T @@ -240,3 +240,4 @@ test('ClosedFam2', extra_clean(['ClosedFam2.o-boot', 'ClosedFam2.hi-boot']), multimod_compile, ['ClosedFam2', '-v0']) test('T8651', normal, compile, ['']) test('T8889', normal, compile, ['']) +test('T8913', normal, compile, ['']) diff --git a/testsuite/tests/simplCore/should_compile/simpl017.stderr b/testsuite/tests/simplCore/should_compile/simpl017.stderr index b04dbb4..18b0a69 100644 --- a/testsuite/tests/simplCore/should_compile/simpl017.stderr +++ b/testsuite/tests/simplCore/should_compile/simpl017.stderr @@ -12,11 +12,8 @@ simpl017.hs:44:12: In a stmt of a 'do' block: return f simpl017.hs:63:5: - Couldn't match type ?forall v. - [E' RValue (ST s) Int] -> E' v (ST s) Int? - with ?[E (ST t0) Int] -> E' RValue (ST s) Int? - Expected type: [E (ST t0) Int] -> E (ST s) Int - Actual type: forall v. [E (ST s) Int] -> E' v (ST s) Int + Couldn't match expected type ?[E (ST t0) Int] -> E (ST s) Int? + with actual type ?forall v. [E (ST s) Int] -> E' v (ST s) Int? Relevant bindings include a :: forall v. [E (ST s) Int] -> E' v (ST s) Int (bound at simpl017.hs:60:5) @@ -28,11 +25,8 @@ simpl017.hs:63:5: In a stmt of a 'do' block: a [one] `plus` a [one] simpl017.hs:63:19: - Couldn't match type ?forall v. - [E' RValue (ST s) Int] -> E' v (ST s) Int? - with ?[E (ST t1) Int] -> E' RValue (ST s) Int? - Expected type: [E (ST t1) Int] -> E (ST s) Int - Actual type: forall v. [E (ST s) Int] -> E' v (ST s) Int + Couldn't match expected type ?[E (ST t1) Int] -> E (ST s) Int? + with actual type ?forall v. [E (ST s) Int] -> E' v (ST s) Int? Relevant bindings include a :: forall v. [E (ST s) Int] -> E' v (ST s) Int (bound at simpl017.hs:60:5) From git at git.haskell.org Mon Mar 24 10:27:08 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Mar 2014 10:27:08 +0000 (UTC) Subject: [commit: ghc] master: Implicit parameters should not be allowed in class and instance declarations (a8b7b28) Message-ID: <20140324102708.116882406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a8b7b28cdb98d14c6fb43d5ad3293fd4a5c1f8b4/ghc >--------------------------------------------------------------- commit a8b7b28cdb98d14c6fb43d5ad3293fd4a5c1f8b4 Author: Simon Peyton Jones Date: Fri Mar 21 15:55:39 2014 +0000 Implicit parameters should not be allowed in class and instance declarations Trac #8912 pointed out that GHC 7.4 and 7.6 have omitted this test, although 7.2 and earlier had it. This patch puts the test back in, and refactors a little. >--------------------------------------------------------------- a8b7b28cdb98d14c6fb43d5ad3293fd4a5c1f8b4 compiler/typecheck/TcValidity.lhs | 72 +++++++++++--------- testsuite/tests/typecheck/should_fail/T7019.stderr | 2 +- .../tests/typecheck/should_fail/T7019a.stderr | 3 +- testsuite/tests/typecheck/should_fail/T8912.hs | 11 +++ testsuite/tests/typecheck/should_fail/T8912.stderr | 6 ++ testsuite/tests/typecheck/should_fail/all.T | 1 + .../tests/typecheck/should_fail/tcfail041.stderr | 9 +-- .../tests/typecheck/should_fail/tcfail211.stderr | 10 +-- 8 files changed, 70 insertions(+), 44 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a8b7b28cdb98d14c6fb43d5ad3293fd4a5c1f8b4 From git at git.haskell.org Mon Mar 24 10:27:10 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Mar 2014 10:27:10 +0000 (UTC) Subject: [commit: ghc] master: Comments only (5c7ced0) Message-ID: <20140324102710.8D8592406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5c7ced0fd1bb67cadf9a7e5be112701bfcb4631b/ghc >--------------------------------------------------------------- commit 5c7ced0fd1bb67cadf9a7e5be112701bfcb4631b Author: Simon Peyton Jones Date: Mon Mar 24 08:27:20 2014 +0000 Comments only >--------------------------------------------------------------- 5c7ced0fd1bb67cadf9a7e5be112701bfcb4631b compiler/coreSyn/CoreSyn.lhs | 2 +- compiler/simplCore/Simplify.lhs | 10 +++++----- 2 files changed, 6 insertions(+), 6 deletions(-) diff --git a/compiler/coreSyn/CoreSyn.lhs b/compiler/coreSyn/CoreSyn.lhs index 47a993e..defd669 100644 --- a/compiler/coreSyn/CoreSyn.lhs +++ b/compiler/coreSyn/CoreSyn.lhs @@ -395,7 +395,7 @@ Here's another example: f :: T -> Bool f = \(x:t). case x of Bool {} Since T has no data constructors, the case alternatives are of course -empty. However note that 'x' is not bound to a visbily-bottom value; +empty. However note that 'x' is not bound to a visibly-bottom value; it's the *type* that tells us it's going to diverge. Its a bit of a degnerate situation but we do NOT want to replace case x of Bool {} --> error Bool "Inaccessible case" diff --git a/compiler/simplCore/Simplify.lhs b/compiler/simplCore/Simplify.lhs index e1327a6..6105133 100644 --- a/compiler/simplCore/Simplify.lhs +++ b/compiler/simplCore/Simplify.lhs @@ -1734,10 +1734,10 @@ case-binder is evaluated *next*. Previously we just asked that the case-binder is used strictly; but that can change case x of { _ -> error "bad" } --> error "bad" -which is very puzzling if 'x' is later bound to (error "good"). -Where the order of evaluation is specified (via seq or case) -we should respect it. -See also Note [Empty case alternatives] in CoreSyn. +which is very puzzling if 'x' currently lambda-bound, but later gets +let-bound to (error "good"). Where the order of evaluation is +specified (via seq or case) we should respect it. See also Note +[Empty case alternatives] in CoreSyn. So instead we use case_bndr_evald_next to see when f is the *next* thing to be eval'd. This came up when fixing Trac #7542. @@ -1751,7 +1751,7 @@ See also Note [Eta reduction of an eval'd function] in CoreUtils. scrut_is_var _ = False -- True if evaluation of the case_bndr is the next - -- thing to be eval'd. Then dropping the case + -- thing to be eval'd. Then dropping the case is fine. Note [Case elimination: unlifted case] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ From git at git.haskell.org Mon Mar 24 11:07:48 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Mar 2014 11:07:48 +0000 (UTC) Subject: [commit: ghc] master: relnotes: GND is not -XSafe compatible. (73cab20) Message-ID: <20140324110748.CD7762406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/73cab206e0f211b75cb6fd62ab9b6ca8ae0950f2/ghc >--------------------------------------------------------------- commit 73cab206e0f211b75cb6fd62ab9b6ca8ae0950f2 Author: Austin Seipp Date: Mon Mar 24 06:07:27 2014 -0500 relnotes: GND is not -XSafe compatible. Signed-off-by: Austin Seipp >--------------------------------------------------------------- 73cab206e0f211b75cb6fd62ab9b6ca8ae0950f2 docs/users_guide/7.8.1-notes.xml | 5 ----- 1 file changed, 5 deletions(-) diff --git a/docs/users_guide/7.8.1-notes.xml b/docs/users_guide/7.8.1-notes.xml index 94aed3b..36b0ad5 100644 --- a/docs/users_guide/7.8.1-notes.xml +++ b/docs/users_guide/7.8.1-notes.xml @@ -108,11 +108,6 @@ For more information, see . - - As a result of this change, - GeneralizedNewtypeDeriving can now - be used with Safe Haskell. - From git at git.haskell.org Mon Mar 24 11:46:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Mar 2014 11:46:43 +0000 (UTC) Subject: [commit: haddock] tag 'haddock-2.14.1-release' created Message-ID: <20140324114644.047F72406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock New tag : haddock-2.14.1-release Referencing: 09288bd67c22bcf33a2c5977038fd9189906b47b From git at git.haskell.org Mon Mar 24 12:04:33 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Mar 2014 12:04:33 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Add missing kind-check for tcEqType on forall-types (7461c98) Message-ID: <20140324120433.F27492406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/7461c989da4763dcf94dc9b93f5d216d23e030d0/ghc >--------------------------------------------------------------- commit 7461c989da4763dcf94dc9b93f5d216d23e030d0 Author: Simon Peyton Jones Date: Fri Mar 21 15:24:49 2014 +0000 Add missing kind-check for tcEqType on forall-types This wasn't showing up as a bug, but it was definitely wrong. (cherry picked from commit 74894e0bc405247092e865b9541f5f18d26aa015) >--------------------------------------------------------------- 7461c989da4763dcf94dc9b93f5d216d23e030d0 compiler/typecheck/TcType.lhs | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/compiler/typecheck/TcType.lhs b/compiler/typecheck/TcType.lhs index cc4ded4..551b17c 100644 --- a/compiler/typecheck/TcType.lhs +++ b/compiler/typecheck/TcType.lhs @@ -245,7 +245,6 @@ checking. It's attached to mutable type variables only. It's knot-tied back to Var.lhs. There is no reason in principle why Var.lhs shouldn't actually have the definition, but it "belongs" here. - Note [Signature skolems] ~~~~~~~~~~~~~~~~~~~~~~~~ Consider this @@ -1008,7 +1007,8 @@ tcEqType ty1 ty2 | Just t2' <- tcView t2 = go env t1 t2' go env (TyVarTy tv1) (TyVarTy tv2) = rnOccL env tv1 == rnOccR env tv2 go _ (LitTy lit1) (LitTy lit2) = lit1 == lit2 - go env (ForAllTy tv1 t1) (ForAllTy tv2 t2) = go (rnBndr2 env tv1 tv2) t1 t2 + go env (ForAllTy tv1 t1) (ForAllTy tv2 t2) = go env (tyVarKind tv1) (tyVarKind tv2) + && go (rnBndr2 env tv1 tv2) t1 t2 go env (AppTy s1 t1) (AppTy s2 t2) = go env s1 s2 && go env t1 t2 go env (FunTy s1 t1) (FunTy s2 t2) = go env s1 s2 && go env t1 t2 go env (TyConApp tc1 ts1) (TyConApp tc2 ts2) = (tc1 == tc2) && gos env ts1 ts2 @@ -1027,7 +1027,8 @@ pickyEqType ty1 ty2 init_env = mkRnEnv2 (mkInScopeSet (tyVarsOfType ty1 `unionVarSet` tyVarsOfType ty2)) go env (TyVarTy tv1) (TyVarTy tv2) = rnOccL env tv1 == rnOccR env tv2 go _ (LitTy lit1) (LitTy lit2) = lit1 == lit2 - go env (ForAllTy tv1 t1) (ForAllTy tv2 t2) = go (rnBndr2 env tv1 tv2) t1 t2 + go env (ForAllTy tv1 t1) (ForAllTy tv2 t2) = go env (tyVarKind tv1) (tyVarKind tv2) + && go (rnBndr2 env tv1 tv2) t1 t2 go env (AppTy s1 t1) (AppTy s2 t2) = go env s1 s2 && go env t1 t2 go env (FunTy s1 t1) (FunTy s2 t2) = go env s1 s2 && go env t1 t2 go env (TyConApp tc1 ts1) (TyConApp tc2 ts2) = (tc1 == tc2) && gos env ts1 ts2 From git at git.haskell.org Mon Mar 24 12:04:36 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Mar 2014 12:04:36 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: relnotes: GND is not -XSafe compatible. (8f2d7eb) Message-ID: <20140324120436.449122406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/8f2d7eb7db00c4ec66f4dc8ad08744ef267f75d4/ghc >--------------------------------------------------------------- commit 8f2d7eb7db00c4ec66f4dc8ad08744ef267f75d4 Author: Austin Seipp Date: Mon Mar 24 06:07:27 2014 -0500 relnotes: GND is not -XSafe compatible. Signed-off-by: Austin Seipp (cherry picked from commit 73cab206e0f211b75cb6fd62ab9b6ca8ae0950f2) >--------------------------------------------------------------- 8f2d7eb7db00c4ec66f4dc8ad08744ef267f75d4 docs/users_guide/7.8.1-notes.xml | 5 ----- 1 file changed, 5 deletions(-) diff --git a/docs/users_guide/7.8.1-notes.xml b/docs/users_guide/7.8.1-notes.xml index 1738fb7..8f3e8ac 100644 --- a/docs/users_guide/7.8.1-notes.xml +++ b/docs/users_guide/7.8.1-notes.xml @@ -108,11 +108,6 @@ For more information, see . - - As a result of this change, - GeneralizedNewtypeDeriving can now - be used with Safe Haskell. - From git at git.haskell.org Mon Mar 24 12:04:38 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Mar 2014 12:04:38 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Implicit parameters should not be allowed in class and instance declarations (4b1814f) Message-ID: <20140324120438.F17122406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/4b1814f0cdd25711f4ae93aa1a9157815a97bde8/ghc >--------------------------------------------------------------- commit 4b1814f0cdd25711f4ae93aa1a9157815a97bde8 Author: Simon Peyton Jones Date: Fri Mar 21 15:55:39 2014 +0000 Implicit parameters should not be allowed in class and instance declarations Trac #8912 pointed out that GHC 7.4 and 7.6 have omitted this test, although 7.2 and earlier had it. This patch puts the test back in, and refactors a little. (cherry picked from commit a8b7b28cdb98d14c6fb43d5ad3293fd4a5c1f8b4) Conflicts: testsuite/tests/typecheck/should_fail/all.T >--------------------------------------------------------------- 4b1814f0cdd25711f4ae93aa1a9157815a97bde8 compiler/typecheck/TcValidity.lhs | 72 +++++++++++--------- testsuite/tests/typecheck/should_fail/T7019.stderr | 2 +- .../tests/typecheck/should_fail/T7019a.stderr | 3 +- testsuite/tests/typecheck/should_fail/T8912.hs | 11 +++ testsuite/tests/typecheck/should_fail/T8912.stderr | 6 ++ testsuite/tests/typecheck/should_fail/all.T | 1 + .../tests/typecheck/should_fail/tcfail041.stderr | 9 +-- .../tests/typecheck/should_fail/tcfail211.stderr | 10 +-- 8 files changed, 70 insertions(+), 44 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 4b1814f0cdd25711f4ae93aa1a9157815a97bde8 From git at git.haskell.org Mon Mar 24 12:04:41 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Mar 2014 12:04:41 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: For equalities with incompatible kinds, new IrredCan goes in the inert set, not work list (ce2c547) Message-ID: <20140324120443.52CE92406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/ce2c547d5edc471ee70977b3fc7ccb5e55dce0d4/ghc >--------------------------------------------------------------- commit ce2c547d5edc471ee70977b3fc7ccb5e55dce0d4 Author: Simon Peyton Jones Date: Fri Mar 21 15:32:58 2014 +0000 For equalities with incompatible kinds, new IrredCan goes in the inert set, not work list This change makes the code for canIrred markedly simpler (and more efficient) See Note [Equalities with incompatible kinds]. I don't think there was really a bug here, but I came across it when fixing Trac #8913 (cherry picked from commit c89c57e3b72a8f3de9f35e1bd6e0f70d2b18a941) >--------------------------------------------------------------- ce2c547d5edc471ee70977b3fc7ccb5e55dce0d4 compiler/typecheck/TcCanonical.lhs | 41 ++++++++++++++---------------------- 1 file changed, 16 insertions(+), 25 deletions(-) diff --git a/compiler/typecheck/TcCanonical.lhs b/compiler/typecheck/TcCanonical.lhs index 823b37f..bb0b279 100644 --- a/compiler/typecheck/TcCanonical.lhs +++ b/compiler/typecheck/TcCanonical.lhs @@ -385,22 +385,9 @@ canIrred old_ev ; case classifyPredType (ctEvPred new_ev) of ClassPred cls tys -> canClassNC new_ev cls tys TuplePred tys -> canTuple new_ev tys - EqPred ty1 ty2 - | something_changed old_ty ty1 ty2 -> canEqNC new_ev ty1 ty2 - _ -> continueWith $ - CIrredEvCan { cc_ev = new_ev } } } } - where - -- If the constraint was a kind-mis-matched equality, we must - -- retry canEqNC only if something has changed, otherwise we - -- get an infinite loop - something_changed old_ty new_ty1 new_ty2 - | EqPred old_ty1 old_ty2 <- classifyPredType old_ty - = not ( new_ty1 `tcEqType` old_ty1 - && typeKind new_ty1 `tcEqKind` typeKind old_ty1 - && new_ty2 `tcEqType` old_ty2 - && typeKind new_ty2 `tcEqKind` typeKind old_ty2) - | otherwise - = True + EqPred ty1 ty2 -> canEqNC new_ev ty1 ty2 + _ -> continueWith $ + CIrredEvCan { cc_ev = new_ev } } } } canHole :: CtEvidence -> OccName -> TcS StopOrContinue canHole ev occ @@ -1214,7 +1201,7 @@ canEqTyVarTyVar ev swapped tv1 tv2 co2 -> continueWith (CTyEqCan { cc_ev = new_ev , cc_tyvar = tv1, cc_rhs = xi2 }) | otherwise - -> checkKind ev xi1 k1 xi2 k2 } + -> checkKind new_ev xi1 k1 xi2 k2 } where reorient_me | k1 `tcEqKind` k2 = tv2 `better_than` tv1 @@ -1246,15 +1233,14 @@ checkKind new_ev s1 k1 s2 k2 -- See Note [Equalities with incompatible kinds] = ASSERT( isKind k1 && isKind k2 ) do { traceTcS "canEqLeaf: incompatible kinds" (vcat [ppr k1, ppr k2]) - -- Put the not-currently-soluble thing back onto the work list - ; updWorkListTcS $ extendWorkListNonEq $ - CIrredEvCan { cc_ev = new_ev } - -- Create a derived kind-equality, and solve it ; mw <- newDerived kind_co_loc (mkEqPred k1 k2) ; case mw of - Nothing -> return Stop - Just kev -> canEqNC kev k1 k2 } + Nothing -> return () + Just kev -> emitWorkNC [kev] + + -- Put the not-currently-soluble thing into the inert set + ; continueWith (CIrredEvCan { cc_ev = new_ev }) } where loc = ctev_loc new_ev kind_co_loc = setCtLocOrigin loc (KindEqOrigin s1 s2 (ctLocOrigin loc)) @@ -1294,8 +1280,8 @@ a well-kinded type ill-kinded; and that is bad (eg typeKind can crash, see Trac #7696). So instead for these ill-kinded equalities we generate a CIrredCan, -which keeps it out of the way until a subsequent substitution (on kind -variables, say) re-activates it. +and put it in the inert set, which keeps it out of the way until a +subsequent substitution (on kind variables, say) re-activates it. NB: it is important that the types s1,s2 are flattened and zonked so that their kinds k1, k2 are inert wrt the substitution. That @@ -1304,6 +1290,11 @@ NB: it is important that the types s1,s2 are flattened and zonked E.g. it is WRONG to make an irred (a:k1)~(b:k2) if we already have a substitution k1:=k2 +NB: it's important that the new CIrredCan goes in the inert set rather +than back into the work list. We used to do the latter, but that led +to an infinite loop when we encountered it again, and put it back it +the work list again. + See also Note [Kind orientation for CTyEqCan] and Note [Kind orientation for CFunEqCan] in TcRnTypes From git at git.haskell.org Mon Mar 24 12:04:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Mar 2014 12:04:43 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Flattener preserves synonyms, rewriteEvidence can drop buggy "optimisation" (09062bd) Message-ID: <20140324120443.F13AA2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/09062bdf1d0b54f078dd200eb9e04a94b15682b4/ghc >--------------------------------------------------------------- commit 09062bdf1d0b54f078dd200eb9e04a94b15682b4 Author: Simon Peyton Jones Date: Fri Mar 21 15:37:27 2014 +0000 Flattener preserves synonyms, rewriteEvidence can drop buggy "optimisation" There was a special case in rewriteEvidence, looking like: = return (Just (if ctEvPred old_ev `tcEqType` new_pred then old_ev else old_ev { ctev_pred = new_pred })) But this was wrong: old_pred and new_pred might differ in the kind of a TyVar occurrence, in which case tcEqType would not notice, but we really, really want new_pred. This caused Trac #8913. I solved this by dropping the whole test, and instead making the flattener preserve type synonyms. This was easy because TcEvidence has TcTyConAppCo which (unlike) Coercion, handles synonyms. (cherry picked from commit 6ae678e31a5fdd3b0bd1f8613fe164012bb630f4) >--------------------------------------------------------------- 09062bdf1d0b54f078dd200eb9e04a94b15682b4 compiler/typecheck/TcCanonical.lhs | 23 +++++++++------ compiler/typecheck/TcSMonad.lhs | 31 ++++++++++---------- .../tests/indexed-types/should_compile/T8913.hs | 16 ++++++++++ testsuite/tests/indexed-types/should_compile/all.T | 1 + .../tests/simplCore/should_compile/simpl017.stderr | 14 +++------ 5 files changed, 51 insertions(+), 34 deletions(-) diff --git a/compiler/typecheck/TcCanonical.lhs b/compiler/typecheck/TcCanonical.lhs index bb0b279..6cd77b1 100644 --- a/compiler/typecheck/TcCanonical.lhs +++ b/compiler/typecheck/TcCanonical.lhs @@ -475,14 +475,6 @@ flatten :: FlattenMode -- -- Postcondition: Coercion :: Xi ~ TcType -flatten f ctxt ty - | Just ty' <- tcView ty - = do { (xi, co) <- flatten f ctxt ty' - ; if xi `tcEqType` ty' then return (ty,co) - else return (xi,co) } - -- Small tweak for better error messages - -- by preserving type synonyms where possible - flatten _ _ xi@(LitTy {}) = return (xi, mkTcNomReflCo xi) flatten f ctxt (TyVarTy tv) @@ -500,7 +492,9 @@ flatten f ctxt (FunTy ty1 ty2) ; return (mkFunTy xi1 xi2, mkTcFunCo Nominal co1 co2) } flatten f ctxt (TyConApp tc tys) - -- For a normal type constructor or data family application, + -- For * a normal data type application + -- * type synonym application See Note [Flattening synonyms] + -- * data family application -- we just recursively flatten the arguments. | not (isSynFamilyTyCon tc) = do { (xis,cos) <- flattenMany f ctxt tys @@ -538,6 +532,17 @@ flatten _f ctxt ty@(ForAllTy {}) ; return (mkForAllTys tvs rho', foldr mkTcForAllCo co tvs) } \end{code} +Note [Flattening synonyms] +~~~~~~~~~~~~~~~~~~~~~~~~~~ +Suppose + type T a = a -> a +and we want to flatten the type (T (F a)). Then we can safely flatten +the (F a) to a skolem, and return (T fsk). We don't need to expand the +synonym. This works because TcTyConAppCo can deal with synonyms +(unlike TyConAppCo), see Note [TcCoercions] in TcEvidence. + +Not expanding synonyms aggressively improves error messages. + Note [Flattening under a forall] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Under a forall, we diff --git a/compiler/typecheck/TcSMonad.lhs b/compiler/typecheck/TcSMonad.lhs index 1cc18d1..0cb7c92 100644 --- a/compiler/typecheck/TcSMonad.lhs +++ b/compiler/typecheck/TcSMonad.lhs @@ -1724,7 +1724,18 @@ Main purpose: create new evidence for new_pred; Given Already in inert Nothing Not Just new_evidence --} + +Note [Rewriting with Refl] +~~~~~~~~~~~~~~~~~~~~~~~~~~ +If the coercion is just reflexivity then you may re-use the same +variable. But be careful! Although the coercion is Refl, new_pred +may reflect the result of unification alpha := ty, so new_pred might +not _look_ the same as old_pred, and it's vital to proceed from now on +using new_pred. + +The flattener preserves type synonyms, so they should appear in new_pred +as well as in old_pred; that is important for good error messages. + -} rewriteEvidence (CtDerived { ctev_loc = loc }) new_pred _co @@ -1738,15 +1749,8 @@ rewriteEvidence (CtDerived { ctev_loc = loc }) new_pred _co newDerived loc new_pred rewriteEvidence old_ev new_pred co - | isTcReflCo co -- If just reflexivity then you may re-use the same variable - = return (Just (if ctEvPred old_ev `tcEqType` new_pred - then old_ev - else old_ev { ctev_pred = new_pred })) - -- Even if the coercion is Refl, it might reflect the result of unification alpha := ty - -- so old_pred and new_pred might not *look* the same, and it's vital to proceed from - -- now on using new_pred. - -- However, if they *do* look the same, we'd prefer to stick with old_pred - -- then retain the old type, so that error messages come out mentioning synonyms + | isTcReflCo co -- See Note [Rewriting with Refl] + = return (Just (old_ev { ctev_pred = new_pred })) rewriteEvidence (CtGiven { ctev_evtm = old_tm , ctev_loc = loc }) new_pred co = do { new_ev <- newGivenEvVar loc (new_pred, new_tm) -- See Note [Bind new Givens immediately] @@ -1789,12 +1793,9 @@ rewriteEqEvidence old_ev swapped nlhs nrhs lhs_co rhs_co = newDerived loc (mkEqPred nlhs nrhs) | NotSwapped <- swapped - , isTcReflCo lhs_co + , isTcReflCo lhs_co -- See Note [Rewriting with Refl] , isTcReflCo rhs_co - , let new_pred = mkTcEqPred nlhs nrhs - = return (Just (if ctEvPred old_ev `tcEqType` new_pred - then old_ev - else old_ev { ctev_pred = new_pred })) + = return (Just (old_ev { ctev_pred = new_pred })) | CtGiven { ctev_evtm = old_tm , ctev_loc = loc } <- old_ev = do { let new_tm = EvCoercion (lhs_co diff --git a/testsuite/tests/indexed-types/should_compile/T8913.hs b/testsuite/tests/indexed-types/should_compile/T8913.hs new file mode 100644 index 0000000..062a252 --- /dev/null +++ b/testsuite/tests/indexed-types/should_compile/T8913.hs @@ -0,0 +1,16 @@ +{-# OPTIONS_GHC -Wall #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE PolyKinds #-} + +module T8913 where + +class GCat f where + gcat :: f p -> Int + +cat :: (GCat (MyRep a), MyGeneric a) => a -> Int +cat x = gcat (from x) + +class MyGeneric a where + type MyRep a :: * -> * + from :: a -> (MyRep a) p diff --git a/testsuite/tests/indexed-types/should_compile/all.T b/testsuite/tests/indexed-types/should_compile/all.T index 5c156ec..76682ad 100644 --- a/testsuite/tests/indexed-types/should_compile/all.T +++ b/testsuite/tests/indexed-types/should_compile/all.T @@ -240,3 +240,4 @@ test('ClosedFam2', extra_clean(['ClosedFam2.o-boot', 'ClosedFam2.hi-boot']), multimod_compile, ['ClosedFam2', '-v0']) test('T8651', normal, compile, ['']) test('T8889', normal, compile, ['']) +test('T8913', normal, compile, ['']) diff --git a/testsuite/tests/simplCore/should_compile/simpl017.stderr b/testsuite/tests/simplCore/should_compile/simpl017.stderr index b04dbb4..18b0a69 100644 --- a/testsuite/tests/simplCore/should_compile/simpl017.stderr +++ b/testsuite/tests/simplCore/should_compile/simpl017.stderr @@ -12,11 +12,8 @@ simpl017.hs:44:12: In a stmt of a 'do' block: return f simpl017.hs:63:5: - Couldn't match type ?forall v. - [E' RValue (ST s) Int] -> E' v (ST s) Int? - with ?[E (ST t0) Int] -> E' RValue (ST s) Int? - Expected type: [E (ST t0) Int] -> E (ST s) Int - Actual type: forall v. [E (ST s) Int] -> E' v (ST s) Int + Couldn't match expected type ?[E (ST t0) Int] -> E (ST s) Int? + with actual type ?forall v. [E (ST s) Int] -> E' v (ST s) Int? Relevant bindings include a :: forall v. [E (ST s) Int] -> E' v (ST s) Int (bound at simpl017.hs:60:5) @@ -28,11 +25,8 @@ simpl017.hs:63:5: In a stmt of a 'do' block: a [one] `plus` a [one] simpl017.hs:63:19: - Couldn't match type ?forall v. - [E' RValue (ST s) Int] -> E' v (ST s) Int? - with ?[E (ST t1) Int] -> E' RValue (ST s) Int? - Expected type: [E (ST t1) Int] -> E (ST s) Int - Actual type: forall v. [E (ST s) Int] -> E' v (ST s) Int + Couldn't match expected type ?[E (ST t1) Int] -> E (ST s) Int? + with actual type ?forall v. [E (ST s) Int] -> E' v (ST s) Int? Relevant bindings include a :: forall v. [E (ST s) Int] -> E' v (ST s) Int (bound at simpl017.hs:60:5) From git at git.haskell.org Mon Mar 24 14:23:20 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 24 Mar 2014 14:23:20 +0000 (UTC) Subject: [commit: ghc] master: Eliminate redundant seq's (Trac #8900) (0b6fa3e) Message-ID: <20140324142322.2D75F2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0b6fa3e95078797f87302780a85607decab806fb/ghc >--------------------------------------------------------------- commit 0b6fa3e95078797f87302780a85607decab806fb Author: Simon Peyton Jones Date: Mon Mar 24 14:22:50 2014 +0000 Eliminate redundant seq's (Trac #8900) This patch makes the simplifier eliminate a redundant seq like case x of y -> ...y.... where y is used strictly. GHC used to do this, but I made it less aggressive in commit 28d9a03253e8fd613667526a170b684f2017d299 (Jan 2013) However #8900 shows that doing so sometimes loses good transformations; and the transformation is valid according to "A semantics for imprecise exceptions". So I'm restoring the old behaviour. See Note [Eliminating redundant seqs] >--------------------------------------------------------------- 0b6fa3e95078797f87302780a85607decab806fb compiler/simplCore/Simplify.lhs | 99 ++++++++++++++++++++++----------------- 1 file changed, 55 insertions(+), 44 deletions(-) diff --git a/compiler/simplCore/Simplify.lhs b/compiler/simplCore/Simplify.lhs index 6105133..75ed48f 100644 --- a/compiler/simplCore/Simplify.lhs +++ b/compiler/simplCore/Simplify.lhs @@ -28,7 +28,7 @@ import DataCon ( DataCon, dataConWorkId, dataConRepStrictness --import TyCon ( isEnumerationTyCon ) -- temporalily commented out. See #8326 import CoreMonad ( Tick(..), SimplifierMode(..) ) import CoreSyn -import Demand ( StrictSig(..), dmdTypeDepth ) +import Demand ( StrictSig(..), dmdTypeDepth, isStrictDmd ) import PprCore ( pprParendExpr, pprCoreExpr ) import CoreUnfold import CoreUtils @@ -1701,22 +1701,26 @@ comparison operations (e.g. in (>=) for Int.Int32) Note [Case elimination: lifted case] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -We also make sure that we deal with this very common case, -where x has a lifted type: +If a case over a lifted type has a single alternative, and is being used +as a strict 'let' (all isDeadBinder bndrs), we may want to do this +transformation: - case e of - x -> ...x... + case e of r ===> let r = e in ...r... + _ -> ...r... -Here we are using the case as a strict let; if x is used only once -then we want to inline it. We have to be careful that this doesn't -make the program terminate when it would have diverged before, so we -check that (a) 'e' is already evaluated (it may so if e is a variable) - Specifically we check (exprIsHNF e) + Specifically we check (exprIsHNF e). In this case + we can just allocate the WHNF directly with a let. or (b) 'x' is not used at all and e is ok-for-speculation + The ok-for-spec bit checks that we don't lose any + exceptions or divergence +or + (c) 'x' is used strictly in the body, and 'e' is a variable + Then we can just subtitute 'e' for 'x' in the body. + See Note [Eliminating redundant seqs] -For the (b), consider +For (b), the "not used at all" test is important. Consider case (case a ># b of { True -> (p,q); False -> (q,p) }) of r -> blah The scrutinee is ok-for-speculation (it looks inside cases), but we do @@ -1725,33 +1729,42 @@ not want to transform to in blah because that builds an unnecessary thunk. -Note [Case binder next] -~~~~~~~~~~~~~~~~~~~~~~~ -If we have - case e of f { _ -> f e1 e2 } -then we can safely do CaseElim. The main criterion is that the -case-binder is evaluated *next*. Previously we just asked that -the case-binder is used strictly; but that can change +Note [Eliminating redundant seqs] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +If we have this: + case x of r { _ -> ..r.. } +where 'r' is used strictly in (..r..), the case is effectively a 'seq' +on 'x', but since 'r' is used strictly anyway, we can safely transform to + (...x...) + +Note that this can change the error behaviour. For example, we might +transform case x of { _ -> error "bad" } --> error "bad" -which is very puzzling if 'x' currently lambda-bound, but later gets -let-bound to (error "good"). Where the order of evaluation is -specified (via seq or case) we should respect it. See also Note -[Empty case alternatives] in CoreSyn. +which is might be puzzling if 'x' currently lambda-bound, but later gets +let-bound to (error "good"). + +Nevertheless, the paper "A semantics for impecise exceptions" allows +this transformation. If you want to fix the evaluation order, use +'pseq'. See Trac #8900 for an example where the loss of this +transformation bit us in practice. + +See also Note [Empty case alternatives] in CoreSyn. -So instead we use case_bndr_evald_next to see when f is the *next* -thing to be eval'd. This came up when fixing Trac #7542. -See also Note [Eta reduction of an eval'd function] in CoreUtils. +Just for reference, the original code (added Jan 13) looked like this: + || case_bndr_evald_next rhs + + case_bndr_evald_next :: CoreExpr -> Bool + -- See Note [Case binder next] + case_bndr_evald_next (Var v) = v == case_bndr + case_bndr_evald_next (Cast e _) = case_bndr_evald_next e + case_bndr_evald_next (App e _) = case_bndr_evald_next e + case_bndr_evald_next (Case e _ _ _) = case_bndr_evald_next e + case_bndr_evald_next _ = False - For reference, the old code was an extra disjunct in elim_lifted - || (strict_case_bndr && scrut_is_var scrut) - strict_case_bndr = isStrictDmd (idDemandInfo case_bndr) - scrut_is_var (Cast s _) = scrut_is_var s - scrut_is_var (Var _) = True - scrut_is_var _ = False +(This came up when fixing Trac #7542. See also Note [Eta reduction of +an eval'd function] in CoreUtils.) - -- True if evaluation of the case_bndr is the next - -- thing to be eval'd. Then dropping the case is fine. Note [Case elimination: unlifted case] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -1875,8 +1888,9 @@ rebuildCase env scrut case_bndr [(_, bndrs, rhs)] cont elim_lifted -- See Note [Case elimination: lifted case] = exprIsHNF scrut || (is_plain_seq && ok_for_spec) - -- Note: not the same as exprIsHNF - || case_bndr_evald_next rhs + -- Note: not the same as exprIsHNF + || (strict_case_bndr && scrut_is_var scrut) + -- See Note [Eliminating redundant seqs] elim_unlifted | is_plain_seq = exprOkForSideEffects scrut @@ -1889,16 +1903,13 @@ rebuildCase env scrut case_bndr [(_, bndrs, rhs)] cont ok_for_spec = exprOkForSpeculation scrut is_plain_seq = isDeadBinder case_bndr -- Evaluation *only* for effect + strict_case_bndr = isStrictDmd (idDemandInfo case_bndr) + + scrut_is_var :: CoreExpr -> Bool + scrut_is_var (Cast s _) = scrut_is_var s + scrut_is_var (Var _) = True + scrut_is_var _ = False - case_bndr_evald_next :: CoreExpr -> Bool - -- See Note [Case binder next] - case_bndr_evald_next (Var v) = v == case_bndr - case_bndr_evald_next (Cast e _) = case_bndr_evald_next e - case_bndr_evald_next (App e _) = case_bndr_evald_next e - case_bndr_evald_next (Case e _ _ _) = case_bndr_evald_next e - case_bndr_evald_next _ = False - -- Could add a case for Let, - -- but I'm worried it could become expensive -------------------------------------------------- -- 3. Try seq rules; see Note [User-defined RULES for seq] in MkId From git at git.haskell.org Tue Mar 25 13:08:50 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Mar 2014 13:08:50 +0000 (UTC) Subject: [commit: packages/stm] ghc-7.8: Integrate tests with TravisCI job (c0de155) Message-ID: <20140325130850.D72372406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/stm On branch : ghc-7.8 Link : http://git.haskell.org/packages/stm.git/commitdiff/c0de155171f6462ca5e862c4dd6bf9c535742143 >--------------------------------------------------------------- commit c0de155171f6462ca5e862c4dd6bf9c535742143 Author: Herbert Valerio Riedel Date: Tue Mar 25 14:05:47 2014 +0100 Integrate tests with TravisCI job A simple bash runner-script is included as the GHC testsuite runner isn't available for the Travis-CI job Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- c0de155171f6462ca5e862c4dd6bf9c535742143 .travis.yml | 6 +++- tests/{stm046.stderr => T2411.stdout.ignore} | 0 tests/runtests.sh | 44 ++++++++++++++++++++++++++ tests/stm050.hs | 6 ++-- 4 files changed, 53 insertions(+), 3 deletions(-) diff --git a/.travis.yml b/.travis.yml index 034a8cc..4d77888 100644 --- a/.travis.yml +++ b/.travis.yml @@ -1,5 +1,5 @@ env: - - GHCVER=6.12.3 +# - GHCVER=6.12.3 - GHCVER=7.0.1 - GHCVER=7.0.2 - GHCVER=7.0.3 @@ -11,6 +11,7 @@ env: - GHCVER=7.6.1 - GHCVER=7.6.2 - GHCVER=7.6.3 + - GHCVER=7.8.1 - GHCVER=head matrix: @@ -27,6 +28,7 @@ install: - cabal-1.18 update script: + - cabal-1.18 install random - cabal-1.18 configure -v2 - cabal-1.18 build - cabal-1.18 check @@ -39,3 +41,5 @@ script: echo "expected '$SRC_TGZ' not found"; exit 1; fi + - cabal-1.18 install random + - tests/runtests.sh \ No newline at end of file diff --git a/tests/stm046.stderr b/tests/T2411.stdout.ignore similarity index 100% copy from tests/stm046.stderr copy to tests/T2411.stdout.ignore diff --git a/tests/runtests.sh b/tests/runtests.sh new file mode 100755 index 0000000..4124fdc --- /dev/null +++ b/tests/runtests.sh @@ -0,0 +1,44 @@ +#!/bin/bash + +# Simple runner script used for TravisCI (where GHC's testsuite runner isn't available) + +set -e + +die () { + echo "ERROR: $1" >&2; + exit 1; +} + +[ -f tests/runtests.sh ] && cd tests/ + +[ -f runtests.sh ] || die "must be called from inside tests folder" + +for T in *.hs;do + T=${T%.hs} + + echo "== running test '$T'" + + ghc --make -threaded -O2 --make ${T}.hs + + if ./${T} > ${T}.stdout.run 2> ${T}.stderr.run + then + echo "${T} exited with code $?" + fi + + for FD in stdout stderr; do + if [ -f "${T}.${FD}.ignore" ]; then + echo "ignoring ${FD} output" + continue + fi + echo "validate ${FD} output..." + if [ -f "${T}.${FD}" ]; then REF="${T}.${FD}"; else REF=/dev/null; fi + diff -w -u ${REF} ${T}.${FD}.run + done + + echo "> '${T}' PASSED" + + rm ${T}.hi ${T}.o ${T} ${T}.stdout.run ${T}.stderr.run +done + +echo "----------------------------------------------------------------------------" +echo "all tests PASSED!" diff --git a/tests/stm050.hs b/tests/stm050.hs index ebb8209..cefeb3d 100644 --- a/tests/stm050.hs +++ b/tests/stm050.hs @@ -200,8 +200,10 @@ directoryPoster2 n state The DirectoryService main process. -} directoryService - = do [s] <- getArgs - let n = read s :: Int + = do args <- getArgs + n <- case args of + [] -> return 10000 + [s] -> return (read s :: Int) c <- atomically (newTChan) t <- atomically (newTVar []) From git at git.haskell.org Tue Mar 25 13:13:46 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Mar 2014 13:13:46 +0000 (UTC) Subject: [commit: packages/stm] ghc-7.8: Fix-up travis-CI script (8d3cd89) Message-ID: <20140325131347.047702406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/stm On branch : ghc-7.8 Link : http://git.haskell.org/packages/stm.git/commitdiff/8d3cd89a338fca607220b507a9a9c52ce1a09596 >--------------------------------------------------------------- commit 8d3cd89a338fca607220b507a9a9c52ce1a09596 Author: Herbert Valerio Riedel Date: Tue Mar 25 14:13:34 2014 +0100 Fix-up travis-CI script Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 8d3cd89a338fca607220b507a9a9c52ce1a09596 .travis.yml | 6 ++---- 1 file changed, 2 insertions(+), 4 deletions(-) diff --git a/.travis.yml b/.travis.yml index 4d77888..1ca0118 100644 --- a/.travis.yml +++ b/.travis.yml @@ -28,15 +28,13 @@ install: - cabal-1.18 update script: - - cabal-1.18 install random - cabal-1.18 configure -v2 - cabal-1.18 build - cabal-1.18 check - cabal-1.18 sdist - export SRC_TGZ=$(cabal-1.18 info . | awk '{print $2 ".tar.gz";exit}') ; - cd dist/; - if [ -f "$SRC_TGZ" ]; then - cabal-1.18 install "$SRC_TGZ"; + if [ -f "dist/$SRC_TGZ" ]; then + cabal-1.18 install "dist/$SRC_TGZ"; else echo "expected '$SRC_TGZ' not found"; exit 1; From git at git.haskell.org Tue Mar 25 14:17:00 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Mar 2014 14:17:00 +0000 (UTC) Subject: [commit: ghc] master: Improve the desugaring of RULE left-hand-sides (fixes Trac #8848) (41ba7cc) Message-ID: <20140325141700.473C62406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/41ba7ccb742278de0abf32cb7571c71b150997a3/ghc >--------------------------------------------------------------- commit 41ba7ccb742278de0abf32cb7571c71b150997a3 Author: Simon Peyton Jones Date: Tue Mar 25 14:12:59 2014 +0000 Improve the desugaring of RULE left-hand-sides (fixes Trac #8848) I've added detailed comments with Note [Decomposing the left-hand side of a RULE] The result is a noticeable improvement. Previously * we rejected a perfectly decent SPECIALISE (Trac #8848) * and for something like f :: (Eq a) => b -> a -> a {-# SPECIALISE f :: b -> [Int] -> [Int] #-} we ended up with RULE f ($fdEqList $dfEqInt) = f_spec whereas we wanted RULES forall (d:Eq [Int]). f d = f_spec >--------------------------------------------------------------- 41ba7ccb742278de0abf32cb7571c71b150997a3 compiler/deSugar/DsBinds.lhs | 149 +++++++++++++------- .../tests/simplCore/should_compile/simpl016.stderr | 2 +- 2 files changed, 98 insertions(+), 53 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 41ba7ccb742278de0abf32cb7571c71b150997a3 From git at git.haskell.org Tue Mar 25 14:35:06 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Mar 2014 14:35:06 +0000 (UTC) Subject: [commit: ghc] master: Comments only (b800e52) Message-ID: <20140325143506.9607B2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b800e52ac503c27912260cab4a14022c09f98ded/ghc >--------------------------------------------------------------- commit b800e52ac503c27912260cab4a14022c09f98ded Author: Simon Peyton Jones Date: Tue Mar 25 14:20:10 2014 +0000 Comments only >--------------------------------------------------------------- b800e52ac503c27912260cab4a14022c09f98ded compiler/coreSyn/CoreSubst.lhs | 12 +++++------- compiler/typecheck/TcDeriv.lhs | 2 +- compiler/typecheck/TcSimplify.lhs | 2 +- 3 files changed, 7 insertions(+), 9 deletions(-) diff --git a/compiler/coreSyn/CoreSubst.lhs b/compiler/coreSyn/CoreSubst.lhs index ff24e2e..ef601a2 100644 --- a/compiler/coreSyn/CoreSubst.lhs +++ b/compiler/coreSyn/CoreSubst.lhs @@ -1118,11 +1118,10 @@ 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] +has a compulsory unfolding. Also see Note [Desugaring coerce as cast] in Desugar %************************************************************************ %* * @@ -1302,10 +1301,9 @@ exprIsLiteral_maybe env@(_, id_unf) e _ -> Nothing \end{code} -Note [exprIsLiteral_maybe] +Note [exprIsLambda_maybe] ~~~~~~~~~~~~~~~~~~~~~~~~~~ - -This function will, given an expression `e`, try to turn it into the form +exprIsLambda_maybe will, given an expression `e`, try to turn it into the form `Lam v e'` (returned as `Just (v,e')`). Besides using lambdas, it looks through casts (using the Push rule), and it unfolds function calls if the unfolding has a greater arity than arguments are present. @@ -1314,10 +1312,10 @@ Currently, it is used in Rules.match, and is required to make "map coerce = coerce" match. \begin{code} --- See Note [exprIsLiteral_maybe] exprIsLambda_maybe :: InScopeEnv -> CoreExpr -> Maybe (Var, CoreExpr) + -- See Note [exprIsLambda_maybe] --- The simpe case: It is a lambda +-- The simple case: It is a lambda already exprIsLambda_maybe _ (Lam x e) = Just (x, e) diff --git a/compiler/typecheck/TcDeriv.lhs b/compiler/typecheck/TcDeriv.lhs index 9cd2cf1..1e19bd4 100644 --- a/compiler/typecheck/TcDeriv.lhs +++ b/compiler/typecheck/TcDeriv.lhs @@ -1492,7 +1492,7 @@ badCon con msg = ptext (sLit "Constructor") <+> quotes (ppr con) <+> msg Note [Check that the type variable is truly universal] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ For Functor, Foldable, Traversable, we must check that the *last argument* -of the type constructor is used truly universally. Example +of the type constructor is used truly universally quantified. Example data T a b where T1 :: a -> b -> T a b -- Fine! Vanilla H-98 diff --git a/compiler/typecheck/TcSimplify.lhs b/compiler/typecheck/TcSimplify.lhs index af57729..fa7c75d 100644 --- a/compiler/typecheck/TcSimplify.lhs +++ b/compiler/typecheck/TcSimplify.lhs @@ -493,7 +493,7 @@ This only half-works, but then let-generalisation only half-works. * * *********************************************************************************** -See note [Simplifying RULE consraints] in TcRule +See note [Simplifying RULE constraints] in TcRule Note [RULE quanfification over equalities] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ From git at git.haskell.org Tue Mar 25 14:35:09 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Mar 2014 14:35:09 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #8848 (88d9452) Message-ID: <20140325143509.71D4D2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/88d94524f46df7c99214cde7e2952aacdd3fb6cc/ghc >--------------------------------------------------------------- commit 88d94524f46df7c99214cde7e2952aacdd3fb6cc Author: Simon Peyton Jones Date: Tue Mar 25 14:34:44 2014 +0000 Test Trac #8848 >--------------------------------------------------------------- 88d94524f46df7c99214cde7e2952aacdd3fb6cc testsuite/tests/simplCore/should_compile/T8848.hs | 26 ++++++++++++++++++++ .../tests/simplCore/should_compile/T8848.stderr | 17 +++++++++++++ testsuite/tests/simplCore/should_compile/T8848a.hs | 19 ++++++++++++++ .../tests/simplCore/should_compile/T8848a.stderr | 8 ++++++ testsuite/tests/simplCore/should_compile/all.T | 2 ++ 5 files changed, 72 insertions(+) diff --git a/testsuite/tests/simplCore/should_compile/T8848.hs b/testsuite/tests/simplCore/should_compile/T8848.hs new file mode 100644 index 0000000..1ddfe94 --- /dev/null +++ b/testsuite/tests/simplCore/should_compile/T8848.hs @@ -0,0 +1,26 @@ +{-# LANGUAGE KindSignatures, GADTs, DataKinds, FlexibleInstances, FlexibleContexts #-} +{-# OPTIONS_GHC -fno-warn-missing-methods #-} + +module T8848 where + +import qualified Control.Applicative as A +import qualified Data.Functor as Fun + +data Nat = S Nat | Z + +data Shape (rank :: Nat) a where + Nil :: Shape Z a + (:*) :: a -> Shape r a -> Shape (S r) a + +instance A.Applicative (Shape Z) where +instance A.Applicative (Shape r)=> A.Applicative (Shape (S r)) where +instance Fun.Functor (Shape Z) where +instance (Fun.Functor (Shape r)) => Fun.Functor (Shape (S r)) where + +map2 :: (A.Applicative (Shape r))=> (a->b ->c) -> (Shape r a) -> (Shape r b) -> (Shape r c ) +map2 = \f l r -> A.pure f A.<*> l A.<*> r + +{-# SPECIALIZE map2 :: (a->b->c)-> (Shape (S (S Z)) a )-> Shape (S (S Z)) b -> Shape (S (S Z)) c #-} + +map3 :: (a->b->c)-> (Shape (S (S Z)) a )-> Shape (S (S Z)) b -> Shape (S (S Z)) c +map3 x y z = map2 x y z \ No newline at end of file diff --git a/testsuite/tests/simplCore/should_compile/T8848.stderr b/testsuite/tests/simplCore/should_compile/T8848.stderr new file mode 100644 index 0000000..1a62868 --- /dev/null +++ b/testsuite/tests/simplCore/should_compile/T8848.stderr @@ -0,0 +1,17 @@ +Rule fired: Class op fmap +Rule fired: Class op fmap +Rule fired: Class op pure +Rule fired: Class op <*> +Rule fired: Class op <*> +Rule fired: SPEC T8848.map2 +Rule fired: Class op $p1Applicative +Rule fired: Class op <*> +Rule fired: Class op $p1Applicative +Rule fired: Class op <*> +Rule fired: Class op $p1Applicative +Rule fired: Class op fmap +Rule fired: Class op <*> +Rule fired: Class op $p1Applicative +Rule fired: Class op fmap +Rule fired: Class op <*> +Rule fired: SPEC T8848.$fFunctorShape ['T8848.Z] diff --git a/testsuite/tests/simplCore/should_compile/T8848a.hs b/testsuite/tests/simplCore/should_compile/T8848a.hs new file mode 100644 index 0000000..81e757f --- /dev/null +++ b/testsuite/tests/simplCore/should_compile/T8848a.hs @@ -0,0 +1,19 @@ +module T8848a where + +f :: Ord a => b -> a -> a +f y x = x + +{-# SPECIALISE f :: b -> [Int] -> [Int] #-} + +{- Specialised badly: + +"SPEC Spec.f" [ALWAYS] + forall (@ b_aX7). + Spec.f @ b_aX7 + @ [GHC.Types.Int] + (GHC.Classes.$fOrd[] + @ GHC.Types.Int + (GHC.Classes.$fEq[] @ GHC.Types.Int GHC.Classes.$fEqInt) + GHC.Classes.$fOrdInt) + = Spec.f_$sf @ b_aX7 +-} \ No newline at end of file diff --git a/testsuite/tests/simplCore/should_compile/T8848a.stderr b/testsuite/tests/simplCore/should_compile/T8848a.stderr new file mode 100644 index 0000000..781d537 --- /dev/null +++ b/testsuite/tests/simplCore/should_compile/T8848a.stderr @@ -0,0 +1,8 @@ + +==================== Tidy Core rules ==================== +"SPEC T8848a.f" [ALWAYS] + forall (@ b) ($dOrd :: GHC.Classes.Ord [GHC.Types.Int]). + T8848a.f @ b @ [GHC.Types.Int] $dOrd + = T8848a.f_$sf @ b + + diff --git a/testsuite/tests/simplCore/should_compile/all.T b/testsuite/tests/simplCore/should_compile/all.T index 9e77926..5f8ddd9 100644 --- a/testsuite/tests/simplCore/should_compile/all.T +++ b/testsuite/tests/simplCore/should_compile/all.T @@ -202,3 +202,5 @@ test('T8832', extra_clean(['T8832.hi', 'T8832a.o']), run_command, ['$MAKE -s --no-print-directory T8832']) +test('T8848', only_ways(['optasm']), compile, ['-ddump-rule-firings']) +test('T8848a', only_ways(['optasm']), compile, ['-ddump-rules']) From git at git.haskell.org Tue Mar 25 14:59:49 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Mar 2014 14:59:49 +0000 (UTC) Subject: [commit: ghc] master: Suppress uniques for simpl016 to normalise debug output (2d1ecd2) Message-ID: <20140325145949.B98722406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2d1ecd2b0395bc3de4424c1a9833454f3fe14fec/ghc >--------------------------------------------------------------- commit 2d1ecd2b0395bc3de4424c1a9833454f3fe14fec Author: Simon Peyton Jones Date: Tue Mar 25 14:59:38 2014 +0000 Suppress uniques for simpl016 to normalise debug output >--------------------------------------------------------------- 2d1ecd2b0395bc3de4424c1a9833454f3fe14fec testsuite/tests/simplCore/should_compile/all.T | 2 +- testsuite/tests/simplCore/should_compile/simpl016.stderr | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/simplCore/should_compile/all.T b/testsuite/tests/simplCore/should_compile/all.T index 5f8ddd9..7239ffc 100644 --- a/testsuite/tests/simplCore/should_compile/all.T +++ b/testsuite/tests/simplCore/should_compile/all.T @@ -16,7 +16,7 @@ test('simpl012', normal, compile, ['']) test('simpl013', normal, compile, ['']) test('simpl014', normal, compile, ['']) test('simpl015', only_ways(['optasm']), compile, ['']) -test('simpl016', normal, compile, ['']) +test('simpl016', normal, compile, ['-dsuppress-uniques']) test('simpl017', normal, compile_fail, ['']) test('simpl018', normal, compile, ['']) test('simpl019', normal, compile, ['']) diff --git a/testsuite/tests/simplCore/should_compile/simpl016.stderr b/testsuite/tests/simplCore/should_compile/simpl016.stderr index 20e941f..2ac4e4f 100644 --- a/testsuite/tests/simplCore/should_compile/simpl016.stderr +++ b/testsuite/tests/simplCore/should_compile/simpl016.stderr @@ -1,4 +1,4 @@ simpl016.hs:5:1: Warning: Forall'd constraint ?Num b? is not bound in RULE lhs - delta' @ Int @ b $dEq_aYH + delta' @ Int @ b $dEq From git at git.haskell.org Tue Mar 25 19:12:29 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Mar 2014 19:12:29 +0000 (UTC) Subject: [commit: packages/stm] ghc-7.8: Tweak tests/runtests.sh to make it pass for older GHCs (85108e2) Message-ID: <20140325191230.501A42406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/stm On branch : ghc-7.8 Link : http://git.haskell.org/packages/stm.git/commitdiff/85108e21d0a6359fc1f3f29f365c05c59278db30 >--------------------------------------------------------------- commit 85108e21d0a6359fc1f3f29f365c05c59278db30 Author: Herbert Valerio Riedel Date: Tue Mar 25 20:11:08 2014 +0100 Tweak tests/runtests.sh to make it pass for older GHCs Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 85108e21d0a6359fc1f3f29f365c05c59278db30 tests/runtests.sh | 30 +++++++++++++++++++++++++++--- 1 file changed, 27 insertions(+), 3 deletions(-) diff --git a/tests/runtests.sh b/tests/runtests.sh index 4124fdc..2111c9a 100755 --- a/tests/runtests.sh +++ b/tests/runtests.sh @@ -4,9 +4,28 @@ set -e +GHCVER=$(ghc --numeric-version) + +echo "using GHC version: $GHCVER" + +# checks if GHC version >= $1 +ghc_minver () { + [ "$1" = "$(echo -e "$1\n${GHCVER}" | sort -V | head -n1)" ] +} + +# hard-coded exceptions +may_fail () { + if [ "$1" = "stm064" ] && ! ghc_minver "7.6"; then + echo "EXPECTED FAIL: '$1' may fail for GHC < 7.6" + return 0 + fi + + return 1 +} + die () { - echo "ERROR: $1" >&2; - exit 1; + echo "ERROR: $1" >&2 + exit 1 } [ -f tests/runtests.sh ] && cd tests/ @@ -30,9 +49,14 @@ for T in *.hs;do echo "ignoring ${FD} output" continue fi + + # fixup typo in exception message for older GHCs + sed -i 's,Transacional invariant,Transactional invariant,g' "${T}.${FD}.run" + echo "validate ${FD} output..." if [ -f "${T}.${FD}" ]; then REF="${T}.${FD}"; else REF=/dev/null; fi - diff -w -u ${REF} ${T}.${FD}.run + + diff -w -u "${REF}" "${T}.${FD}.run" || may_fail "${T}" done echo "> '${T}' PASSED" From git at git.haskell.org Tue Mar 25 20:45:12 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Mar 2014 20:45:12 +0000 (UTC) Subject: [commit: packages/stm] ghc-7.8: stm064 was only fixed in GHC 7.6.2 (143b02d) Message-ID: <20140325204512.974CD2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/stm On branch : ghc-7.8 Link : http://git.haskell.org/packages/stm.git/commitdiff/143b02dabc32ec20509fbf98573f826ce1d1d23b >--------------------------------------------------------------- commit 143b02dabc32ec20509fbf98573f826ce1d1d23b Author: Herbert Valerio Riedel Date: Tue Mar 25 21:35:35 2014 +0100 stm064 was only fixed in GHC 7.6.2 This should fix the Travis-CI job for good Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 143b02dabc32ec20509fbf98573f826ce1d1d23b tests/runtests.sh | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/tests/runtests.sh b/tests/runtests.sh index 2111c9a..9da51aa 100755 --- a/tests/runtests.sh +++ b/tests/runtests.sh @@ -15,8 +15,8 @@ ghc_minver () { # hard-coded exceptions may_fail () { - if [ "$1" = "stm064" ] && ! ghc_minver "7.6"; then - echo "EXPECTED FAIL: '$1' may fail for GHC < 7.6" + if [ "$1" = "stm064" ] && ! ghc_minver "7.6.2"; then + echo "EXPECTED FAIL: '$1' may fail for GHC < 7.6.2" return 0 fi From git at git.haskell.org Tue Mar 25 21:32:41 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Mar 2014 21:32:41 +0000 (UTC) Subject: [commit: packages/stm] master: Replace deprecated pragmas by current LANGUAGE pragmas (52c3028) Message-ID: <20140325213241.F1AA42406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/stm On branch : master Link : http://git.haskell.org/packages/stm.git/commitdiff/52c3028aff127fd957cdaf1ec7605fc533a59961 >--------------------------------------------------------------- commit 52c3028aff127fd957cdaf1ec7605fc533a59961 Author: Herbert Valerio Riedel Date: Tue Mar 25 22:28:17 2014 +0100 Replace deprecated pragmas by current LANGUAGE pragmas This reduces the amount of compile warnings for the stm test-cases Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 52c3028aff127fd957cdaf1ec7605fc533a59961 tests/stm046.hs | 2 +- tests/stm047.hs | 2 +- tests/stm048.hs | 2 +- tests/stm049.hs | 2 +- tests/stm052.hs | 2 +- tests/stm060.hs | 2 +- tests/stm061.hs | 2 +- 7 files changed, 7 insertions(+), 7 deletions(-) diff --git a/tests/stm046.hs b/tests/stm046.hs index e2fc39e..2a57877 100644 --- a/tests/stm046.hs +++ b/tests/stm046.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE PatternSignatures #-} +{-# LANGUAGE ScopedTypeVariables #-} module Main where import GHC.Conc diff --git a/tests/stm047.hs b/tests/stm047.hs index 8caaf1d..6199b9a 100644 --- a/tests/stm047.hs +++ b/tests/stm047.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE PatternSignatures #-} +{-# LANGUAGE ScopedTypeVariables #-} module Main where import GHC.Conc diff --git a/tests/stm048.hs b/tests/stm048.hs index 48a63af..be65219 100644 --- a/tests/stm048.hs +++ b/tests/stm048.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE PatternSignatures #-} +{-# LANGUAGE ScopedTypeVariables #-} module Main where import GHC.Conc diff --git a/tests/stm049.hs b/tests/stm049.hs index 60d5dd1..f1d5b6b 100644 --- a/tests/stm049.hs +++ b/tests/stm049.hs @@ -1,6 +1,6 @@ -- STM stress test -{-# OPTIONS -fffi #-} +{-# LANGUAGE ForeignFunctionInterface #-} module Main (main) where import Control.Concurrent diff --git a/tests/stm052.hs b/tests/stm052.hs index 5e37a93..7a47a49 100644 --- a/tests/stm052.hs +++ b/tests/stm052.hs @@ -1,6 +1,6 @@ -- STM stress test -{-# OPTIONS -fffi #-} +{-# LANGUAGE ForeignFunctionInterface #-} module Main (main) where import Foreign diff --git a/tests/stm060.hs b/tests/stm060.hs index 707bf04..5ebdaf0 100644 --- a/tests/stm060.hs +++ b/tests/stm060.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE PatternSignatures #-} +{-# LANGUAGE ScopedTypeVariables #-} module Main where import GHC.Conc diff --git a/tests/stm061.hs b/tests/stm061.hs index 4c29558..70606a1 100644 --- a/tests/stm061.hs +++ b/tests/stm061.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE PatternSignatures #-} +{-# LANGUAGE ScopedTypeVariables #-} module Main where import GHC.Conc From git at git.haskell.org Tue Mar 25 21:32:43 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Mar 2014 21:32:43 +0000 (UTC) Subject: [commit: packages/stm] master's head updated: Replace deprecated pragmas by current LANGUAGE pragmas (52c3028) Message-ID: <20140325213243.4E1872406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/stm Branch 'master' now includes: c0de155 Integrate tests with TravisCI job 8d3cd89 Fix-up travis-CI script 85108e2 Tweak tests/runtests.sh to make it pass for older GHCs 143b02d stm064 was only fixed in GHC 7.6.2 52c3028 Replace deprecated pragmas by current LANGUAGE pragmas From git at git.haskell.org Tue Mar 25 22:01:08 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Mar 2014 22:01:08 +0000 (UTC) Subject: [commit: packages/stm] tag 'stm-2.4.3-release' created Message-ID: <20140325220108.E97F02406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/stm New tag : stm-2.4.3-release Referencing: e6ae12c7127c2a765403eb8b99eeb66082bfc427 From git at git.haskell.org Tue Mar 25 22:02:36 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 25 Mar 2014 22:02:36 +0000 (UTC) Subject: [commit: ghc] master: Typos in comments (ce335ce) Message-ID: <20140325220236.D7E312406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ce335cee31de24d817246a87935bb9ffd21168f9/ghc >--------------------------------------------------------------- commit ce335cee31de24d817246a87935bb9ffd21168f9 Author: Gabor Greif Date: Tue Mar 25 22:52:13 2014 +0100 Typos in comments >--------------------------------------------------------------- ce335cee31de24d817246a87935bb9ffd21168f9 compiler/simplCore/Simplify.lhs | 4 ++-- compiler/typecheck/TcCanonical.lhs | 2 +- compiler/typecheck/TcSimplify.lhs | 4 ++-- compiler/typecheck/TcValidity.lhs | 4 ++-- 4 files changed, 7 insertions(+), 7 deletions(-) diff --git a/compiler/simplCore/Simplify.lhs b/compiler/simplCore/Simplify.lhs index 75ed48f..02470be 100644 --- a/compiler/simplCore/Simplify.lhs +++ b/compiler/simplCore/Simplify.lhs @@ -1717,7 +1717,7 @@ or exceptions or divergence or (c) 'x' is used strictly in the body, and 'e' is a variable - Then we can just subtitute 'e' for 'x' in the body. + Then we can just substitute 'e' for 'x' in the body. See Note [Eliminating redundant seqs] For (b), the "not used at all" test is important. Consider @@ -1744,7 +1744,7 @@ transform which is might be puzzling if 'x' currently lambda-bound, but later gets let-bound to (error "good"). -Nevertheless, the paper "A semantics for impecise exceptions" allows +Nevertheless, the paper "A semantics for imprecise exceptions" allows this transformation. If you want to fix the evaluation order, use 'pseq'. See Trac #8900 for an example where the loss of this transformation bit us in practice. diff --git a/compiler/typecheck/TcCanonical.lhs b/compiler/typecheck/TcCanonical.lhs index 3e23756..cc53d03 100644 --- a/compiler/typecheck/TcCanonical.lhs +++ b/compiler/typecheck/TcCanonical.lhs @@ -1303,7 +1303,7 @@ NB: it is important that the types s1,s2 are flattened and zonked NB: it's important that the new CIrredCan goes in the inert set rather than back into the work list. We used to do the latter, but that led -to an infinite loop when we encountered it again, and put it back it +to an infinite loop when we encountered it again, and put it back in the work list again. See also Note [Kind orientation for CTyEqCan] and diff --git a/compiler/typecheck/TcSimplify.lhs b/compiler/typecheck/TcSimplify.lhs index fa7c75d..c4308f6 100644 --- a/compiler/typecheck/TcSimplify.lhs +++ b/compiler/typecheck/TcSimplify.lhs @@ -495,9 +495,9 @@ This only half-works, but then let-generalisation only half-works. See note [Simplifying RULE constraints] in TcRule -Note [RULE quanfification over equalities] +Note [RULE quantification over equalities] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -Decideing which equalities to quantify over is tricky: +Deciding which equalities to quantify over is tricky: * We do not want to quantify over insoluble equalities (Int ~ Bool) (a) because we prefer to report a LHS type error (b) because if such things end up in 'givens' we get a bogus diff --git a/compiler/typecheck/TcValidity.lhs b/compiler/typecheck/TcValidity.lhs index d4fc09e..84453eb 100644 --- a/compiler/typecheck/TcValidity.lhs +++ b/compiler/typecheck/TcValidity.lhs @@ -443,8 +443,8 @@ instances is a bit subtle. If we allowed instance (?x::Int, Eq a) => Foo [a] where ... then when we saw (e :: (?x::Int) => t) -it would be unclear how to discharge all the potential usas of the ?x -in e. For example, a constraint Foo [Int] might come out of e,and +it would be unclear how to discharge all the potential uses of the ?x +in e. For example, a constraint Foo [Int] might come out of e, and applying the instance decl would show up two uses of ?x. Trac #8912. \begin{code} From git at git.haskell.org Wed Mar 26 17:59:56 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 26 Mar 2014 17:59:56 +0000 (UTC) Subject: [commit: ghc] master: Add flags to control memcpy and memset inlining (11b31c3) Message-ID: <20140326175956.CCB6F2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/11b31c3c9bbe05486e6532ec6217c8cf2587adbb/ghc >--------------------------------------------------------------- commit 11b31c3c9bbe05486e6532ec6217c8cf2587adbb Author: Johan Tibell Date: Wed Mar 26 17:08:29 2014 +0100 Add flags to control memcpy and memset inlining This adds -fmax-inline-memcpy-insns and -fmax-inline-memset-insns. These flags control when we inline calls to memcpy/memset with statically known arguments. The flag naming style is taken from GCC and the same limit is used by both GCC and LLVM. >--------------------------------------------------------------- 11b31c3c9bbe05486e6532ec6217c8cf2587adbb compiler/main/DynFlags.hs | 20 +++++-- compiler/nativeGen/X86/CodeGen.hs | 56 +++++++++++--------- docs/users_guide/flags.xml | 24 +++++++++ testsuite/.gitignore | 1 + testsuite/tests/codeGen/should_gen_asm/all.T | 2 + .../tests/codeGen/should_gen_asm/memset-unroll.asm | 14 +++++ .../tests/codeGen/should_gen_asm/memset-unroll.cmm | 8 +++ 7 files changed, 95 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 11b31c3c9bbe05486e6532ec6217c8cf2587adbb From git at git.haskell.org Thu Mar 27 13:49:59 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Mar 2014 13:49:59 +0000 (UTC) Subject: [commit: ghc] master: Fixup help text (f868254) Message-ID: <20140327135000.0269F2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f86825462bf1d14ea6aad1029a5ec9d7a08049df/ghc >--------------------------------------------------------------- commit f86825462bf1d14ea6aad1029a5ec9d7a08049df Author: Simon Marlow Date: Thu Mar 20 15:46:41 2014 +0000 Fixup help text >--------------------------------------------------------------- f86825462bf1d14ea6aad1029a5ec9d7a08049df configure.ac | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/configure.ac b/configure.ac index 9d55194..0a4df23 100644 --- a/configure.ac +++ b/configure.ac @@ -367,7 +367,7 @@ AS_IF([test "x$with_system_libffi" = "xyes"], AC_SUBST(UseSystemLibFFI) AC_ARG_WITH([ffi-includes], -[AC_HELP_STRING([--with-ffi-includes=ARG] +[AC_HELP_STRING([--with-ffi-includes=ARG], [Find includes for libffi in ARG [default=system default]]) ], [ @@ -382,7 +382,7 @@ AC_ARG_WITH([ffi-includes], AC_SUBST(FFIIncludeDir) AC_ARG_WITH([ffi-libraries], -[AC_HELP_STRING([--with-ffi-libraries=ARG] +[AC_HELP_STRING([--with-ffi-libraries=ARG], [Find libffi in ARG [default=system default]]) ], [ From git at git.haskell.org Thu Mar 27 13:50:02 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Mar 2014 13:50:02 +0000 (UTC) Subject: [commit: ghc] master: Don't perform permission checks for scripts named with -ghci-script (#6017) (a6f2c85) Message-ID: <20140327135002.8F9662406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a6f2c852d49313fa8acea2deb3741ab86c6ef995/ghc >--------------------------------------------------------------- commit a6f2c852d49313fa8acea2deb3741ab86c6ef995 Author: Simon Marlow Date: Thu Mar 20 21:47:22 2014 +0000 Don't perform permission checks for scripts named with -ghci-script (#6017) The user explicitly requested this script on the command-line, so it's unnecessary to require that the script is also owned by the user. Also, it is currently impossible to make a GHCi wrapper that invokes a custom script without first making a copy of the script to circumvent the permissions check, which seems wrong. >--------------------------------------------------------------- a6f2c852d49313fa8acea2deb3741ab86c6ef995 ghc/InteractiveUI.hs | 26 ++++++++++++++++++-------- ghc/ghc-bin.cabal.in | 1 + 2 files changed, 19 insertions(+), 8 deletions(-) diff --git a/ghc/InteractiveUI.hs b/ghc/InteractiveUI.hs index 1476f95..b41c2db 100644 --- a/ghc/InteractiveUI.hs +++ b/ghc/InteractiveUI.hs @@ -455,13 +455,18 @@ runGHCi paths maybe_exprs = do canonicalizePath' fp = liftM Just (canonicalizePath fp) `catchIO` \_ -> return Nothing - sourceConfigFile :: FilePath -> GHCi () - sourceConfigFile file = do + sourceConfigFile :: (FilePath, Bool) -> GHCi () + sourceConfigFile (file, check_perms) = do exists <- liftIO $ doesFileExist file when exists $ do - dir_ok <- liftIO $ checkPerms (getDirectory file) - file_ok <- liftIO $ checkPerms file - when (dir_ok && file_ok) $ do + perms_ok <- + if not check_perms + then return True + else do + dir_ok <- liftIO $ checkPerms (getDirectory file) + file_ok <- liftIO $ checkPerms file + return (dir_ok && file_ok) + when perms_ok $ do either_hdl <- liftIO $ tryIO (openFile file ReadMode) case either_hdl of Left _e -> return () @@ -479,9 +484,14 @@ runGHCi paths maybe_exprs = do setGHCContextFromGHCiState when (read_dot_files) $ do - mcfgs0 <- sequence $ [ current_dir, app_user_dir, home_dir ] ++ map (return . Just ) (ghciScripts dflags) - mcfgs <- liftIO $ mapM canonicalizePath' (catMaybes mcfgs0) - mapM_ sourceConfigFile $ nub $ catMaybes mcfgs + mcfgs0 <- catMaybes <$> sequence [ current_dir, app_user_dir, home_dir ] + let mcfgs1 = zip mcfgs0 (repeat True) + ++ zip (ghciScripts dflags) (repeat False) + -- False says "don't check permissions". We don't + -- require that a script explicitly added by + -- -ghci-script is owned by the current user. (#6017) + mcfgs <- liftIO $ mapM (\(f, b) -> (,b) <$> canonicalizePath' f) mcfgs1 + mapM_ sourceConfigFile $ nub $ [ (f,b) | (Just f, b) <- mcfgs ] -- nub, because we don't want to read .ghci twice if the -- CWD is $HOME. diff --git a/ghc/ghc-bin.cabal.in b/ghc/ghc-bin.cabal.in index 561c55c..68338f3 100644 --- a/ghc/ghc-bin.cabal.in +++ b/ghc/ghc-bin.cabal.in @@ -48,6 +48,7 @@ Executable ghc Extensions: ForeignFunctionInterface, UnboxedTuples, FlexibleInstances, + TupleSections, MagicHash Extensions: CPP, PatternGuards, NondecreasingIndentation From git at git.haskell.org Thu Mar 27 13:50:05 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Mar 2014 13:50:05 +0000 (UTC) Subject: [commit: ghc] master: Pass custom CC and LD opts to Cabal when configuring a package (e7f26cd) Message-ID: <20140327135005.A9AB42406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e7f26cd3e7e9eb92e3eb3457730e635747b43050/ghc >--------------------------------------------------------------- commit e7f26cd3e7e9eb92e3eb3457730e635747b43050 Author: Simon Marlow Date: Thu Mar 27 12:29:48 2014 +0000 Pass custom CC and LD opts to Cabal when configuring a package Cabal compiles a program to check for the existence of foreign libraries, so it needs to know our custom options, if any. >--------------------------------------------------------------- e7f26cd3e7e9eb92e3eb3457730e635747b43050 rules/build-package-data.mk | 14 +++++++++++--- 1 file changed, 11 insertions(+), 3 deletions(-) diff --git a/rules/build-package-data.mk b/rules/build-package-data.mk index c53a084..aea2adb 100644 --- a/rules/build-package-data.mk +++ b/rules/build-package-data.mk @@ -49,9 +49,17 @@ endif # We filter out -Werror from SRC_CC_OPTS, because when configure tests # for a feature it may not generate warning-free C code, and thus may # think that the feature doesn't exist if -Werror is on. -$1_$2_CONFIGURE_OPTS += --configure-option=CFLAGS="$$(filter-out -Werror,$$(SRC_CC_OPTS)) $$(CONF_CC_OPTS_STAGE$3) $$($1_CC_OPTS) $$($1_$2_CC_OPTS) $$(SRC_CC_WARNING_OPTS)" -$1_$2_CONFIGURE_OPTS += --configure-option=LDFLAGS="$$(SRC_LD_OPTS) $$(CONF_GCC_LINKER_OPTS_STAGE$3) $$($1_LD_OPTS) $$($1_$2_LD_OPTS)" -$1_$2_CONFIGURE_OPTS += --configure-option=CPPFLAGS="$$(SRC_CPP_OPTS) $$(CONF_CPP_OPTS_STAGE$3) $$($1_CPP_OPTS) $$($1_$2_CPP_OPTS)" +$1_$2_CONFIGURE_CFLAGS = $$(filter-out -Werror,$$(SRC_CC_OPTS)) $$(CONF_CC_OPTS_STAGE$3) $$($1_CC_OPTS) $$($1_$2_CC_OPTS) $$(SRC_CC_WARNING_OPTS) +$1_$2_CONFIGURE_LDFLAGS = $$(SRC_LD_OPTS) $$(CONF_GCC_LINKER_OPTS_STAGE$3) $$($1_LD_OPTS) $$($1_$2_LD_OPTS) +$1_$2_CONFIGURE_CPPFLAGS = $$(SRC_CPP_OPTS) $$(CONF_CPP_OPTS_STAGE$3) $$($1_CPP_OPTS) $$($1_$2_CPP_OPTS) + +$1_$2_CONFIGURE_OPTS += --configure-option=CFLAGS="$$($1_$2_CONFIGURE_CFLAGS)" +$1_$2_CONFIGURE_OPTS += --configure-option=LDFLAGS="$$($1_$2_CONFIGURE_LDFLAGS)" +$1_$2_CONFIGURE_OPTS += --configure-option=CPPFLAGS="$$($1_$2_CONFIGURE_CPPFLAGS)" + +# Also pass these as gcc-options, because Cabal uses them to check for +# the existence of foreign libraries. +$1_$2_CONFIGURE_OPTS += --gcc-options="$$($1_$2_CONFIGURE_CFLAGS) $$($1_$2_CONFIGURE_LDFLAGS)" ifneq "$$(ICONV_INCLUDE_DIRS)" "" $1_$2_CONFIGURE_OPTS += --configure-option=--with-iconv-includes="$$(ICONV_INCLUDE_DIRS)" From git at git.haskell.org Thu Mar 27 13:50:08 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Mar 2014 13:50:08 +0000 (UTC) Subject: [commit: ghc] master: --with-gcc overrides CC_STAGE0 when not cross-compiling (#8498) (6189c76) Message-ID: <20140327135008.302842406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6189c7674fc5c735db1a446d0b222369a3767369/ghc >--------------------------------------------------------------- commit 6189c7674fc5c735db1a446d0b222369a3767369 Author: Simon Marlow Date: Thu Mar 20 15:47:18 2014 +0000 --with-gcc overrides CC_STAGE0 when not cross-compiling (#8498) >--------------------------------------------------------------- 6189c7674fc5c735db1a446d0b222369a3767369 aclocal.m4 | 18 +++++++++++++++++- configure.ac | 7 ++++++- 2 files changed, 23 insertions(+), 2 deletions(-) diff --git a/aclocal.m4 b/aclocal.m4 index c2a7ba2..be38031 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -643,6 +643,10 @@ AC_ARG_WITH($2, else $1=$withval fi + + # Remember that we set this manually. Used to override CC_STAGE0 + # and friends later, if we are not cross-compiling. + With_$2=$withval ], [ if test "$HostOS" != "mingw32" @@ -685,6 +689,10 @@ AC_ARG_WITH($2, else $1=$withval fi + + # Remember that we set this manually. Used to override CC_STAGE0 + # and friends later, if we are not cross-compiling. + With_$2=$withval ], [ if test "$HostOS" != "mingw32" @@ -2058,7 +2066,8 @@ AC_DEFUN([FIND_GCC],[ $1="$CC" else FP_ARG_WITH_PATH_GNU_PROG_OPTIONAL([$1], [$2], [$3]) - # From Xcode 5 on, OS X command line tools do not include gcc anymore. Use clang. + # From Xcode 5 on, OS X command line tools do not include gcc + # anymore. Use clang. if test -z "$$1" then FP_ARG_WITH_PATH_GNU_PROG_OPTIONAL([$1], [clang], [clang]) @@ -2071,4 +2080,11 @@ AC_DEFUN([FIND_GCC],[ AC_SUBST($1) ]) +AC_DEFUN([MAYBE_OVERRIDE_STAGE0],[ + if test ! -z "$With_$1" -a "$CrossCompiling" != "YES"; then + AC_MSG_NOTICE([Not cross-compiling, so --with-$1 also sets $2]) + $2=$With_$1 + fi +]) + # LocalWords: fi diff --git a/configure.ac b/configure.ac index 0a4df23..9f0edaa 100644 --- a/configure.ac +++ b/configure.ac @@ -474,6 +474,11 @@ FIND_GCC([WhatGccIsCalled], [gcc], [gcc]) CC="$WhatGccIsCalled" export CC +# If --with-gcc was used, and we're not cross-compiling, then it also +# applies to the stage0 compiler. +MAYBE_OVERRIDE_STAGE0([gcc],[CC_STAGE0]) +MAYBE_OVERRIDE_STAGE0([ar],[AR_STAGE0]) + dnl ** Which ld to use? dnl -------------------------------------------------------------- FP_ARG_WITH_PATH_GNU_PROG([LD], [ld], [ld]) @@ -583,8 +588,8 @@ FP_PROG_LD_FILELIST FPTOOLS_SET_C_LD_FLAGS([target],[CFLAGS],[LDFLAGS],[IGNORE_LINKER_LD_FLAGS],[CPPFLAGS]) FPTOOLS_SET_C_LD_FLAGS([build],[CONF_CC_OPTS_STAGE0],[CONF_GCC_LINKER_OPTS_STAGE0],[CONF_LD_LINKER_OPTS_STAGE0],[CONF_CPP_OPTS_STAGE0]) FPTOOLS_SET_C_LD_FLAGS([target],[CONF_CC_OPTS_STAGE1],[CONF_GCC_LINKER_OPTS_STAGE1],[CONF_LD_LINKER_OPTS_STAGE1],[CONF_CPP_OPTS_STAGE1]) -# Stage 3 won't be supported by cross-compilation FPTOOLS_SET_C_LD_FLAGS([target],[CONF_CC_OPTS_STAGE2],[CONF_GCC_LINKER_OPTS_STAGE2],[CONF_LD_LINKER_OPTS_STAGE2],[CONF_CPP_OPTS_STAGE2]) +# Stage 3 won't be supported by cross-compilation FP_GCC_EXTRA_FLAGS From git at git.haskell.org Thu Mar 27 13:50:10 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Mar 2014 13:50:10 +0000 (UTC) Subject: [commit: ghc] master: Include EXTRA_LD_OPTS (amongst other things) when linking programs (975e9cb) Message-ID: <20140327135010.91B0F2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/975e9cb8e7744a0750bb6c8763f628e05672643e/ghc >--------------------------------------------------------------- commit 975e9cb8e7744a0750bb6c8763f628e05672643e Author: Simon Marlow Date: Tue Mar 25 14:32:28 2014 +0000 Include EXTRA_LD_OPTS (amongst other things) when linking programs One problem was that we weren't including $1_$2_DIST_LD_OPTS when linking a program, which looks to be accidental: it was being defined but not used anywhere. This meant that setting $1_$2_EXTRA_LD_OPTS, for example, had no effect. This commit straightens out the handling of LD_OPTS to be consistent with the way we handle CC_OPTS and HC_OPTS. >--------------------------------------------------------------- 975e9cb8e7744a0750bb6c8763f628e05672643e rules/build-prog.mk | 4 ++-- rules/distdir-way-opts.mk | 49 ++++++++++++++++++++++++++------------------- 2 files changed, 30 insertions(+), 23 deletions(-) diff --git a/rules/build-prog.mk b/rules/build-prog.mk index c6780d1..399369e 100644 --- a/rules/build-prog.mk +++ b/rules/build-prog.mk @@ -259,11 +259,11 @@ $1/$2/build/tmp/$$($1_$2_PROG).dll : $$($1_$2_$$($1_$2_PROGRAM_WAY)_HS_OBJS) $$( else ifeq "$$($1_$2_LINK_WITH_GCC)" "NO" $1/$2/build/tmp/$$($1_$2_PROG) : $$($1_$2_$$($1_$2_PROGRAM_WAY)_HS_OBJS) $$($1_$2_$$($1_$2_PROGRAM_WAY)_C_OBJS) $$($1_$2_$$($1_$2_PROGRAM_WAY)_S_OBJS) $$($1_$2_OTHER_OBJS) | $$$$(dir $$$$@)/. - $$(call cmd,$1_$2_HC) -o $$@ $$($1_$2_$$($1_$2_PROGRAM_WAY)_ALL_HC_OPTS) $$(LD_OPTS) $$($1_$2_$$($1_$2_PROGRAM_WAY)_GHC_LD_OPTS) $$($1_$2_$$($1_$2_PROGRAM_WAY)_HS_OBJS) $$($1_$2_$$($1_$2_PROGRAM_WAY)_C_OBJS) $$($1_$2_$$($1_$2_PROGRAM_WAY)_S_OBJS) $$($1_$2_OTHER_OBJS) $$(addprefix -l,$$($1_$2_EXTRA_LIBRARIES)) + $$(call cmd,$1_$2_HC) -o $$@ $$($1_$2_$$($1_$2_PROGRAM_WAY)_ALL_HC_OPTS) $$($1_$2_$$($1_$2_PROGRAM_WAY)_GHC_LD_OPTS) $$($1_$2_$$($1_$2_PROGRAM_WAY)_HS_OBJS) $$($1_$2_$$($1_$2_PROGRAM_WAY)_C_OBJS) $$($1_$2_$$($1_$2_PROGRAM_WAY)_S_OBJS) $$($1_$2_OTHER_OBJS) $$(addprefix -l,$$($1_$2_EXTRA_LIBRARIES)) else $1/$2/build/tmp/$$($1_$2_PROG) : $$($1_$2_$$($1_$2_PROGRAM_WAY)_HS_OBJS) $$($1_$2_$$($1_$2_PROGRAM_WAY)_C_OBJS) $$($1_$2_$$($1_$2_PROGRAM_WAY)_S_OBJS) $$($1_$2_OTHER_OBJS) | $$$$(dir $$$$@)/. - $$(call cmd,$1_$2_CC) -o $$@ $$($1_$2_$$($1_$2_PROGRAM_WAY)_ALL_CC_OPTS) $$(LD_OPTS) $$($1_$2_$$($1_$2_PROGRAM_WAY)_HS_OBJS) $$($1_$2_$$($1_$2_PROGRAM_WAY)_C_OBJS) $$($1_$2_$$($1_$2_PROGRAM_WAY)_S_OBJS) $$($1_$2_OTHER_OBJS) $$($1_$2_$$($1_$2_PROGRAM_WAY)_EXTRA_CC_OPTS) $$(addprefix -l,$$($1_$2_EXTRA_LIBRARIES)) + $$(call cmd,$1_$2_CC) -o $$@ $$($1_$2_$$($1_$2_PROGRAM_WAY)_ALL_CC_OPTS) $$($1_$2_$$($1_$2_PROGRAM_WAY)_ALL_LD_OPTS) $$($1_$2_$$($1_$2_PROGRAM_WAY)_HS_OBJS) $$($1_$2_$$($1_$2_PROGRAM_WAY)_C_OBJS) $$($1_$2_$$($1_$2_PROGRAM_WAY)_S_OBJS) $$($1_$2_OTHER_OBJS) $$($1_$2_$$($1_$2_PROGRAM_WAY)_EXTRA_CC_OPTS) $$(addprefix -l,$$($1_$2_EXTRA_LIBRARIES)) endif endif diff --git a/rules/distdir-way-opts.mk b/rules/distdir-way-opts.mk index 8c0377e..93bc60b 100644 --- a/rules/distdir-way-opts.mk +++ b/rules/distdir-way-opts.mk @@ -131,20 +131,6 @@ endif endif endif -ifeq "$3" "dyn" -ifneq "$4" "0" -ifeq "$$(TargetElf)" "YES" -$1_$2_$3_GHC_LD_OPTS += \ - -fno-use-rpaths \ - $$(foreach d,$$($1_$2_TRANSITIVE_DEPS),-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_DEPS),-optl-Wl$$(comma)-rpath -optl-Wl$$(comma)'@loader_path/../$$d') -endif -endif -endif - $1_$2_$3_ALL_CC_OPTS = \ $$(WAY_$3_CC_OPTS) \ $$($1_$2_DIST_GCC_CC_OPTS) \ @@ -154,13 +140,20 @@ $1_$2_$3_ALL_CC_OPTS = \ $$(EXTRA_CC_OPTS) $1_$2_$3_GHC_CC_OPTS = \ - $$(addprefix -optc, \ - $$(WAY_$3_CC_OPTS) \ - $$($1_$2_DIST_CC_OPTS) \ - $$($1_$2_$3_CC_OPTS) \ - $$($$(basename $$<)_CC_OPTS) \ - $$($1_$2_EXTRA_CC_OPTS) \ - $$(EXTRA_CC_OPTS)) \ + $$(addprefix -optc, $$($1_$2_$3_ALL_CC_OPTS)) \ + $$($1_$2_$3_MOST_HC_OPTS) + +# Options for passing to plain ld +$1_$2_$3_ALL_LD_OPTS = \ + $$(WAY_$3_LD_OPTS) \ + $$($1_$2_DIST_LD_OPTS) \ + $$($1_$2_$3_LD_OPTS) \ + $$($1_$2_EXTRA_LD_OPTS) \ + $$(EXTRA_LD_OPTS) + +# Options for passing to GHC when we use it for linking +$1_$2_$3_GHC_LD_OPTS = \ + $$(addprefix -optl, $$($1_$2_$3_ALL_LD_OPTS)) \ $$($1_$2_$3_MOST_HC_OPTS) $1_$2_$3_ALL_AS_OPTS = \ @@ -172,5 +165,19 @@ $1_$2_$3_ALL_AS_OPTS = \ $$($1_$2_$3_AS_OPTS) \ $$(EXTRA_AS_OPTS) +ifeq "$3" "dyn" +ifneq "$4" "0" +ifeq "$$(TargetElf)" "YES" +$1_$2_$3_GHC_LD_OPTS += \ + -fno-use-rpaths \ + $$(foreach d,$$($1_$2_TRANSITIVE_DEPS),-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_DEPS),-optl-Wl$$(comma)-rpath -optl-Wl$$(comma)'@loader_path/../$$d') +endif +endif +endif + endef From git at git.haskell.org Thu Mar 27 13:50:13 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Mar 2014 13:50:13 +0000 (UTC) Subject: [commit: ghc] master: Include SRC_CC_OPTS and SRC_LD_OPTS when compiling ghc-cabal (d011cde) Message-ID: <20140327135013.1D9F92406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d011cdefca7aa66cbcf71c941f38a4e6dd4c5579/ghc >--------------------------------------------------------------- commit d011cdefca7aa66cbcf71c941f38a4e6dd4c5579 Author: Simon Marlow Date: Thu Mar 27 12:33:44 2014 +0000 Include SRC_CC_OPTS and SRC_LD_OPTS when compiling ghc-cabal >--------------------------------------------------------------- d011cdefca7aa66cbcf71c941f38a4e6dd4c5579 utils/ghc-cabal/ghc.mk | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/utils/ghc-cabal/ghc.mk b/utils/ghc-cabal/ghc.mk index 29db69c..ff5762a 100644 --- a/utils/ghc-cabal/ghc.mk +++ b/utils/ghc-cabal/ghc.mk @@ -31,7 +31,10 @@ $(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/Distribution/*/*.hs) $(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/Distribution/*.hs) $(ghc-cabal_DIST_BINARY): utils/ghc-cabal/Main.hs $(TOUCH_DEP) | $$(dir $$@)/. bootstrapping/. - "$(GHC)" $(SRC_HC_OPTS) --make utils/ghc-cabal/Main.hs -o $@ \ + "$(GHC)" $(SRC_HC_OPTS) \ + $(addprefix -optc, $(SRC_CC_OPTS) $(CONF_CC_OPTS_STAGE0)) \ + $(addprefix -optl, $(SRC_LD_OPTS) $(CONF_LD_OPTS_STAGE0)) \ + --make utils/ghc-cabal/Main.hs -o $@ \ -no-user-$(GHC_PACKAGE_DB_FLAG) \ -Wall -fno-warn-unused-imports -fno-warn-warnings-deprecations \ -DCABAL_VERSION=$(CABAL_VERSION) \ @@ -65,4 +68,3 @@ utils/ghc-cabal_dist-install_WANT_BINDIST_WRAPPER = YES utils/ghc-cabal_dist-install_MODULES = Main $(eval $(call build-prog,utils/ghc-cabal,dist-install,1)) - From git at git.haskell.org Thu Mar 27 13:50:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Mar 2014 13:50:15 +0000 (UTC) Subject: [commit: ghc] master: Use LDFLAGS when compiling ghc-pwd (2aa7810) Message-ID: <20140327135015.8F8B62406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2aa78106ae8f3c9b71d7b85c2a8a5558c4c35fb4/ghc >--------------------------------------------------------------- commit 2aa78106ae8f3c9b71d7b85c2a8a5558c4c35fb4 Author: Simon Marlow Date: Thu Mar 27 12:34:38 2014 +0000 Use LDFLAGS when compiling ghc-pwd >--------------------------------------------------------------- 2aa78106ae8f3c9b71d7b85c2a8a5558c4c35fb4 aclocal.m4 | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/aclocal.m4 b/aclocal.m4 index be38031..5f5c424 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -1806,7 +1806,13 @@ AC_MSG_NOTICE(Building in-tree ghc-pwd) dnl except we don't want to have to know what make is called. Sigh. rm -rf utils/ghc-pwd/dist-boot mkdir utils/ghc-pwd/dist-boot - if ! "$WithGhc" -v0 -no-user-$GHC_PACKAGE_DB_FLAG -hidir utils/ghc-pwd/dist-boot -odir utils/ghc-pwd/dist-boot -stubdir utils/ghc-pwd/dist-boot --make utils/ghc-pwd/Main.hs -o utils/ghc-pwd/dist-boot/ghc-pwd + dnl If special linker flags are needed to build things, then allow + dnl the user to pass them in via LDFLAGS. + changequote(, )dnl + GHC_LDFLAGS=`echo $LDFLAGS | sed 's/\(^\| \)\([^ ]\)/\1-optl\2/g'` + changequote([, ])dnl + echo $GHC_LDFLAGS + if ! "$WithGhc" $GHC_LDFLAGS -v0 -no-user-$GHC_PACKAGE_DB_FLAG -hidir utils/ghc-pwd/dist-boot -odir utils/ghc-pwd/dist-boot -stubdir utils/ghc-pwd/dist-boot --make utils/ghc-pwd/Main.hs -o utils/ghc-pwd/dist-boot/ghc-pwd then AC_MSG_ERROR([Building ghc-pwd failed]) fi From git at git.haskell.org Thu Mar 27 13:50:17 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Mar 2014 13:50:17 +0000 (UTC) Subject: [commit: ghc] master: increase bounds for T3064 (261a97b) Message-ID: <20140327135018.7670B2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/261a97b92611581437d490622e4d727ad8172c9c/ghc >--------------------------------------------------------------- commit 261a97b92611581437d490622e4d727ad8172c9c Author: Simon Marlow Date: Thu Mar 27 13:49:36 2014 +0000 increase bounds for T3064 >--------------------------------------------------------------- 261a97b92611581437d490622e4d727ad8172c9c testsuite/tests/perf/compiler/all.T | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index b03a48f..647548a 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -207,7 +207,7 @@ test('T3064', # expected value: 14 (x86/Linux 28-06-2012): # 2013-11-13: 18 (x86/Windows, 64bit machine) # 2014-01-22: 23 (x86/Linux) - (wordsize(64), 37, 20)]), + (wordsize(64), 42, 20)]), # (amd64/Linux): 18 # (amd64/Linux) 2012-02-07: 26 # (amd64/Linux) 2013-02-12: 23; increased range to 10% From git at git.haskell.org Thu Mar 27 15:47:30 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Mar 2014 15:47:30 +0000 (UTC) Subject: [commit: packages/base] master: add /Since/ annotation (090ca42) Message-ID: <20140327154731.0CBB12406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/base On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/090ca42d43578310fe033df0a21134370dc6ddc3/base >--------------------------------------------------------------- commit 090ca42d43578310fe033df0a21134370dc6ddc3 Author: Herbert Valerio Riedel Date: Thu Mar 27 16:47:16 2014 +0100 add /Since/ annotation >--------------------------------------------------------------- 090ca42d43578310fe033df0a21134370dc6ddc3 GHC/TypeLits.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/GHC/TypeLits.hs b/GHC/TypeLits.hs index 4a6c7b9..94a4288 100644 --- a/GHC/TypeLits.hs +++ b/GHC/TypeLits.hs @@ -154,9 +154,13 @@ infixr 8 ^ type x <= y = (x <=? y) ~ True -- | Comparison of type-level symbols, as a function. +-- +-- /Since: 4.7.0.0/ type family CmpSymbol (m :: Symbol) (n :: Symbol) :: Ordering -- | Comparison of type-level naturals, as a function. +-- +-- /Since: 4.7.0.0/ type family CmpNat (m :: Nat) (n :: Nat) :: Ordering {- | Comparison of type-level naturals, as a function. From git at git.haskell.org Thu Mar 27 16:10:59 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Mar 2014 16:10:59 +0000 (UTC) Subject: [commit: packages/base] ghc-7.8: Add functions for comparing type-level Nats and Symbols. (fca6b0b) Message-ID: <20140327161059.140732406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/base On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/fca6b0b9ee8371e4cbd440a802a21886f1f2d630/base >--------------------------------------------------------------- commit fca6b0b9ee8371e4cbd440a802a21886f1f2d630 Author: Iavor S. Diatchki Date: Tue Mar 18 19:35:05 2014 -0700 Add functions for comparing type-level Nats and Symbols. (cherry picked from commit c1d3546420ee482bbbd9f15d45a6e8a26304d419) >--------------------------------------------------------------- fca6b0b9ee8371e4cbd440a802a21886f1f2d630 GHC/TypeLits.hs | 11 +++++++++-- 1 file changed, 9 insertions(+), 2 deletions(-) diff --git a/GHC/TypeLits.hs b/GHC/TypeLits.hs index e85b36c..ac0f1ae 100644 --- a/GHC/TypeLits.hs +++ b/GHC/TypeLits.hs @@ -29,12 +29,13 @@ module GHC.TypeLits , sameNat, sameSymbol - -- * Functions on type nats + -- * Functions on type literals , type (<=), type (<=?), type (+), type (*), type (^), type (-) + , CmpNat, CmpSymbol ) where -import GHC.Base(Eq(..), Ord(..), Bool(True,False), otherwise) +import GHC.Base(Eq(..), Ord(..), Bool(True,False), Ordering(..), otherwise) import GHC.Num(Integer) import GHC.Base(String) import GHC.Show(Show(..)) @@ -153,6 +154,12 @@ infixr 8 ^ type x <= y = (x <=? y) ~ True -- | Comparison of type-level naturals, as a function. +type family CmpSymbol (m :: Symbol) (n :: Symbol) :: Ordering + +-- | Comparison of type-level symbols, as a function. +type family CmpNat (m :: Nat) (n :: Nat) :: Ordering + +-- | Comparison of type-level naturals, as a function. type family (m :: Nat) <=? (n :: Nat) :: Bool -- | Addition of type-level naturals. From git at git.haskell.org Thu Mar 27 16:11:01 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Mar 2014 16:11:01 +0000 (UTC) Subject: [commit: packages/base] ghc-7.8: Comments only. (4a33679) Message-ID: <20140327161103.D0D4A2406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/base On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/4a33679b04de66d89cf67fb25fcff55e0c428b8d/base >--------------------------------------------------------------- commit 4a33679b04de66d89cf67fb25fcff55e0c428b8d Author: Iavor S. Diatchki Date: Sun Mar 23 17:10:38 2014 -0700 Comments only. Fix the documentation on CmpSymbol and CmpNat; add a note on (<=?). (cherry picked from commit 5edb063688e73ec00fd1f61ac0e8317dd122f44a) >--------------------------------------------------------------- 4a33679b04de66d89cf67fb25fcff55e0c428b8d GHC/TypeLits.hs | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/GHC/TypeLits.hs b/GHC/TypeLits.hs index ac0f1ae..4a6c7b9 100644 --- a/GHC/TypeLits.hs +++ b/GHC/TypeLits.hs @@ -153,13 +153,16 @@ infixr 8 ^ -- | Comparison of type-level naturals, as a constraint. type x <= y = (x <=? y) ~ True --- | Comparison of type-level naturals, as a function. +-- | Comparison of type-level symbols, as a function. type family CmpSymbol (m :: Symbol) (n :: Symbol) :: Ordering --- | Comparison of type-level symbols, as a function. +-- | Comparison of type-level naturals, as a function. type family CmpNat (m :: Nat) (n :: Nat) :: Ordering --- | Comparison of type-level naturals, as a function. +{- | Comparison of type-level naturals, as a function. +NOTE: The functionality for this function should be subsumed +by 'CmpNat', so this might go away in the future. +Please let us know, if you encounter discrepancies between the two. -} type family (m :: Nat) <=? (n :: Nat) :: Bool -- | Addition of type-level naturals. From git at git.haskell.org Thu Mar 27 16:11:03 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Mar 2014 16:11:03 +0000 (UTC) Subject: [commit: packages/base] ghc-7.8: add /Since/ annotation (065aef8) Message-ID: <20140327161103.D735D24069@ghc.haskell.org> Repository : ssh://git at git.haskell.org/base On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/065aef8da36a16bb23f07b298ccd63ed2a64f7fe/base >--------------------------------------------------------------- commit 065aef8da36a16bb23f07b298ccd63ed2a64f7fe Author: Herbert Valerio Riedel Date: Thu Mar 27 16:47:16 2014 +0100 add /Since/ annotation (cherry picked from commit 090ca42d43578310fe033df0a21134370dc6ddc3) >--------------------------------------------------------------- 065aef8da36a16bb23f07b298ccd63ed2a64f7fe GHC/TypeLits.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/GHC/TypeLits.hs b/GHC/TypeLits.hs index 4a6c7b9..94a4288 100644 --- a/GHC/TypeLits.hs +++ b/GHC/TypeLits.hs @@ -154,9 +154,13 @@ infixr 8 ^ type x <= y = (x <=? y) ~ True -- | Comparison of type-level symbols, as a function. +-- +-- /Since: 4.7.0.0/ type family CmpSymbol (m :: Symbol) (n :: Symbol) :: Ordering -- | Comparison of type-level naturals, as a function. +-- +-- /Since: 4.7.0.0/ type family CmpNat (m :: Nat) (n :: Nat) :: Ordering {- | Comparison of type-level naturals, as a function. From git at git.haskell.org Thu Mar 27 16:11:25 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Mar 2014 16:11:25 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Implement ordering comparisons for type-level naturals and symbols. (65aa60b) Message-ID: <20140327161125.B64042406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/65aa60b5409e0932ff771c54383ba8f8c133991b/ghc >--------------------------------------------------------------- commit 65aa60b5409e0932ff771c54383ba8f8c133991b Author: Iavor S. Diatchki Date: Tue Mar 18 18:54:23 2014 -0700 Implement ordering comparisons for type-level naturals and symbols. This is done with two built-in type families: `CmpNat and `CmpSymbol`. Both of these return a promoted `Ordering` type (EQ, LT, or GT). (cherry picked from commit 5e4bdb5fc5e741522cbb787731422da3f12aa398) >--------------------------------------------------------------- 65aa60b5409e0932ff771c54383ba8f8c133991b compiler/prelude/PrelNames.lhs | 3 + compiler/prelude/TysWiredIn.lhs | 16 +++++ compiler/typecheck/TcTypeNats.hs | 142 +++++++++++++++++++++++++++++++++++++- 3 files changed, 160 insertions(+), 1 deletion(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 65aa60b5409e0932ff771c54383ba8f8c133991b From git at git.haskell.org Thu Mar 27 21:00:02 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Mar 2014 21:00:02 +0000 (UTC) Subject: [commit: ghc] master: Use the correct callClobberedRegs on Windows/x64 (#8834) (c4eeacd) Message-ID: <20140327210002.7B9042406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c4eeacdfdf4578eb6e75bbf2e067bfe70ec94ab0/ghc >--------------------------------------------------------------- commit c4eeacdfdf4578eb6e75bbf2e067bfe70ec94ab0 Author: Simon Marlow Date: Mon Mar 24 14:36:16 2014 +0000 Use the correct callClobberedRegs on Windows/x64 (#8834) Signed-off-by: Austin Seipp >--------------------------------------------------------------- c4eeacdfdf4578eb6e75bbf2e067bfe70ec94ab0 compiler/nativeGen/X86/Regs.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/compiler/nativeGen/X86/Regs.hs b/compiler/nativeGen/X86/Regs.hs index b5139c9..127a811 100644 --- a/compiler/nativeGen/X86/Regs.hs +++ b/compiler/nativeGen/X86/Regs.hs @@ -403,6 +403,9 @@ callClobberedRegs :: Platform -> [Reg] -- caller-saves registers callClobberedRegs platform | target32Bit platform = [eax,ecx,edx] ++ map regSingle (floatregnos platform) + | platformOS platform == OSMinGW32 + = [rax,rcx,rdx,r8,r9,r10,r11] + ++ map regSingle (floatregnos platform) | otherwise -- all xmm regs are caller-saves -- caller-saves registers From git at git.haskell.org Thu Mar 27 21:03:33 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Mar 2014 21:03:33 +0000 (UTC) Subject: [commit: ghc] ghc-7.8: Use the correct callClobberedRegs on Windows/x64 (#8834) (fc5aa5d) Message-ID: <20140327210333.7D7642406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.8 Link : http://ghc.haskell.org/trac/ghc/changeset/fc5aa5d8a0a7c7fc57cfe268f1e051e14c90b93b/ghc >--------------------------------------------------------------- commit fc5aa5d8a0a7c7fc57cfe268f1e051e14c90b93b Author: Simon Marlow Date: Mon Mar 24 14:36:16 2014 +0000 Use the correct callClobberedRegs on Windows/x64 (#8834) Signed-off-by: Austin Seipp (cherry picked from commit c4eeacdfdf4578eb6e75bbf2e067bfe70ec94ab0) >--------------------------------------------------------------- fc5aa5d8a0a7c7fc57cfe268f1e051e14c90b93b compiler/nativeGen/X86/Regs.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/compiler/nativeGen/X86/Regs.hs b/compiler/nativeGen/X86/Regs.hs index b5139c9..127a811 100644 --- a/compiler/nativeGen/X86/Regs.hs +++ b/compiler/nativeGen/X86/Regs.hs @@ -403,6 +403,9 @@ callClobberedRegs :: Platform -> [Reg] -- caller-saves registers callClobberedRegs platform | target32Bit platform = [eax,ecx,edx] ++ map regSingle (floatregnos platform) + | platformOS platform == OSMinGW32 + = [rax,rcx,rdx,r8,r9,r10,r11] + ++ map regSingle (floatregnos platform) | otherwise -- all xmm regs are caller-saves -- caller-saves registers From git at git.haskell.org Thu Mar 27 21:52:29 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 27 Mar 2014 21:52:29 +0000 (UTC) Subject: [commit: ghc] master: rts: remove unused functions, fix validate on OS X (7ef3f0d) Message-ID: <20140327215229.3B69A2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7ef3f0d6dbd54d9e58fb6ab1f2db322bc8fac37a/ghc >--------------------------------------------------------------- commit 7ef3f0d6dbd54d9e58fb6ab1f2db322bc8fac37a Author: Austin Seipp Date: Thu Mar 27 16:51:07 2014 -0500 rts: remove unused functions, fix validate on OS X After a toolchain update, Clang is no longer appreciative of the fact these are unused, thanks to -Werror during validate. Signed-off-by: Austin Seipp >--------------------------------------------------------------- 7ef3f0d6dbd54d9e58fb6ab1f2db322bc8fac37a rts/eventlog/EventLog.c | 6 ------ 1 file changed, 6 deletions(-) diff --git a/rts/eventlog/EventLog.c b/rts/eventlog/EventLog.c index ef6f69c..2e0e9bb 100644 --- a/rts/eventlog/EventLog.c +++ b/rts/eventlog/EventLog.c @@ -203,15 +203,9 @@ static inline void postEventHeader(EventsBuf *eb, EventTypeNum type) static inline void postInt8(EventsBuf *eb, StgInt8 i) { postWord8(eb, (StgWord8)i); } -static inline void postInt16(EventsBuf *eb, StgInt16 i) -{ postWord16(eb, (StgWord16)i); } - static inline void postInt32(EventsBuf *eb, StgInt32 i) { postWord32(eb, (StgWord32)i); } -static inline void postInt64(EventsBuf *eb, StgInt64 i) -{ postWord64(eb, (StgWord64)i); } - void initEventLogging(void) From git at git.haskell.org Fri Mar 28 08:03:29 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Mar 2014 08:03:29 +0000 (UTC) Subject: [commit: ghc] master: Make copy array ops out-of-line by default (e54828b) Message-ID: <20140328080329.B06542406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e54828bf25fa99e74588fecb0adc705fb869a8b4/ghc >--------------------------------------------------------------- commit e54828bf25fa99e74588fecb0adc705fb869a8b4 Author: Johan Tibell Date: Thu Mar 27 18:04:56 2014 +0100 Make copy array ops out-of-line by default This should reduce code size when there's little to gain from inlining these primops, while still retaining the inlining benefit when the size of the copy is known statically. >--------------------------------------------------------------- e54828bf25fa99e74588fecb0adc705fb869a8b4 compiler/codeGen/StgCmmPrim.hs | 77 +++++++++++++++++++++++---------------- compiler/prelude/primops.txt.pp | 12 +++--- includes/Cmm.h | 53 +++++++++++++++++++++++++++ rts/PrimOps.cmm | 20 ++++++++++ 4 files changed, 124 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 e54828bf25fa99e74588fecb0adc705fb869a8b4 From git at git.haskell.org Fri Mar 28 09:13:32 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 28 Mar 2014 09:13:32 +0000 (UTC) Subject: [commit: ghc] master: Remove debugging output (4c8edfd) Message-ID: <20140328091333.13D922406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4c8edfd2c722504baaa6896d194fd3a8c3f9b652/ghc >--------------------------------------------------------------- commit 4c8edfd2c722504baaa6896d194fd3a8c3f9b652 Author: Simon Marlow Date: Fri Mar 28 09:09:38 2014 +0000 Remove debugging output >--------------------------------------------------------------- 4c8edfd2c722504baaa6896d194fd3a8c3f9b652 aclocal.m4 | 1 - 1 file changed, 1 deletion(-) diff --git a/aclocal.m4 b/aclocal.m4 index 5f5c424..7cae3b5 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -1811,7 +1811,6 @@ AC_MSG_NOTICE(Building in-tree ghc-pwd) changequote(, )dnl GHC_LDFLAGS=`echo $LDFLAGS | sed 's/\(^\| \)\([^ ]\)/\1-optl\2/g'` changequote([, ])dnl - echo $GHC_LDFLAGS if ! "$WithGhc" $GHC_LDFLAGS -v0 -no-user-$GHC_PACKAGE_DB_FLAG -hidir utils/ghc-pwd/dist-boot -odir utils/ghc-pwd/dist-boot -stubdir utils/ghc-pwd/dist-boot --make utils/ghc-pwd/Main.hs -o utils/ghc-pwd/dist-boot/ghc-pwd then AC_MSG_ERROR([Building ghc-pwd failed]) From git at git.haskell.org Sat Mar 29 10:24:57 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 29 Mar 2014 10:24:57 +0000 (UTC) Subject: [commit: ghc] master: Add SmallArray# and SmallMutableArray# types (90329b6) Message-ID: <20140329102457.1CE182406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/90329b6cc183b3cd05956ae6bdeb6ac6951549c2/ghc >--------------------------------------------------------------- commit 90329b6cc183b3cd05956ae6bdeb6ac6951549c2 Author: Johan Tibell Date: Sun Mar 23 12:06:56 2014 +0100 Add SmallArray# and SmallMutableArray# types These array types are smaller than Array# and MutableArray# and are faster when the array size is small, as they don't have the overhead of a card table. Having no card table reduces the closure size with 2 words in the typical small array case and leads to less work when updating or GC:ing the array. Reduces both the runtime and memory allocation by 8.8% on my insert benchmark for the HashMap type in the unordered-containers package, which makes use of lots of small arrays. With tuned GC settings (i.e. `+RTS -A6M`) the runtime reduction is 15%. Fixes #8923. >--------------------------------------------------------------- 90329b6cc183b3cd05956ae6bdeb6ac6951549c2 compiler/cmm/CLabel.hs | 9 +- compiler/cmm/CmmParse.y | 2 +- compiler/cmm/SMRep.lhs | 57 +++++-- compiler/codeGen/StgCmmBind.hs | 8 +- compiler/codeGen/StgCmmCon.hs | 4 +- compiler/codeGen/StgCmmForeign.hs | 5 +- compiler/codeGen/StgCmmLayout.hs | 2 +- compiler/codeGen/StgCmmPrim.hs | 168 ++++++++++++++++---- compiler/ghci/ByteCodeGen.lhs | 5 + compiler/ghci/RtClosureInspect.hs | 2 + compiler/prelude/PrelNames.lhs | 6 +- compiler/prelude/TysPrim.lhs | 17 +- compiler/prelude/primops.txt.pp | 156 +++++++++++++++++- includes/Cmm.h | 33 ++++ includes/rts/storage/ClosureMacros.h | 9 ++ includes/rts/storage/ClosureTypes.h | 6 +- includes/rts/storage/Closures.h | 6 + includes/stg/MiscClosures.h | 14 ++ rts/CheckUnload.c | 8 + rts/ClosureFlags.c | 8 +- rts/LdvProfile.c | 4 + rts/Linker.c | 9 ++ rts/PrimOps.cmm | 118 ++++++++++++++ rts/Printer.c | 15 ++ rts/ProfHeap.c | 8 + rts/RetainerProfile.c | 12 ++ rts/StgMiscClosures.cmm | 12 ++ rts/sm/Compact.c | 31 ++++ rts/sm/Evac.c | 8 + rts/sm/Scav.c | 148 +++++++++++++++++ .../should_run/{cgrun064.hs => CopySmallArray.hs} | 42 ++--- .../{cgrun064.stdout => CopySmallArray.stdout} | 0 .../{cgrun068.hs => CopySmallArrayStressTest.hs} | 32 ++-- ...n068.stdout => CopySmallArrayStressTest.stdout} | 0 .../{cgrun065.hs => SizeOfSmallArray.hs} | 11 +- .../{cgrun065.stdout => SizeOfSmallArray.stdout} | 0 testsuite/tests/codeGen/should_run/all.T | 3 + utils/deriveConstants/DeriveConstants.hs | 3 + utils/genprimopcode/Main.hs | 3 + 39 files changed, 880 insertions(+), 104 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 90329b6cc183b3cd05956ae6bdeb6ac6951549c2 From git at git.haskell.org Sat Mar 29 10:29:15 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 29 Mar 2014 10:29:15 +0000 (UTC) Subject: [commit: ghc] master: Add missing symbols to linker (838bfb2) Message-ID: <20140329102915.8B7902406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/838bfb224784d6668f9da441866504eba4351ee6/ghc >--------------------------------------------------------------- commit 838bfb224784d6668f9da441866504eba4351ee6 Author: Johan Tibell Date: Sat Mar 29 10:57:49 2014 +0100 Add missing symbols to linker The copy array family of primops were moved out-of-line. >--------------------------------------------------------------- 838bfb224784d6668f9da441866504eba4351ee6 includes/stg/MiscClosures.h | 4 ++++ rts/Linker.c | 6 +++++- 2 files changed, 9 insertions(+), 1 deletion(-) diff --git a/includes/stg/MiscClosures.h b/includes/stg/MiscClosures.h index 944adac..0c4d2f9 100644 --- a/includes/stg/MiscClosures.h +++ b/includes/stg/MiscClosures.h @@ -351,6 +351,10 @@ RTS_FUN_DECL(stg_casIntArrayzh); RTS_FUN_DECL(stg_fetchAddIntArrayzh); RTS_FUN_DECL(stg_newArrayzh); RTS_FUN_DECL(stg_newArrayArrayzh); +RTS_FUN_DECL(stg_copyArrayzh); +RTS_FUN_DECL(stg_copyMutableArrayzh); +RTS_FUN_DECL(stg_copyArrayArrayzh); +RTS_FUN_DECL(stg_copyMutableArrayArrayzh); RTS_FUN_DECL(stg_cloneArrayzh); RTS_FUN_DECL(stg_cloneMutableArrayzh); RTS_FUN_DECL(stg_freezzeArrayzh); diff --git a/rts/Linker.c b/rts/Linker.c index 9c73757..c0e1b8d 100644 --- a/rts/Linker.c +++ b/rts/Linker.c @@ -1162,9 +1162,13 @@ typedef struct _RtsSymbolVal { SymI_HasProto(stg_myThreadIdzh) \ SymI_HasProto(stg_labelThreadzh) \ SymI_HasProto(stg_newArrayzh) \ + SymI_HasProto(stg_copyArrayzh) \ + SymI_HasProto(stg_copyMutableArrayzh) \ + SymI_HasProto(stg_copyArrayArrayzh) \ + SymI_HasProto(stg_copyMutableArrayArrayzh) \ SymI_HasProto(stg_cloneArrayzh) \ SymI_HasProto(stg_cloneMutableArrayzh) \ - SymI_HasProto(stg_freezzeArrayzh) \ + SymI_HasProto(stg_freezzeArrayzh) \ SymI_HasProto(stg_thawArrayzh) \ SymI_HasProto(stg_newArrayArrayzh) \ SymI_HasProto(stg_casArrayzh) \ From git at git.haskell.org Sat Mar 29 15:28:41 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 29 Mar 2014 15:28:41 +0000 (UTC) Subject: [commit: ghc] master: PrimOps.cmm: whitespace only (dd02850) Message-ID: <20140329152841.4CD222406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/dd02850975cb67678900d7cb4fddb1572c7cba24/ghc >--------------------------------------------------------------- commit dd02850975cb67678900d7cb4fddb1572c7cba24 Author: Johan Tibell Date: Fri Mar 28 09:21:10 2014 +0100 PrimOps.cmm: whitespace only Harmonize the indentation amount. The file mixed 4, 2, and in some cases 3 spaces for indentation. >--------------------------------------------------------------- dd02850975cb67678900d7cb4fddb1572c7cba24 rts/PrimOps.cmm | 875 ++++++++++++++++++++++++++++--------------------------- 1 file changed, 438 insertions(+), 437 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc dd02850975cb67678900d7cb4fddb1572c7cba24 From git at git.haskell.org Sat Mar 29 17:23:28 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 29 Mar 2014 17:23:28 +0000 (UTC) Subject: [commit: ghc] master: Add more missing linker symbols (4de517f) Message-ID: <20140329172328.79E4E2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4de517f5f46a878e45c95ecf8650bc1e25dab479/ghc >--------------------------------------------------------------- commit 4de517f5f46a878e45c95ecf8650bc1e25dab479 Author: Johan Tibell Date: Sat Mar 29 17:17:41 2014 +0100 Add more missing linker symbols >--------------------------------------------------------------- 4de517f5f46a878e45c95ecf8650bc1e25dab479 rts/Linker.c | 3 +++ 1 file changed, 3 insertions(+) diff --git a/rts/Linker.c b/rts/Linker.c index c0e1b8d..78bfc34 100644 --- a/rts/Linker.c +++ b/rts/Linker.c @@ -1279,6 +1279,9 @@ typedef struct _RtsSymbolVal { SymI_HasProto(stg_MUT_ARR_PTRS_DIRTY_info) \ SymI_HasProto(stg_MUT_ARR_PTRS_FROZEN_info) \ SymI_HasProto(stg_MUT_ARR_PTRS_FROZEN0_info) \ + SymI_HasProto(stg_SMALL_MUT_ARR_PTRS_DIRTY_info) \ + SymI_HasProto(stg_SMALL_MUT_ARR_PTRS_FROZEN_info) \ + SymI_HasProto(stg_SMALL_MUT_ARR_PTRS_FROZEN0_info) \ SymI_HasProto(stg_MUT_VAR_CLEAN_info) \ SymI_HasProto(stg_MUT_VAR_DIRTY_info) \ SymI_HasProto(stg_WEAK_info) \ From git at git.haskell.org Sat Mar 29 20:09:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 29 Mar 2014 20:09:24 +0000 (UTC) Subject: [commit: ghc] master: CopySmallArrayStressTest needs random (c310823) Message-ID: <20140329200924.18DF82406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c3108234cb1ce1842bcb288ab533315934524cff/ghc >--------------------------------------------------------------- commit c3108234cb1ce1842bcb288ab533315934524cff Author: Joachim Breitner Date: Sat Mar 29 21:08:17 2014 +0100 CopySmallArrayStressTest needs random >--------------------------------------------------------------- c3108234cb1ce1842bcb288ab533315934524cff testsuite/tests/codeGen/should_run/all.T | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/codeGen/should_run/all.T b/testsuite/tests/codeGen/should_run/all.T index 7604427..9077af2 100644 --- a/testsuite/tests/codeGen/should_run/all.T +++ b/testsuite/tests/codeGen/should_run/all.T @@ -119,5 +119,5 @@ test('T6084',normal, compile_and_run, ['-O2']) test('StaticArraySize', normal, compile_and_run, ['-O2']) test('StaticByteArraySize', normal, compile_and_run, ['-O2']) test('CopySmallArray', normal, compile_and_run, ['']) -test('CopySmallArrayStressTest', normal, compile_and_run, ['']) +test('CopySmallArrayStressTest', reqlib('random'), compile_and_run, ['']) test('SizeOfSmallArray', normal, compile_and_run, ['']) From git at git.haskell.org Sun Mar 30 13:33:07 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 30 Mar 2014 13:33:07 +0000 (UTC) Subject: [commit: ghc] master: Add inline versions of copy ops for small arrays (1a11e9b) Message-ID: <20140330133308.162992406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1a11e9ba87469d19b8cc7da9c5f5ac043246b367/ghc >--------------------------------------------------------------- commit 1a11e9ba87469d19b8cc7da9c5f5ac043246b367 Author: Johan Tibell Date: Sun Mar 30 15:12:01 2014 +0200 Add inline versions of copy ops for small arrays If the number of elements being copied is known statically this might lead to the copy loop being unrolled in the backend. >--------------------------------------------------------------- 1a11e9ba87469d19b8cc7da9c5f5ac043246b367 compiler/codeGen/StgCmmPrim.hs | 63 ++++++++++++++++++++++++++++++++++++++++ 1 file changed, 63 insertions(+) diff --git a/compiler/codeGen/StgCmmPrim.hs b/compiler/codeGen/StgCmmPrim.hs index 2c4ad4e..5c75acb 100644 --- a/compiler/codeGen/StgCmmPrim.hs +++ b/compiler/codeGen/StgCmmPrim.hs @@ -189,6 +189,14 @@ shouldInlinePrimOp dflags NewSmallArrayOp [(CmmLit (CmmInt n _)), init] ] (fromInteger n) init +shouldInlinePrimOp _ CopySmallArrayOp + [src, src_off, dst, dst_off, (CmmLit (CmmInt n _))] = + Just $ \ [] -> doCopySmallArrayOp src src_off dst dst_off (fromInteger n) + +shouldInlinePrimOp _ CopySmallMutableArrayOp + [src, src_off, dst, dst_off, (CmmLit (CmmInt n _))] = + Just $ \ [] -> doCopySmallMutableArrayOp src src_off dst dst_off (fromInteger n) + shouldInlinePrimOp dflags CloneSmallArrayOp [src, src_off, (CmmLit (CmmInt n _))] | wordsToBytes dflags (fromInteger n) <= maxInlineAllocSize dflags = Just $ \ [res] -> emitCloneSmallArray mkSMAP_FROZEN_infoLabel res src src_off (fromInteger n) @@ -1747,6 +1755,61 @@ emitCopyArray copy src0 src_off dst0 dst_off0 n = do emitSetCards dst_off dst_cards_p n +doCopySmallArrayOp :: CmmExpr -> CmmExpr -> CmmExpr -> CmmExpr -> WordOff + -> FCode () +doCopySmallArrayOp = emitCopySmallArray copy + where + -- Copy data (we assume the arrays aren't overlapping since + -- they're of different types) + copy _src _dst dst_p src_p bytes = + do dflags <- getDynFlags + emitMemcpyCall dst_p src_p (mkIntExpr dflags bytes) + (mkIntExpr dflags (wORD_SIZE dflags)) + + +doCopySmallMutableArrayOp :: CmmExpr -> CmmExpr -> CmmExpr -> CmmExpr -> WordOff + -> FCode () +doCopySmallMutableArrayOp = emitCopySmallArray copy + where + -- The only time the memory might overlap is when the two arrays + -- we were provided are the same array! + -- TODO: Optimize branch for common case of no aliasing. + copy src dst dst_p src_p bytes = do + dflags <- getDynFlags + [moveCall, cpyCall] <- forkAlts + [ getCode $ emitMemmoveCall dst_p src_p (mkIntExpr dflags bytes) + (mkIntExpr dflags (wORD_SIZE dflags)) + , getCode $ emitMemcpyCall dst_p src_p (mkIntExpr dflags bytes) + (mkIntExpr dflags (wORD_SIZE dflags)) + ] + emit =<< mkCmmIfThenElse (cmmEqWord dflags src dst) moveCall cpyCall + +emitCopySmallArray :: (CmmExpr -> CmmExpr -> CmmExpr -> CmmExpr -> ByteOff + -> FCode ()) -- ^ copy function + -> CmmExpr -- ^ source array + -> CmmExpr -- ^ offset in source array + -> CmmExpr -- ^ destination array + -> CmmExpr -- ^ offset in destination array + -> WordOff -- ^ number of elements to copy + -> FCode () +emitCopySmallArray copy src0 src_off dst0 dst_off n = do + dflags <- getDynFlags + + -- Passed as arguments (be careful) + src <- assignTempE src0 + dst <- assignTempE dst0 + + -- Set the dirty bit in the header. + emit (setInfo dst (CmmLit (CmmLabel mkSMAP_DIRTY_infoLabel))) + + dst_p <- assignTempE $ cmmOffsetExprW dflags + (cmmOffsetB dflags dst (smallArrPtrsHdrSize dflags)) dst_off + src_p <- assignTempE $ cmmOffsetExprW dflags + (cmmOffsetB dflags src (smallArrPtrsHdrSize dflags)) src_off + let bytes = wordsToBytes dflags n + + copy src dst dst_p src_p bytes + -- | Takes an info table label, a register to return the newly -- allocated array in, a source array, an offset in the source array, -- and the number of elements to copy. Allocates a new array and From git at git.haskell.org Sun Mar 30 15:20:24 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 30 Mar 2014 15:20:24 +0000 (UTC) Subject: [commit: packages/process] master: Remove support for Hugs (5fe18cb) Message-ID: <20140330152025.0ED362406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5fe18cb98baba398ea62558b0863b5a3e2cfb980/process >--------------------------------------------------------------- commit 5fe18cb98baba398ea62558b0863b5a3e2cfb980 Author: Johan Tibell Date: Sun Mar 30 16:59:21 2014 +0200 Remove support for Hugs >--------------------------------------------------------------- 5fe18cb98baba398ea62558b0863b5a3e2cfb980 System/Process.hs | 14 -------------- 1 file changed, 14 deletions(-) diff --git a/System/Process.hs b/System/Process.hs index 26dab2a..19c500c 100644 --- a/System/Process.hs +++ b/System/Process.hs @@ -35,7 +35,6 @@ -} module System.Process ( -#ifndef __HUGS__ -- * Running sub-processes createProcess, shell, proc, @@ -71,14 +70,12 @@ module System.Process ( runCommand, runInteractiveProcess, runInteractiveCommand, -#endif system, rawSystem, ) where import Prelude hiding (mapM) -#ifndef __HUGS__ import System.Process.Internals import Control.Exception (SomeException, mask, try, throwIO) @@ -95,7 +92,6 @@ import Foreign import Foreign.C import System.IO import Data.Maybe -#endif import System.Exit ( ExitCode(..) ) #ifdef __GLASGOW_HASKELL__ @@ -108,13 +104,6 @@ import System.Posix.Signals #endif #endif -#ifdef __HUGS__ -import Hugs.System -#endif - - -#ifndef __HUGS__ - -- ---------------------------------------------------------------------------- -- createProcess @@ -845,7 +834,6 @@ runInteractiveProcess1 fun cmd = do std_out = CreatePipe, std_err = CreatePipe } return (fromJust mb_in, fromJust mb_out, fromJust mb_err, p) -#endif /* !__HUGS__ */ -- --------------------------------------------------------------------------- @@ -903,8 +891,6 @@ rawSystem cmd args = do #elif !mingw32_HOST_OS -- crude fallback implementation: could do much better than this under Unix rawSystem cmd args = system (showCommandForUser cmd args) -#elif __HUGS__ -rawSystem cmd args = system (cmd ++ showCommandForUser "" args) #else rawSystem cmd args = system (showCommandForUser cmd args) #endif From git at git.haskell.org Sun Mar 30 15:20:27 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 30 Mar 2014 15:20:27 +0000 (UTC) Subject: [commit: packages/process] master: Clean up import and export lists (b39e340) Message-ID: <20140330152027.1F1C42406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b39e340bb1fa887842e99db9824906858515cdf7/process >--------------------------------------------------------------- commit b39e340bb1fa887842e99db9824906858515cdf7 Author: Johan Tibell Date: Sun Mar 30 17:05:23 2014 +0200 Clean up import and export lists Imports are now sorted alphabetically and shared imports come before compiler/OS specific ones. Import lists now use consistent indentation. Nested CPP if statements are now indented so it's possible to match up the ifs with the ends. >--------------------------------------------------------------- b39e340bb1fa887842e99db9824906858515cdf7 System/Process.hs | 103 ++++++++++++++++++++++--------------------- System/Process/Internals.hs | 52 +++++++++++----------- 2 files changed, 78 insertions(+), 77 deletions(-) diff --git a/System/Process.hs b/System/Process.hs index 19c500c..87e9a41 100644 --- a/System/Process.hs +++ b/System/Process.hs @@ -35,73 +35,74 @@ -} module System.Process ( - -- * Running sub-processes - createProcess, - shell, proc, - CreateProcess(..), - CmdSpec(..), - StdStream(..), - ProcessHandle, - - -- ** Simpler functions for common tasks - callProcess, - callCommand, - spawnProcess, - spawnCommand, - readProcess, - readProcessWithExitCode, - - -- ** Related utilities - showCommandForUser, - - -- ** Control-C handling on Unix - -- $ctlc-handling - - -- * Process completion - waitForProcess, - getProcessExitCode, - terminateProcess, - interruptProcessGroupOf, - - -- * Old deprecated functions - -- | These functions pre-date 'createProcess' which is much more - -- flexible. - runProcess, - runCommand, - runInteractiveProcess, - runInteractiveCommand, - system, - rawSystem, - ) where + -- * Running sub-processes + createProcess, + shell, proc, + CreateProcess(..), + CmdSpec(..), + StdStream(..), + ProcessHandle, + + -- ** Simpler functions for common tasks + callProcess, + callCommand, + spawnProcess, + spawnCommand, + readProcess, + readProcessWithExitCode, + + -- ** Related utilities + showCommandForUser, + + -- ** Control-C handling on Unix + -- $ctlc-handling + + -- * Process completion + waitForProcess, + getProcessExitCode, + terminateProcess, + interruptProcessGroupOf, + + -- * Old deprecated functions + -- | These functions pre-date 'createProcess' which is much more + -- flexible. + runProcess, + runCommand, + runInteractiveProcess, + runInteractiveCommand, + system, + rawSystem, + ) where import Prelude hiding (mapM) import System.Process.Internals -import Control.Exception (SomeException, mask, try, throwIO) +import Control.Concurrent import Control.DeepSeq (rnf) -import System.IO.Error (mkIOError, ioeSetErrorString) -#if !defined(mingw32_HOST_OS) -import System.Posix.Types -import System.Posix.Process (getProcessGroupIDOf) -#endif +import Control.Exception (SomeException, mask, try, throwIO) import qualified Control.Exception as C -import Control.Concurrent import Control.Monad +import Data.Maybe import Foreign import Foreign.C -import System.IO -import Data.Maybe import System.Exit ( ExitCode(..) ) +import System.IO +import System.IO.Error (mkIOError, ioeSetErrorString) + +#if !defined(mingw32_HOST_OS) +import System.Posix.Process (getProcessGroupIDOf) +import System.Posix.Types +#endif #ifdef __GLASGOW_HASKELL__ import GHC.IO.Exception ( ioException, IOErrorType(..), IOException(..) ) -#if defined(mingw32_HOST_OS) -import System.Win32.Process (getProcessId) +# if defined(mingw32_HOST_OS) import System.Win32.Console (generateConsoleCtrlEvent, cTRL_BREAK_EVENT) -#else +import System.Win32.Process (getProcessId) +# else import System.Posix.Signals -#endif +# endif #endif -- ---------------------------------------------------------------------------- diff --git a/System/Process/Internals.hs b/System/Process/Internals.hs index c4f8797..9dc2af7 100644 --- a/System/Process/Internals.hs +++ b/System/Process/Internals.hs @@ -20,33 +20,25 @@ ----------------------------------------------------------------------------- module System.Process.Internals ( - ProcessHandle(..), ProcessHandle__(..), - PHANDLE, closePHANDLE, mkProcessHandle, - modifyProcessHandle, withProcessHandle, + ProcessHandle(..), ProcessHandle__(..), + PHANDLE, closePHANDLE, mkProcessHandle, + modifyProcessHandle, withProcessHandle, #ifdef __GLASGOW_HASKELL__ - CreateProcess(..), - CmdSpec(..), StdStream(..), - createProcess_, - runGenProcess_, --deprecated + CreateProcess(..), + CmdSpec(..), StdStream(..), + createProcess_, + runGenProcess_, --deprecated #endif - startDelegateControlC, - endDelegateControlC, + startDelegateControlC, + endDelegateControlC, #if !defined(mingw32_HOST_OS) && !defined(__MINGW32__) - pPrPr_disableITimers, c_execvpe, - ignoreSignal, defaultSignal, -#endif - withFilePathException, withCEnvironment, - translate, - fdToHandle, - ) where - -#if !defined(mingw32_HOST_OS) && !defined(__MINGW32__) -import Control.Monad -import Data.Char -import System.Posix.Types -import System.Posix.Process.Internals ( pPrPr_disableITimers, c_execvpe ) -import System.IO + pPrPr_disableITimers, c_execvpe, + ignoreSignal, defaultSignal, #endif + withFilePathException, withCEnvironment, + translate, + fdToHandle, + ) where import Control.Concurrent import Control.Exception @@ -57,6 +49,14 @@ import Foreign.Ptr import Foreign.Storable import System.IO.Unsafe +#if !defined(mingw32_HOST_OS) && !defined(__MINGW32__) +import Control.Monad +import Data.Char +import System.IO +import System.Posix.Process.Internals ( pPrPr_disableITimers, c_execvpe ) +import System.Posix.Types +#endif + #ifdef __GLASGOW_HASKELL__ import System.Posix.Internals import GHC.IO.Exception @@ -68,12 +68,12 @@ import GHC.IO.Handle.Internals import GHC.IO.Handle.Types hiding (ClosedHandle) import System.IO.Error import Data.Typeable -#if defined(mingw32_HOST_OS) +# if defined(mingw32_HOST_OS) import GHC.IO.IOMode import System.Win32.DebugApi (PHANDLE) -#else +# else import System.Posix.Signals as Sig -#endif +# endif #endif #if defined(mingw32_HOST_OS) From git at git.haskell.org Mon Mar 31 04:35:12 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 31 Mar 2014 04:35:12 +0000 (UTC) Subject: [commit: haddock] master: Print kind signatures on GADTs (bd134c7) Message-ID: <20140331043512.6B90B2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : master Link : http://git.haskell.org/haddock.git/commitdiff/bd134c7b2a6880bf3858fd8c27fa16ab946d7718 >--------------------------------------------------------------- commit bd134c7b2a6880bf3858fd8c27fa16ab946d7718 Author: Mateusz Kowalczyk Date: Mon Mar 31 05:34:36 2014 +0100 Print kind signatures on GADTs >--------------------------------------------------------------- bd134c7b2a6880bf3858fd8c27fa16ab946d7718 CHANGES | 2 + html-test/ref/AdvanceTypes.html | 2 +- html-test/ref/{Ticket253_2.html => Bug85.html} | 86 +++++++++++++++--------- html-test/src/Bug85.hs | 15 +++++ src/Haddock/Backends/Xhtml/Decl.hs | 16 +++-- 5 files changed, 83 insertions(+), 38 deletions(-) diff --git a/CHANGES b/CHANGES index be2de82..31851e5 100644 --- a/CHANGES +++ b/CHANGES @@ -2,6 +2,8 @@ Changes in version 2.15.0 * Always read in prologue files as UTF8 (#286 and Cabal #1721) + * Print kind signatures GADTs (#85) + Changes in version 2.14.1 * Render * and -> with their UnicodeSyntax equivalents if -U is enabled diff --git a/html-test/ref/AdvanceTypes.html b/html-test/ref/AdvanceTypes.html index ab37fe6..b918a22 100644 --- a/html-test/ref/AdvanceTypes.html +++ b/html-test/ref/AdvanceTypes.html @@ -50,7 +50,7 @@ window.onload = function () {pageLoad();setSynopsis("mini_AdvanceTypes.html");}; >data Pattern :: [*] -> * where

    Ticket253_2Bug85

    Ticket253_2

    Synopsis

    Bug85

    Documentation

    bar :: Intdata Foo :: (* -> *) -> * -> * where

    Comment

    Constructors

    Bar :: f x -> Foo f (f x) 
    data Baz :: * where

    data Qux where

    Constructors

    Quux :: Qux 

    Documentation

    foo :: Int

    f :: ()

    documentation for foo

    This leading whitespace
    +should be dropped
    +

    bar :: Int

    g :: ()

    documentation for bar

     But this one
    + should not
    +
    this should
    +be dropped
    and so should this
    +because there's a space before closing @
    +
    this should +> be dropped + +@ + and so should this + because there's a space before closing @ + @ +-} +g :: () +g = () diff --git a/src/Haddock/Parser.hs b/src/Haddock/Parser.hs index cd7bb02..bd5cd20 100644 --- a/src/Haddock/Parser.hs +++ b/src/Haddock/Parser.hs @@ -2,6 +2,7 @@ {-# LANGUAGE StandaloneDeriving , FlexibleInstances, UndecidableInstances , IncoherentInstances #-} +{-# LANGUAGE LambdaCase #-} -- | -- Module : Haddock.Parser -- Copyright : (c) Mateusz Kowalczyk 2013, @@ -21,7 +22,7 @@ import Control.Applicative import Data.Attoparsec.ByteString.Char8 hiding (parse, take, endOfLine) import qualified Data.ByteString.Char8 as BS import Data.Char (chr, isAsciiUpper) -import Data.List (stripPrefix, intercalate) +import Data.List (stripPrefix, intercalate, unfoldr) import Data.Maybe (fromMaybe) import Data.Monoid import DynFlags @@ -59,7 +60,8 @@ parseParas d = parse (p <* skipSpace) . encodeUtf8 . (++ "\n") p :: Parser (Doc RdrName) p = mconcat <$> paragraph d `sepBy` many (skipHorizontalSpace *> "\n") --- | Parse a text paragraph. +-- | Parse a text paragraph. Actually just a wrapper over 'parseStringBS' which +-- drops leading whitespace and encodes the string to UTF8 first. parseString :: DynFlags -> String -> Doc RdrName parseString d = parseStringBS d . encodeUtf8 . dropWhile isSpace @@ -366,8 +368,31 @@ property = DocProperty . strip . decodeUtf8 <$> ("prop>" *> takeWhile1 (/= '\n') -- for markup. codeblock :: DynFlags -> Parser (Doc RdrName) codeblock d = - DocCodeBlock . parseStringBS d <$> ("@" *> skipHorizontalSpace *> "\n" *> block' <* "@") + DocCodeBlock . parseStringBS d . dropSpaces + <$> ("@" *> skipHorizontalSpace *> "\n" *> block' <* "@") where + dropSpaces xs = + let rs = decodeUtf8 xs + in case splitByNl rs of + [] -> xs + ys -> case last ys of + ' ':_ -> case mapM dropSpace ys of + Nothing -> xs + Just zs -> encodeUtf8 $ intercalate "\n" zs + _ -> xs + + -- This is necessary because ?lines? swallows up a trailing newline + -- and we lose information about whether the last line belongs to @ or to + -- text which we need to decide whether we actually want to be dropping + -- anything at all. + splitByNl = unfoldr (\case '\n':s -> Just (span (/= '\n') s) + _ -> Nothing) + . ('\n' :) + + dropSpace "" = Just "" + dropSpace (' ':xs) = Just xs + dropSpace _ = Nothing + block' = scan False p where p isNewline c diff --git a/test/Haddock/ParserSpec.hs b/test/Haddock/ParserSpec.hs index db843cc..f44b7d0 100644 --- a/test/Haddock/ParserSpec.hs +++ b/test/Haddock/ParserSpec.hs @@ -432,12 +432,34 @@ spec = before initStaticOpts $ do ] `shouldParseTo` DocCodeBlock "foo\n@\nbar\n" it "accepts horizontal space before the @" $ do + unlines [ " @" + , "foo" + , "" + , "bar" + , "@" + ] `shouldParseTo` DocCodeBlock "foo\n\nbar\n" + + it "strips a leading space from a @ block if present" $ do + unlines [ " @" + , " hello" + , " world" + , " @" + ] `shouldParseTo` DocCodeBlock "hello\nworld\n" + unlines [ " @" - , " foo" + , " hello" , "" - , " bar" + , " world" , " @" - ] `shouldParseTo` DocCodeBlock " foo\n\n bar\n " + ] `shouldParseTo` DocCodeBlock "hello\n\nworld\n" + + it "only drops whitespace if there's some before closing @" $ do + unlines [ "@" + , " Formatting" + , " matters." + , "@" + ] + `shouldParseTo` DocCodeBlock " Formatting\n matters.\n" it "accepts unicode" $ do "@foo ?????? bar@" `shouldParseTo` DocCodeBlock "foo ?????? bar" From git at git.haskell.org Mon Mar 31 18:17:53 2014 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 31 Mar 2014 18:17:53 +0000 (UTC) Subject: [commit: haddock] master: Crash when exporting record selectors of data family instances (a6e36fc) Message-ID: <20140331181753.206042406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haddock On branch : master Link : http://git.haskell.org/haddock.git/commitdiff/a6e36fc8cde675c2b7b2bc8f519221c93f20f207 >--------------------------------------------------------------- commit a6e36fc8cde675c2b7b2bc8f519221c93f20f207 Author: Niklas Haas Date: Mon Mar 31 20:02:36 2014 +0200 Crash when exporting record selectors of data family instances This fixes bug #294. This also fixes a related but never-before-mentioned bug about the display of GADT record selectors with non-polymorphic type signatures. Note: Associated data type constructors fail to show up if nothing is exported that they could be attached to. Exporting any of the data types in the instance head, or the class + data family itself, causes them to show up, but in the absence of either of these, exporting just the associated data type with the constructor itself will result in it being hidden. The only scenario I can come up that would involve this kind of situation involved OverlappingInstances, and even then it can be mitigated by just exporting the class itself, so I'm not going to solve it since the logic would most likely be very complicated. >--------------------------------------------------------------- a6e36fc8cde675c2b7b2bc8f519221c93f20f207 .../ref/{HiddenInstances.html => Bug294.html} | 148 ++++++++++---------- html-test/src/Bug294.hs | 37 +++++ src/Haddock/Interface/Create.hs | 34 +++-- 3 files changed, 136 insertions(+), 83 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a6e36fc8cde675c2b7b2bc8f519221c93f20f207