From git at git.haskell.org Thu Feb 1 04:29:51 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 1 Feb 2018 04:29:51 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Fix test output broken by efba054640d3 (7d9812e) Message-ID: <20180201042951.C76B33A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7d9812e8f4e8723c94a8ee9f7ba629ac9f1d4e71/ghc >--------------------------------------------------------------- commit 7d9812e8f4e8723c94a8ee9f7ba629ac9f1d4e71 Author: Ben Gamari Date: Wed Jan 31 23:02:52 2018 -0500 testsuite: Fix test output broken by efba054640d3 Looks right to me. >--------------------------------------------------------------- 7d9812e8f4e8723c94a8ee9f7ba629ac9f1d4e71 testsuite/tests/typecheck/should_fail/T10619.stderr | 4 ++-- testsuite/tests/typecheck/should_fail/T5691.stderr | 10 +++++----- 2 files changed, 7 insertions(+), 7 deletions(-) diff --git a/testsuite/tests/typecheck/should_fail/T10619.stderr b/testsuite/tests/typecheck/should_fail/T10619.stderr index 0cd5364..fde2daf 100644 --- a/testsuite/tests/typecheck/should_fail/T10619.stderr +++ b/testsuite/tests/typecheck/should_fail/T10619.stderr @@ -1,6 +1,6 @@ T10619.hs:9:15: error: - • Couldn't match type ‘b -> b’ with ‘forall a. a -> a’ + • Couldn't match type ‘forall a. a -> a’ with ‘b -> b’ Expected type: (b -> b) -> b -> b Actual type: (forall a. a -> a) -> b -> b • In the expression: @@ -40,7 +40,7 @@ T10619.hs:14:15: error: bar :: p -> (b -> b) -> b -> b (bound at T10619.hs:12:1) T10619.hs:16:13: error: - • Couldn't match type ‘b -> b’ with ‘forall a. a -> a’ + • Couldn't match type ‘forall a. a -> a’ with ‘b -> b’ Expected type: (b -> b) -> b -> b Actual type: (forall a. a -> a) -> b -> b • In the expression: diff --git a/testsuite/tests/typecheck/should_fail/T5691.stderr b/testsuite/tests/typecheck/should_fail/T5691.stderr index 9d4e587..ad5c7e4 100644 --- a/testsuite/tests/typecheck/should_fail/T5691.stderr +++ b/testsuite/tests/typecheck/should_fail/T5691.stderr @@ -1,12 +1,12 @@ -T5691.hs:15:24: error: +T5691.hs:14:9: error: • Couldn't match type ‘p’ with ‘PrintRuleInterp’ Expected type: PrintRuleInterp a Actual type: p a - • In the first argument of ‘printRule_’, namely ‘f’ - In the second argument of ‘($)’, namely ‘printRule_ f’ - In the expression: MkPRI $ printRule_ f - • Relevant bindings include f :: p a (bound at T5691.hs:14:9) + • When checking that the pattern signature: p a + fits the type of its context: PrintRuleInterp a + In the pattern: f :: p a + In an equation for ‘test’: test (f :: p a) = MkPRI $ printRule_ f T5691.hs:24:10: error: • No instance for (Alternative RecDecParser) From git at git.haskell.org Thu Feb 1 04:29:54 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 1 Feb 2018 04:29:54 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Fix test output of T14715 (fe6fdf6) Message-ID: <20180201042954.DC70F3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fe6fdf689853f5d6e4ef01ba9952e4be48a92f45/ghc >--------------------------------------------------------------- commit fe6fdf689853f5d6e4ef01ba9952e4be48a92f45 Author: Ben Gamari Date: Wed Jan 31 22:53:16 2018 -0500 testsuite: Fix test output of T14715 Arguably the warning should just be disabled for this test to eliminate unnecessary wiggle in the future. >--------------------------------------------------------------- fe6fdf689853f5d6e4ef01ba9952e4be48a92f45 testsuite/tests/partial-sigs/should_compile/T14715.stderr | 11 ++++++++++- 1 file changed, 10 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/partial-sigs/should_compile/T14715.stderr b/testsuite/tests/partial-sigs/should_compile/T14715.stderr index 0519ecb..c846b47 100644 --- a/testsuite/tests/partial-sigs/should_compile/T14715.stderr +++ b/testsuite/tests/partial-sigs/should_compile/T14715.stderr @@ -1 +1,10 @@ - \ No newline at end of file +T14715.hs:13:53: warning: [-Wpartial-type-signatures (in -Wdefault)] + Found type wildcard ‘_’ standing for ‘Reduce (LiftOf zq) zq’ + Where: ‘zq’ is a rigid type variable bound by + the inferred type of + bench_mulPublic :: (z ~ LiftOf zq, Reduce (LiftOf zq) zq) => + Cyc zp -> Cyc z -> IO (zp, zq) + at T14715.hs:(14,1)-(16,14) + In the type signature: + bench_mulPublic :: forall z zp zq. + (z ~ LiftOf zq, _) => Cyc zp -> Cyc z -> IO (zp, zq) From git at git.haskell.org Thu Feb 1 04:29:58 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 1 Feb 2018 04:29:58 +0000 (UTC) Subject: [commit: ghc] master: Make RTS keep less memory (fixes #14702) (0171e09) Message-ID: <20180201042958.099383A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0171e09e4d073d8466953ebbf01292e55829fb20/ghc >--------------------------------------------------------------- commit 0171e09e4d073d8466953ebbf01292e55829fb20 Author: Andrey Sverdlichenko Date: Wed Jan 31 21:33:58 2018 -0500 Make RTS keep less memory (fixes #14702) Currently runtime keeps hold to 4*used_memory. This includes, in particular, nursery, which can be quite large on multiprocessor machines: 16 CPUs x 64Mb each is 1GB. Multiplying it by 4 means whatever actual memory usage is, runtime will never release memory under 4GB, and this is quite excessive for processes which only need a lot of memory shortly (think building data structures from large files). This diff makes multiplier to apply only to GC-managed memory, leaving all "static" allocations alone. Test Plan: make test TEST="T14702" Reviewers: bgamari, erikd, simonmar Reviewed By: simonmar Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14702 Differential Revision: https://phabricator.haskell.org/D4338 >--------------------------------------------------------------- 0171e09e4d073d8466953ebbf01292e55829fb20 rts/RetainerProfile.c | 2 -- rts/RetainerProfile.h | 2 -- rts/sm/GC.c | 52 ++++++++++++++++++++++++++++++++++--------- testsuite/tests/rts/T14702.hs | 36 ++++++++++++++++++++++++++++++ testsuite/tests/rts/all.T | 5 +++++ 5 files changed, 83 insertions(+), 14 deletions(-) diff --git a/rts/RetainerProfile.c b/rts/RetainerProfile.c index 7a9b9cc..4badbfe 100644 --- a/rts/RetainerProfile.c +++ b/rts/RetainerProfile.c @@ -279,7 +279,6 @@ isEmptyRetainerStack( void ) /* ----------------------------------------------------------------------------- * Returns size of stack * -------------------------------------------------------------------------- */ -#if defined(DEBUG) W_ retainerStackBlocks( void ) { @@ -291,7 +290,6 @@ retainerStackBlocks( void ) return res; } -#endif /* ----------------------------------------------------------------------------- * Returns true if stackTop is at the stack boundary of the current stack, diff --git a/rts/RetainerProfile.h b/rts/RetainerProfile.h index 6882a2a..bc11cc7 100644 --- a/rts/RetainerProfile.h +++ b/rts/RetainerProfile.h @@ -41,9 +41,7 @@ retainerSetOf( const StgClosure *c ) } // Used by Storage.c:memInventory() -#if defined(DEBUG) extern W_ retainerStackBlocks ( void ); -#endif #include "EndPrivate.h" diff --git a/rts/sm/GC.c b/rts/sm/GC.c index c5ab7a8..197b466 100644 --- a/rts/sm/GC.c +++ b/rts/sm/GC.c @@ -28,6 +28,7 @@ #include "Sparks.h" #include "Sweep.h" +#include "Arena.h" #include "Storage.h" #include "RtsUtils.h" #include "Apply.h" @@ -50,6 +51,10 @@ #include "CNF.h" #include "RtsFlags.h" +#if defined(PROFILING) +#include "RetainerProfile.h" +#endif + #include // for memset() #include @@ -756,24 +761,51 @@ GarbageCollect (uint32_t collect_gen, ACQUIRE_SM_LOCK; if (major_gc) { - W_ need, got; - need = BLOCKS_TO_MBLOCKS(n_alloc_blocks); - got = mblocks_allocated; + W_ need_prealloc, need_live, need, got; + uint32_t i; + + need_live = 0; + for (i = 0; i < RtsFlags.GcFlags.generations; i++) { + need_live += genLiveBlocks(&generations[i]); + } + need_live = stg_max(RtsFlags.GcFlags.minOldGenSize, need_live); + + need_prealloc = 0; + for (i = 0; i < n_nurseries; i++) { + need_prealloc += nurseries[i].n_blocks; + } + need_prealloc += RtsFlags.GcFlags.largeAllocLim; + need_prealloc += countAllocdBlocks(exec_block); + need_prealloc += arenaBlocks(); +#if defined(PROFILING) + if (RtsFlags.ProfFlags.doHeapProfile == HEAP_BY_RETAINER) { + need_prealloc = retainerStackBlocks(); + } +#endif + /* If the amount of data remains constant, next major GC we'll - require (F+1)*need. We leave (F+2)*need in order to reduce - repeated deallocation and reallocation. */ - need = (RtsFlags.GcFlags.oldGenFactor + 2) * need; + * require (F+1)*live + prealloc. We leave (F+2)*live + prealloc + * in order to reduce repeated deallocation and reallocation. #14702 + */ + need = need_prealloc + (RtsFlags.GcFlags.oldGenFactor + 2) * need_live; + + /* Also, if user set heap size, do not drop below it. + */ + need = stg_max(RtsFlags.GcFlags.heapSizeSuggestion, need); + /* But with a large nursery, the above estimate might exceed * maxHeapSize. A large resident set size might make the OS * kill this process, or swap unnecessarily. Therefore we * ensure that our estimate does not exceed maxHeapSize. */ if (RtsFlags.GcFlags.maxHeapSize != 0) { - W_ max = BLOCKS_TO_MBLOCKS(RtsFlags.GcFlags.maxHeapSize); - if (need > max) { - need = max; - } + need = stg_min(RtsFlags.GcFlags.maxHeapSize, need); } + + need = BLOCKS_TO_MBLOCKS(need); + + got = mblocks_allocated; + if (got > need) { returnMemoryToOS(got - need); } diff --git a/testsuite/tests/rts/T14702.hs b/testsuite/tests/rts/T14702.hs new file mode 100644 index 0000000..8e07529 --- /dev/null +++ b/testsuite/tests/rts/T14702.hs @@ -0,0 +1,36 @@ +module Main where + +import Control.Monad +import Data.Array.IO.Safe +import Data.Word +import GHC.Stats +import System.Exit +import System.Mem + +printAlloc :: String -> IO (Word64, Word64) +printAlloc name = do + performGC + details <- gc <$> getRTSStats + let dat = (gcdetails_live_bytes details, gcdetails_mem_in_use_bytes details) + putStrLn $ name ++ ": " ++ show dat + pure dat + +allocateAndPrint :: IO () +allocateAndPrint = do + -- allocate and touch a lot of memory (4MB * 260 ~ 1GB) + memoryHog <- forM [1 .. 300] $ \_ -> + (newArray (0, 1000000) 0 :: IO (IOUArray Word Word32)) + _ <- printAlloc "with large allocation" + -- do something with memory to prevent it from being GC'ed until now + forM_ memoryHog $ \a -> void $ readArray a 0 + +main :: IO () +main = do + (firstLive, firstTotal) <- printAlloc "initial" + allocateAndPrint + (lastLive, lastTotal) <- printAlloc "final" + + -- Now there is no reason to have more memory allocated than at start + let ratio = fromIntegral lastTotal / fromIntegral firstTotal + putStrLn $ "alloc ratio " ++ show ratio + when (ratio > 1.5) $ exitFailure diff --git a/testsuite/tests/rts/all.T b/testsuite/tests/rts/all.T index fe86dd1..ef77d57 100644 --- a/testsuite/tests/rts/all.T +++ b/testsuite/tests/rts/all.T @@ -383,3 +383,8 @@ test('T13832', exit_code(1), compile_and_run, ['-threaded']) test('T13894', normal, compile_and_run, ['']) test('T14497', normal, compile_and_run, ['-O']) test('T14695', normal, run_command, ['$MAKE -s --no-print-directory T14695']) +test('T14702', [ ignore_stdout + , only_ways(['threaded1', 'threaded2']) + , extra_run_opts('+RTS -A32m -N8 -T -RTS') + ] + , compile_and_run, ['']) From git at git.haskell.org Thu Feb 1 04:30:01 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 1 Feb 2018 04:30:01 +0000 (UTC) Subject: [commit: ghc] master: appveyor: Refactor (5f922fb) Message-ID: <20180201043001.233643A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5f922fbbef56dd4f0133ffe07ab8f0ebcb58fbaf/ghc >--------------------------------------------------------------- commit 5f922fbbef56dd4f0133ffe07ab8f0ebcb58fbaf Author: Ben Gamari Date: Wed Jan 31 19:14:47 2018 -0500 appveyor: Refactor Move build logic into a dedicated bash script, avoiding repetitive bash invocations. Furthermore, disable pacman update step as it breaks things in non-predictable ways. >--------------------------------------------------------------- 5f922fbbef56dd4f0133ffe07ab8f0ebcb58fbaf .appveyor.sh | 50 ++++++++++++++++++++++++++++++++++++++++++++++++++ appveyor.yml | 19 +++---------------- 2 files changed, 53 insertions(+), 16 deletions(-) diff --git a/.appveyor.sh b/.appveyor.sh new file mode 100644 index 0000000..436e54b --- /dev/null +++ b/.appveyor.sh @@ -0,0 +1,50 @@ +# Configure the environment +MSYSTEM=MINGW64 +source /etc/profile || true # a terrible, terrible workaround for msys2 brokenness + +# Don't set -e until after /etc/profile is sourced +set -ex +cd $APPVEYOR_BUILD_FOLDER + +case "$1" in + "prepare") + # Bring msys up-to-date + # However, we current don't do this: generally one must restart all + # msys2 processes when updating the msys2 runtime, which this may do. We can't + # easily do this and therefore do simply don't update. + #pacman --noconfirm -Syuu + + # Install basic build dependencies + pacman --noconfirm -S --needed git tar bsdtar binutils autoconf make xz curl libtool automake python python2 p7zip patch mingw-w64-$(uname -m)-python3-sphinx mingw-w64-$(uname -m)-tools-git + + # Prepare the tree + git config remote.origin.url git://github.com/ghc/ghc.git + git config --global url."git://github.com/ghc/packages-".insteadOf git://github.com/ghc/packages/ + git submodule init + git submodule --quiet update --recursive + + # Install build dependencies + wget -q -O - https://downloads.haskell.org/~ghc/8.2.1/ghc-8.2.1-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1 + mkdir -p /usr/local/bin + wget -q -O - https://www.haskell.org/cabal/release/cabal-install-1.24.0.0/cabal-install-1.24.0.0-x86_64-unknown-mingw32.zip | bsdtar -xzf- -C /usr/local/bin + cabal update + cabal install -j --prefix=/usr/local alex happy + ;; + + "build") + # Build the compiler + ./boot + ./configure --enable-tarballs-autodownload + make -j2 + ;; + + "test") + make binary_dist + 7z a ghc-windows.zip *.tar.xz + ;; + + *) + echo "$0: unknown mode $1" + exit 1 + ;; +esac diff --git a/appveyor.yml b/appveyor.yml index 0af5304..7ccf2e0 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -18,24 +18,11 @@ deploy: off install: - cmd: | SET "PATH=C:\%MSYS2_DIR%\%MSYSTEM%\bin;C:\%MSYS2_DIR%\usr\bin;%PATH%" - bash -lc "pacman --noconfirm -Syuu" - bash -lc "pacman --noconfirm -S --needed git tar bsdtar binutils autoconf make xz curl libtool automake python python2 p7zip patch mingw-w64-$(uname -m)-python3-sphinx mingw-w64-$(uname -m)-tools-git" - bash -lc "cd $APPVEYOR_BUILD_FOLDER; git config remote.origin.url git://github.com/ghc/ghc.git" - bash -lc "cd $APPVEYOR_BUILD_FOLDER; git config --global url.\"git://github.com/ghc/packages-\".insteadOf git://github.com/ghc/packages/" - bash -lc "cd $APPVEYOR_BUILD_FOLDER; git submodule init" - bash -lc "cd $APPVEYOR_BUILD_FOLDER; git submodule --quiet update --recursive" - bash -lc "curl -L https://downloads.haskell.org/~ghc/8.2.1/ghc-8.2.1-x86_64-unknown-mingw32.tar.xz | tar -xJ -C /mingw64 --strip-components=1" - bash -lc "mkdir -p /usr/local/bin" - bash -lc "curl -L https://www.haskell.org/cabal/release/cabal-install-1.24.0.0/cabal-install-1.24.0.0-x86_64-unknown-mingw32.zip | bsdtar -xzf- -C /usr/local/bin" - bash -lc "cabal update" - bash -lc "cabal install -j --prefix=/usr/local alex happy" + bash .appveyor.sh prepare build_script: - - bash -lc "cd $APPVEYOR_BUILD_FOLDER; ./boot" - - bash -lc "cd $APPVEYOR_BUILD_FOLDER; ./configure --enable-tarballs-autodownload" - - bash -lc "cd $APPVEYOR_BUILD_FOLDER; make -j2" - - bash -lc "cd $APPVEYOR_BUILD_FOLDER; make binary_dist" - bash -lc "cd $APPVEYOR_BUILD_FOLDER; 7z a ghc-windows.zip *.tar.xz" + - bash .appveyor.sh build + - bash .appveyor.sh test artifacts: - path: C:\projects\ghc\ghc-windows.zip From git at git.haskell.org Thu Feb 1 04:30:04 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 1 Feb 2018 04:30:04 +0000 (UTC) Subject: [commit: ghc] master: Don't add targets that can't be found in GHCi (0bff9e6) Message-ID: <20180201043004.675E33A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0bff9e677f0569bc8a7207c20cddddfd67e2448f/ghc >--------------------------------------------------------------- commit 0bff9e677f0569bc8a7207c20cddddfd67e2448f Author: Julian Priestley Date: Wed Jan 31 21:35:00 2018 -0500 Don't add targets that can't be found in GHCi When using the :add command in haxlsh/ghci, a module/file that can't be found is still added to the list of targets, resulting in an error message for the bad module/file for every subsequent usage of the command. The add command should verify that the module/file can be found before adding it to the list of targets. Also add a ":show targets" command to show the currently added list of commands, and an ":unadd" command to remove a target. Test Plan: Add a new GHCi testcase that checks that :add doesn't remember either files or modules that could not be found, and that both the new :show and :unadd commands work as expected. Reviewers: simonmar, bgamari Reviewed By: simonmar Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14676 Differential Revision: https://phabricator.haskell.org/D4321 >--------------------------------------------------------------- 0bff9e677f0569bc8a7207c20cddddfd67e2448f ghc/GHCi/UI.hs | 45 +++++++++++++++++++++++++++++- testsuite/tests/ghci/scripts/T14676.script | 7 +++++ testsuite/tests/ghci/scripts/T14676.stdout | 3 ++ testsuite/tests/ghci/scripts/all.T | 1 + 4 files changed, 55 insertions(+), 1 deletion(-) diff --git a/ghc/GHCi/UI.hs b/ghc/GHCi/UI.hs index 01c8505..b83ceeb 100644 --- a/ghc/GHCi/UI.hs +++ b/ghc/GHCi/UI.hs @@ -43,6 +43,7 @@ import GHCi.RemoteTypes import GHCi.BreakArray import DynFlags import ErrUtils hiding (traceCmd) +import Finder import GhcMonad ( modifySession ) import qualified GHC import GHC ( LoadHowMuch(..), Target(..), TargetId(..), InteractiveImport(..), @@ -208,6 +209,7 @@ ghciCommands = map mkCmd [ ("stepmodule",keepGoing stepModuleCmd, completeIdentifier), ("type", keepGoing' typeOfExpr, completeExpression), ("trace", keepGoing traceCmd, completeExpression), + ("unadd", keepGoingPaths unAddModule, completeFilename), ("undef", keepGoing undefineMacro, completeMacro), ("unset", keepGoing unsetOptions, completeSetOptions), ("where", keepGoing whereCmd, noCompletion) @@ -305,6 +307,7 @@ defFullHelpText = " :type show the type of \n" ++ " :type +d show the type of , defaulting type variables\n" ++ " :type +v show the type of , with its specified tyvars\n" ++ + " :unadd ... remove module(s) from the current target set\n" ++ " :undef undefine user-defined command :\n" ++ " :! run the shell command \n" ++ "\n" ++ @@ -371,6 +374,7 @@ defFullHelpText = " :show packages show the currently active package flags\n" ++ " :show paths show the currently active search paths\n" ++ " :show language show the currently active language flags\n" ++ + " :show targets show the current set of targets\n" ++ " :show show value of , which is one of\n" ++ " [args, prog, editor, stop]\n" ++ " :showi language show language flags for interactive evaluation\n" ++ @@ -1657,9 +1661,39 @@ addModule files = do lift revertCAFs -- always revert CAFs on load/add. files' <- mapM expandPath files targets <- mapM (\m -> GHC.guessTarget m Nothing) files' + targets' <- filterM checkTarget targets -- remove old targets with the same id; e.g. for :add *M + mapM_ GHC.removeTarget [ tid | Target tid _ _ <- targets' ] + mapM_ GHC.addTarget targets' + _ <- doLoadAndCollectInfo False LoadAllTargets + return () + where + checkTarget :: Target -> InputT GHCi Bool + checkTarget (Target (TargetModule m) _ _) = checkTargetModule m + checkTarget (Target (TargetFile f _) _ _) = liftIO $ checkTargetFile f + + checkTargetModule :: ModuleName -> InputT GHCi Bool + checkTargetModule m = do + hsc_env <- GHC.getSession + result <- liftIO $ + Finder.findImportedModule hsc_env m (Just (fsLit "this")) + case result of + Found _ _ -> return True + _ -> (liftIO $ putStrLn $ + "Module " ++ moduleNameString m ++ " not found") >> return False + + checkTargetFile :: String -> IO Bool + checkTargetFile f = do + exists <- (doesFileExist f) :: IO Bool + unless exists $ putStrLn $ "File " ++ f ++ " not found" + return exists + +-- | @:unadd@ command +unAddModule :: [FilePath] -> InputT GHCi () +unAddModule files = do + files' <- mapM expandPath files + targets <- mapM (\m -> GHC.guessTarget m Nothing) files' mapM_ GHC.removeTarget [ tid | Target tid _ _ <- targets ] - mapM_ GHC.addTarget targets _ <- doLoadAndCollectInfo False LoadAllTargets return () @@ -2779,6 +2813,7 @@ showCmd str = do , action "language" $ showLanguages , hidden "languages" $ showLanguages -- backwards compat , hidden "lang" $ showLanguages -- useful abbreviation + , action "targets" $ showTargets ] case words str of @@ -2941,6 +2976,14 @@ showLanguages' show_all dflags = Nothing -> Just Haskell2010 other -> other +showTargets :: GHCi () +showTargets = mapM_ showTarget =<< GHC.getTargets + where + showTarget :: Target -> GHCi () + showTarget (Target (TargetFile f _) _ _) = liftIO (putStrLn f) + showTarget (Target (TargetModule m) _ _) = + liftIO (putStrLn $ moduleNameString m) + -- ----------------------------------------------------------------------------- -- Completion diff --git a/testsuite/tests/ghci/scripts/T14676.script b/testsuite/tests/ghci/scripts/T14676.script new file mode 100644 index 0000000..9cfe693 --- /dev/null +++ b/testsuite/tests/ghci/scripts/T14676.script @@ -0,0 +1,7 @@ +:add Notfound.hs +:add NotFound +:show targets +:add prog002/A1.hs +:show targets +:unadd prog002/A1.hs +:show targets diff --git a/testsuite/tests/ghci/scripts/T14676.stdout b/testsuite/tests/ghci/scripts/T14676.stdout new file mode 100644 index 0000000..c3e9fbd --- /dev/null +++ b/testsuite/tests/ghci/scripts/T14676.stdout @@ -0,0 +1,3 @@ +File Notfound.hs not found +Module NotFound not found +prog002/A1.hs diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T index ced4841..997203f 100755 --- a/testsuite/tests/ghci/scripts/all.T +++ b/testsuite/tests/ghci/scripts/all.T @@ -263,3 +263,4 @@ test('T13407', normal, ghci_script, ['T13407.script']) test('T13963', normal, ghci_script, ['T13963.script']) test('T14342', [extra_hc_opts("-XOverloadedStrings -XRebindableSyntax")], ghci_script, ['T14342.script']) +test('T14676', extra_files(['../prog002']), ghci_script, ['T14676.script']) From git at git.haskell.org Thu Feb 1 04:30:08 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 1 Feb 2018 04:30:08 +0000 (UTC) Subject: [commit: ghc] master: Implement BlockArguments (#10843) (be84823) Message-ID: <20180201043008.743EE3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/be84823b956f0aa09c58d94d1901f2dff13546b4/ghc >--------------------------------------------------------------- commit be84823b956f0aa09c58d94d1901f2dff13546b4 Author: Takano Akio Date: Wed Jan 31 21:35:29 2018 -0500 Implement BlockArguments (#10843) This patch implements the BlockArguments extension, as proposed at https://github.com/ghc-proposals/ghc-proposals/pull/90. It also fixes #10855 as a side-effect. This patch adds a large number of shift-reduce conflicts to the parser. All of them concern the ambiguity as to where constructs like `if` and `let` end. Fortunately they are resolved correctly by preferring shift. The patch is based on @gibiansky's ArgumentDo implementation (D1219). Test Plan: ./validate Reviewers: goldfire, bgamari, alanz, mpickering Reviewed By: bgamari, mpickering Subscribers: Wizek, dfeuer, gibiansky, rwbarton, thomie, mpickering, carter GHC Trac Issues: #10843, #10855 Differential Revision: https://phabricator.haskell.org/D4260 >--------------------------------------------------------------- be84823b956f0aa09c58d94d1901f2dff13546b4 compiler/main/DynFlags.hs | 1 + compiler/parser/Lexer.x | 17 +- compiler/parser/Parser.y | 188 +++++++++++++-------- compiler/parser/RdrHsSyn.hs | 24 +++ docs/users_guide/bugs.rst | 6 - docs/users_guide/glasgow_exts.rst | 98 +++++++++++ .../ghc-boot-th/GHC/LanguageExtensions/Type.hs | 1 + testsuite/tests/driver/T4437.hs | 1 + .../tests/parser/should_compile/BlockArguments.hs | 25 +++ .../should_compile/BlockArgumentsLambdaCase.hs | 13 ++ .../parser/should_compile/NoBlockArguments.hs | 8 + testsuite/tests/parser/should_compile/T10855.hs | 5 + testsuite/tests/parser/should_compile/all.T | 4 + .../parser/should_fail/NoBlockArgumentsFail.hs | 7 + .../parser/should_fail/NoBlockArgumentsFail.stderr | 6 + .../parser/should_fail/NoBlockArgumentsFail2.hs | 6 + .../should_fail/NoBlockArgumentsFail2.stderr | 6 + .../parser/should_fail/NoBlockArgumentsFail3.hs | 8 + .../should_fail/NoBlockArgumentsFail3.stderr | 6 + .../parser/should_fail/ParserNoLambdaCase.stderr | 4 +- testsuite/tests/parser/should_fail/all.T | 3 + testsuite/tests/perf/compiler/all.T | 3 +- 22 files changed, 355 insertions(+), 85 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc be84823b956f0aa09c58d94d1901f2dff13546b4 From git at git.haskell.org Thu Feb 1 04:30:11 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 1 Feb 2018 04:30:11 +0000 (UTC) Subject: [commit: ghc] master: rts: Ensure that forkOS releases Task on termination (382c12d) Message-ID: <20180201043011.429C43A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/382c12d18f3d64e01502a5c8bbc64d4aa4842e3e/ghc >--------------------------------------------------------------- commit 382c12d18f3d64e01502a5c8bbc64d4aa4842e3e Author: Ben Gamari Date: Wed Jan 31 21:37:21 2018 -0500 rts: Ensure that forkOS releases Task on termination Test Plan: validate Reviewers: simonmar, erikd Reviewed By: simonmar Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14725 Differential Revision: https://phabricator.haskell.org/D4346 >--------------------------------------------------------------- 382c12d18f3d64e01502a5c8bbc64d4aa4842e3e rts/posix/OSThreads.c | 1 + rts/win32/OSThreads.c | 1 + 2 files changed, 2 insertions(+) diff --git a/rts/posix/OSThreads.c b/rts/posix/OSThreads.c index e2471a2..9cf42aa 100644 --- a/rts/posix/OSThreads.c +++ b/rts/posix/OSThreads.c @@ -223,6 +223,7 @@ forkOS_createThreadWrapper ( void * entry ) cap = rts_lock(); rts_evalStableIO(&cap, (HsStablePtr) entry, NULL); rts_unlock(cap); + rts_done(); return NULL; } diff --git a/rts/win32/OSThreads.c b/rts/win32/OSThreads.c index ad42340..b1a98ce 100644 --- a/rts/win32/OSThreads.c +++ b/rts/win32/OSThreads.c @@ -236,6 +236,7 @@ forkOS_createThreadWrapper ( void * entry ) cap = rts_lock(); rts_evalStableIO(&cap, (HsStablePtr) entry, NULL); rts_unlock(cap); + rts_done(); return 0; } From git at git.haskell.org Thu Feb 1 04:30:14 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 1 Feb 2018 04:30:14 +0000 (UTC) Subject: [commit: ghc] master: Mark xmm6 as caller saved in the register allocator for windows. (add4e1f) Message-ID: <20180201043014.6628F3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/add4e1f11b88cd603f6c01bc135eb576e1922a8e/ghc >--------------------------------------------------------------- commit add4e1f11b88cd603f6c01bc135eb576e1922a8e Author: klebinger.andreas at gmx.at Date: Wed Jan 31 21:39:19 2018 -0500 Mark xmm6 as caller saved in the register allocator for windows. This prevents the register being picked up as a scratch register. Otherwise the allocator would be free to use it before a call. This fixes #14619. Test Plan: ci, repro case on #14619 Reviewers: bgamari, Phyx, erikd, simonmar, RyanGlScott, simonpj Reviewed By: Phyx, RyanGlScott, simonpj Subscribers: simonpj, RyanGlScott, Phyx, rwbarton, thomie, carter GHC Trac Issues: #14619 Differential Revision: https://phabricator.haskell.org/D4348 >--------------------------------------------------------------- add4e1f11b88cd603f6c01bc135eb576e1922a8e compiler/nativeGen/X86/Regs.hs | 6 ++-- includes/rts/Constants.h | 8 +++-- rts/StgCRun.c | 33 ++++++++++++++--- testsuite/tests/codeGen/should_run/T14619.hs | 46 ++++++++++++++++++++++++ testsuite/tests/codeGen/should_run/T14619.stdout | 1 + testsuite/tests/codeGen/should_run/all.T | 1 + 6 files changed, 86 insertions(+), 9 deletions(-) diff --git a/compiler/nativeGen/X86/Regs.hs b/compiler/nativeGen/X86/Regs.hs index 169d402..d6983b7 100644 --- a/compiler/nativeGen/X86/Regs.hs +++ b/compiler/nativeGen/X86/Regs.hs @@ -238,7 +238,6 @@ xmmregnos platform = [firstxmm .. lastxmm platform] floatregnos :: Platform -> [RegNo] floatregnos platform = fakeregnos ++ xmmregnos platform - -- argRegs is the set of regs which are read for an n-argument call to C. -- For archs which pass all args on the stack (x86), is empty. -- Sparc passes up to the first 6 args in regs. @@ -408,7 +407,10 @@ 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) + -- Only xmm0-5 are caller-saves registers on 64bit windows. + -- ( https://docs.microsoft.com/en-us/cpp/build/register-usage ) + -- For details check the Win64 ABI. + ++ map regSingle fakeregnos ++ map xmm [0 .. 5] | otherwise -- all xmm regs are caller-saves -- caller-saves registers diff --git a/includes/rts/Constants.h b/includes/rts/Constants.h index 27097bf..5774bd7 100644 --- a/includes/rts/Constants.h +++ b/includes/rts/Constants.h @@ -113,11 +113,15 @@ /* ----------------------------------------------------------------------------- How large is the stack frame saved by StgRun? world. Used in StgCRun.c. + + The size has to be enough to save the registers (see StgCRun) + plus padding if the result is not 16 byte aligned. + See the Note [Stack Alignment on X86] in StgCRun.c for details. + -------------------------------------------------------------------------- */ #if defined(x86_64_HOST_ARCH) # if defined(mingw32_HOST_OS) -/* 8 larger than necessary to make the alignment right*/ -# define STG_RUN_STACK_FRAME_SIZE 80 +# define STG_RUN_STACK_FRAME_SIZE 144 # else # define STG_RUN_STACK_FRAME_SIZE 48 # endif diff --git a/rts/StgCRun.c b/rts/StgCRun.c index 5460598..ab66c64 100644 --- a/rts/StgCRun.c +++ b/rts/StgCRun.c @@ -236,7 +236,7 @@ StgRunIsImplementedInAssembler(void) ); } -#endif +#endif // defined(i386_HOST_ARCH) /* ---------------------------------------------------------------------------- x86-64 is almost the same as plain x86. @@ -279,9 +279,23 @@ StgRunIsImplementedInAssembler(void) "movq %%r14,32(%%rax)\n\t" "movq %%r15,40(%%rax)\n\t" #if defined(mingw32_HOST_OS) + /* + * Additional callee saved registers on Win64. This must match + * callClobberedRegisters in compiler/nativeGen/X86/Regs.hs as + * both represent the Win64 calling convention. + */ "movq %%rdi,48(%%rax)\n\t" "movq %%rsi,56(%%rax)\n\t" - "movq %%xmm6,64(%%rax)\n\t" + "movq %%xmm6, 64(%%rax)\n\t" + "movq %%xmm7, 72(%%rax)\n\t" + "movq %%xmm8, 80(%%rax)\n\t" + "movq %%xmm9, 88(%%rax)\n\t" + "movq %%xmm10, 96(%%rax)\n\t" + "movq %%xmm11,104(%%rax)\n\t" + "movq %%xmm12,112(%%rax)\n\t" + "movq %%xmm13,120(%%rax)\n\t" + "movq %%xmm14,128(%%rax)\n\t" + "movq %%xmm15,136(%%rax)\n\t" #endif /* * Set BaseReg @@ -317,9 +331,18 @@ StgRunIsImplementedInAssembler(void) "movq 32(%%rsp),%%r14\n\t" "movq 40(%%rsp),%%r15\n\t" #if defined(mingw32_HOST_OS) - "movq 48(%%rsp),%%rdi\n\t" - "movq 56(%%rsp),%%rsi\n\t" - "movq 64(%%rsp),%%xmm6\n\t" + "movq 48(%%rsp),%%rdi\n\t" + "movq 56(%%rsp),%%rsi\n\t" + "movq 64(%%rsp),%%xmm6\n\t" + "movq 72(%%rax),%%xmm7\n\t" + "movq 80(%%rax),%%xmm8\n\t" + "movq 88(%%rax),%%xmm9\n\t" + "movq 96(%%rax),%%xmm10\n\t" + "movq 104(%%rax),%%xmm11\n\t" + "movq 112(%%rax),%%xmm12\n\t" + "movq 120(%%rax),%%xmm13\n\t" + "movq 128(%%rax),%%xmm14\n\t" + "movq 136(%%rax),%%xmm15\n\t" #endif "addq %1, %%rsp\n\t" "retq" diff --git a/testsuite/tests/codeGen/should_run/T14619.hs b/testsuite/tests/codeGen/should_run/T14619.hs new file mode 100644 index 0000000..7af16df --- /dev/null +++ b/testsuite/tests/codeGen/should_run/T14619.hs @@ -0,0 +1,46 @@ +{-# OPTIONS_GHC -O1 #-} + +{- + On windows some xmm registers are callee saved. This means + they can't be used as scratch registers before a call to C. + + In #14619 this wasn't respected which lead to a wrong value + ending up in xmm6 and being returned in the final result. + + This code compiles to a non trivial fp computation followed + by a call to sqrt at O1+. If xmm6 isn't properly handled it + will be used as a scratch register failing the test. + + The original code used regular sqrt which on 8.2 generated + a C call in the backend. To imitate this behaviour on 8.4+ + we force a call to a C function instead. +-} + +module Main (main) where + + + +import Prelude hiding((*>), (<*)) +import Foreign.C +import Unsafe.Coerce + +foreign import ccall unsafe "sqrt" call_sqrt :: CDouble -> CDouble + +type V3 = (Double, Double, Double) + +absf :: V3 -> V3 -> Double +absf (x, y, z) (x', y', z') = x*x' +y*y'+z*z' + + +{-# NOINLINE sphereIntersection #-} +sphereIntersection :: V3 -> V3 -> (V3) +sphereIntersection orig dir@(_, _, dirz) + | b < 0 = undefined + | t1 > 0 = dir + | t1 < 0 = orig + | otherwise = undefined + where b = orig `absf` dir + sqrtDisc = realToFrac . call_sqrt $ CDouble b + t1 = b - sqrtDisc + +main = print $ sphereIntersection (11, 22, 33) (44, 55, 66) diff --git a/testsuite/tests/codeGen/should_run/T14619.stdout b/testsuite/tests/codeGen/should_run/T14619.stdout new file mode 100644 index 0000000..a11c04d --- /dev/null +++ b/testsuite/tests/codeGen/should_run/T14619.stdout @@ -0,0 +1 @@ +(44.0,55.0,66.0) diff --git a/testsuite/tests/codeGen/should_run/all.T b/testsuite/tests/codeGen/should_run/all.T index 42d8a2f..145365e 100644 --- a/testsuite/tests/codeGen/should_run/all.T +++ b/testsuite/tests/codeGen/should_run/all.T @@ -165,3 +165,4 @@ test('T13825-unit', extra_run_opts('"' + config.libdir + '"'), compile_and_run, ['-package ghc']) +test('T14619', normal, compile_and_run, ['']) From git at git.haskell.org Thu Feb 1 04:30:17 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 1 Feb 2018 04:30:17 +0000 (UTC) Subject: [commit: ghc] master: Sequester deriving-related validity check into cond_stdOK (1a911f2) Message-ID: <20180201043017.E8CE73A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1a911f217a18c8c0362ab2bf2b6ec7f7da015622/ghc >--------------------------------------------------------------- commit 1a911f217a18c8c0362ab2bf2b6ec7f7da015622 Author: Ryan Scott Date: Wed Jan 31 21:36:51 2018 -0500 Sequester deriving-related validity check into cond_stdOK Currently, any standalone-derived instance must satisfy the property that the tycon of the data type having an instance being derived for it must be either a normal ADT tycon or a data family tycon. But there are several other primitive tycons—such as `(->)`, `Int#`, and others—which cannot have standalone-derived instances (via the `anyclass` strategy) as a result of this check! See https://ghc.haskell.org/trac/ghc/ticket/13154#comment:8 for an example of where this overly conservative restriction bites. Really, this validity check only makes sense in the context of `stock` deriving, where we need the property that the tycon is that of a normal ADT or a data family in order to inspect its data constructors. Other deriving strategies don't require this validity check, so the most sensible way to fix this error is to move the logic of this check into `cond_stdOK`, which is specific to `stock` deriving. This makes progress towards fixing (but does not entirely fix) Test Plan: make test TEST=T13154a Reviewers: bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #13154 Differential Revision: https://phabricator.haskell.org/D4337 >--------------------------------------------------------------- 1a911f217a18c8c0362ab2bf2b6ec7f7da015622 compiler/typecheck/TcDeriv.hs | 19 ++-- compiler/typecheck/TcDerivUtils.hs | 123 ++++++++++++++------- testsuite/tests/deriving/should_compile/T13154a.hs | 14 +++ testsuite/tests/deriving/should_compile/all.T | 1 + 4 files changed, 111 insertions(+), 46 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1a911f217a18c8c0362ab2bf2b6ec7f7da015622 From git at git.haskell.org Thu Feb 1 04:30:20 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 1 Feb 2018 04:30:20 +0000 (UTC) Subject: [commit: ghc] master: Optimize coercionKind (Trac #11735) (e4ab65b) Message-ID: <20180201043020.ACC143A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e4ab65bd57b2c39f4af52879654514bb6d5b42a0/ghc >--------------------------------------------------------------- commit e4ab65bd57b2c39f4af52879654514bb6d5b42a0 Author: Tobias Dammers Date: Wed Jan 31 21:39:45 2018 -0500 Optimize coercionKind (Trac #11735) Reviewers: simonpj, goldfire, bgamari Reviewed By: simonpj Subscribers: rwbarton, thomie, carter GHC Trac Issues: #11735 Differential Revision: https://phabricator.haskell.org/D4355 >--------------------------------------------------------------- e4ab65bd57b2c39f4af52879654514bb6d5b42a0 compiler/types/Coercion.hs | 52 ++++++++++++++++++++++++++++++++-------------- 1 file changed, 36 insertions(+), 16 deletions(-) diff --git a/compiler/types/Coercion.hs b/compiler/types/Coercion.hs index cec56b1..7a7918c 100644 --- a/compiler/types/Coercion.hs +++ b/compiler/types/Coercion.hs @@ -1693,22 +1693,18 @@ coercionType co = case coercionKindRole co of -- i.e. the kind of @c@ relates @t1@ and @t2@, then @coercionKind c = Pair t1 t2 at . coercionKind :: Coercion -> Pair Type -coercionKind co = go co +coercionKind co = + {-# SCC "coercionKind" #-} + go co where go (Refl _ ty) = Pair ty ty go (TyConAppCo _ tc cos)= mkTyConApp tc <$> (sequenceA $ map go cos) go (AppCo co1 co2) = mkAppTy <$> go co1 <*> go co2 - go (ForAllCo tv1 k_co co) - = let Pair _ k2 = go k_co - tv2 = setTyVarKind tv1 k2 - Pair ty1 ty2 = go co - subst = zipTvSubst [tv1] [TyVarTy tv2 `mk_cast_ty` mkSymCo k_co] - ty2' = substTyAddInScope subst ty2 in - -- We need free vars of ty2 in scope to satisfy the invariant - -- from Note [The substitution invariant] - -- This is doing repeated substitutions and probably doesn't - -- need to, see #11735 - mkInvForAllTy <$> Pair tv1 tv2 <*> Pair ty1 ty2' + go co@(ForAllCo tv1 k_co co1) + | isReflCo k_co = mkInvForAllTy tv1 <$> go co1 + | otherwise = go_forall empty_subst co + where + empty_subst = mkEmptyTCvSubst (mkInScopeSet $ tyCoVarsOfCo co) go (FunCo _ co1 co2) = mkFunTy <$> go co1 <*> go co2 go (CoVarCo cv) = coVarTypes cv go (HoleCo h) = coVarTypes (coHoleCoVar h) @@ -1760,10 +1756,34 @@ coercionKind co = go co go_app (InstCo co arg) args = go_app co (arg:args) go_app co args = piResultTys <$> go co <*> (sequenceA $ map go args) - -- The real mkCastTy is too slow, and we can easily have nested ForAllCos. - mk_cast_ty :: Type -> Coercion -> Type - mk_cast_ty ty (Refl {}) = ty - mk_cast_ty ty co = CastTy ty co + go_forall subst (ForAllCo tv1 k_co co) + -- See Note [Nested ForAllCos] + = mkInvForAllTy <$> Pair tv1 tv2 <*> go_forall subst' co + where + Pair _ k2 = go k_co + tv2 = setTyVarKind tv1 (substTy subst k2) + subst' | isReflCo k_co = extendTCvInScope subst tv1 + | otherwise = extendTvSubst (extendTCvInScope subst tv2) tv1 $ + TyVarTy tv2 `mkCastTy` mkSymCo k_co + go_forall subst other_co + = substTy subst `pLiftSnd` go other_co + +{- + +Note [Nested ForAllCos] +~~~~~~~~~~~~~~~~~~~~~~~ + +Suppose we need `coercionKind (ForAllCo a1 (ForAllCo a2 ... (ForAllCo an +co)...) )`. We do not want to perform `n` single-type-variable +substitutions over the kind of `co`; rather we want to do one substitution +which substitutes for all of `a1`, `a2` ... simultaneously. If we do one +at a time we get the performance hole reported in Trac #11735. + +Solution: gather up the type variables for nested `ForAllCos`, and +substitute for them all at once. Remarkably, for Trac #11735 this single +change reduces /total/ compile time by a factor of more than ten. + +-} -- | Apply 'coercionKind' to multiple 'Coercion's coercionKinds :: [Coercion] -> Pair [Type] From git at git.haskell.org Thu Feb 1 04:30:24 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 1 Feb 2018 04:30:24 +0000 (UTC) Subject: [commit: ghc] master: UnboxedTuples can't be used as constraints (ced9fbd) Message-ID: <20180201043024.159F83A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ced9fbd3913e1316498961bc389bfb1e141221a1/ghc >--------------------------------------------------------------- commit ced9fbd3913e1316498961bc389bfb1e141221a1 Author: HE, Tao Date: Wed Jan 31 21:40:03 2018 -0500 UnboxedTuples can't be used as constraints Fixes #14740. Test Plan: make test TEST="14740" Reviewers: bgamari, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, thomie, carter GHC Trac Issues: #14740 Differential Revision: https://phabricator.haskell.org/D4359 >--------------------------------------------------------------- ced9fbd3913e1316498961bc389bfb1e141221a1 compiler/parser/RdrHsSyn.hs | 13 ++++++++++++- testsuite/tests/parser/should_fail/T14740.hs | 6 ++++++ testsuite/tests/parser/should_fail/T14740.stderr | 4 ++++ testsuite/tests/parser/should_fail/all.T | 1 + 4 files changed, 23 insertions(+), 1 deletion(-) diff --git a/compiler/parser/RdrHsSyn.hs b/compiler/parser/RdrHsSyn.hs index fcb1fed..357d224 100644 --- a/compiler/parser/RdrHsSyn.hs +++ b/compiler/parser/RdrHsSyn.hs @@ -849,11 +849,22 @@ checkBlockArguments expr = case unLoc expr of $$ text "You could write it with parentheses" $$ text "Or perhaps you meant to enable BlockArguments?" +-- | Validate the context constraints and break up a context into a list +-- of predicates. +-- +-- @ +-- (Eq a, Ord b) --> [Eq a, Ord b] +-- Eq a --> [Eq a] +-- (Eq a) --> [Eq a] +-- (((Eq a))) --> [Eq a] +-- @ checkContext :: LHsType GhcPs -> P ([AddAnn],LHsContext GhcPs) checkContext (L l orig_t) = check [] (L l orig_t) where - check anns (L lp (HsTupleTy _ ts)) -- (Eq a, Ord b) shows up as a tuple type + check anns (L lp (HsTupleTy HsBoxedOrConstraintTuple ts)) + -- (Eq a, Ord b) shows up as a tuple type. Only boxed tuples can + -- be used as context constraints. = return (anns ++ mkParensApiAnn lp,L l ts) -- Ditto () -- don't let HsAppsTy get in the way diff --git a/testsuite/tests/parser/should_fail/T14740.hs b/testsuite/tests/parser/should_fail/T14740.hs new file mode 100644 index 0000000..b56687f --- /dev/null +++ b/testsuite/tests/parser/should_fail/T14740.hs @@ -0,0 +1,6 @@ +{-# LANGUAGE UnboxedTuples #-} + +module T14740 where + +x :: ((##)) => () +x = () diff --git a/testsuite/tests/parser/should_fail/T14740.stderr b/testsuite/tests/parser/should_fail/T14740.stderr new file mode 100644 index 0000000..8827873 --- /dev/null +++ b/testsuite/tests/parser/should_fail/T14740.stderr @@ -0,0 +1,4 @@ + +T14740.hs:5:7: + Expecting a lifted type, but ‘(# #)’ is unlifted + In the type signature: x :: ((# #)) => () diff --git a/testsuite/tests/parser/should_fail/all.T b/testsuite/tests/parser/should_fail/all.T index 6f6331f..ef47ed3 100644 --- a/testsuite/tests/parser/should_fail/all.T +++ b/testsuite/tests/parser/should_fail/all.T @@ -106,6 +106,7 @@ test('T8501b', normal, compile_fail, ['']) test('T8501c', normal, compile_fail, ['']) test('T12610', normal, compile_fail, ['']) test('T14588', normal, compile_fail, ['']) +test('T14740', normal, compile_fail, ['']) test('NoNumericUnderscores0', normal, compile_fail, ['']) test('NoNumericUnderscores1', normal, compile_fail, ['']) From git at git.haskell.org Thu Feb 1 04:51:42 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 1 Feb 2018 04:51:42 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: Move zonkWC to the right place in simplfyInfer (e6c1474) Message-ID: <20180201045142.E58383A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/e6c147442fbeb161bbed209126186056f371d60c/ghc >--------------------------------------------------------------- commit e6c147442fbeb161bbed209126186056f371d60c Author: Simon Peyton Jones Date: Wed Jan 31 11:35:33 2018 +0000 Move zonkWC to the right place in simplfyInfer runTcSWithEvBinds does some unification, so the zonkWC must be after, not before! Yikes. An outright bug. This fixes Trac #14715. (cherry picked from commit e7c3878dacbad8120aacbe4423857b5ca9b43eb4) >--------------------------------------------------------------- e6c147442fbeb161bbed209126186056f371d60c compiler/typecheck/TcSimplify.hs | 5 ++--- testsuite/tests/partial-sigs/should_compile/T14715.hs | 19 +++++++++++++++++++ .../should_compile/T14715.stderr} | 0 testsuite/tests/partial-sigs/should_compile/all.T | 1 + 4 files changed, 22 insertions(+), 3 deletions(-) diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs index 7985746..970ebaf 100644 --- a/compiler/typecheck/TcSimplify.hs +++ b/compiler/typecheck/TcSimplify.hs @@ -648,9 +648,7 @@ simplifyInfer rhs_tclvl infer_mode sigs name_taus wanteds psig_givens = mkGivens loc psig_theta_vars ; _ <- solveSimpleGivens psig_givens -- See Note [Add signature contexts as givens] - ; wanteds' <- solveWanteds wanteds - ; TcS.zonkWC wanteds' } - + ; solveWanteds wanteds } -- Find quant_pred_candidates, the predicates that -- we'll consider quantifying over @@ -658,6 +656,7 @@ simplifyInfer rhs_tclvl infer_mode sigs name_taus wanteds -- the psig_theta; it's just the extra bit -- NB2: We do not do any defaulting when inferring a type, this can lead -- to less polymorphic types, see Note [Default while Inferring] + ; wanted_transformed_incl_derivs <- TcM.zonkWC wanted_transformed_incl_derivs ; let definite_error = insolubleWC wanted_transformed_incl_derivs -- See Note [Quantification with errors] -- NB: must include derived errors in this test, diff --git a/testsuite/tests/partial-sigs/should_compile/T14715.hs b/testsuite/tests/partial-sigs/should_compile/T14715.hs new file mode 100644 index 0000000..1a902ac --- /dev/null +++ b/testsuite/tests/partial-sigs/should_compile/T14715.hs @@ -0,0 +1,19 @@ +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE PartialTypeSignatures #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE TypeFamilies #-} +module T14715 (bench_mulPublic) where + +data Cyc r +data CT zp r'q +class Reduce a b +type family LiftOf b + +bench_mulPublic :: forall z zp zq . (z ~ LiftOf zq, _) => Cyc zp -> Cyc z -> IO (zp,zq) +bench_mulPublic pt sk = do + ct :: CT zp (Cyc zq) <- encrypt sk pt + undefined ct + +encrypt :: forall z zp zq. Reduce z zq => Cyc z -> Cyc zp -> IO (CT zp (Cyc zq)) +encrypt = undefined diff --git a/testsuite/tests/deSugar/should_run/T5472.stdout b/testsuite/tests/partial-sigs/should_compile/T14715.stderr similarity index 100% copy from testsuite/tests/deSugar/should_run/T5472.stdout copy to testsuite/tests/partial-sigs/should_compile/T14715.stderr diff --git a/testsuite/tests/partial-sigs/should_compile/all.T b/testsuite/tests/partial-sigs/should_compile/all.T index d13af5c..ebf6338 100644 --- a/testsuite/tests/partial-sigs/should_compile/all.T +++ b/testsuite/tests/partial-sigs/should_compile/all.T @@ -73,4 +73,5 @@ test('T13482', normal, compile, ['']) test('T14217', normal, compile_fail, ['']) test('T14643', normal, compile, ['']) test('T14643a', normal, compile, ['']) +test('T14715', normal, compile, ['']) From git at git.haskell.org Thu Feb 1 04:51:46 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 1 Feb 2018 04:51:46 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: Prioritise equalities when solving, incl deriveds (77cdf60) Message-ID: <20180201045146.BD7083A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/77cdf60c8a68d2208cd8109d82b5f83b17bf0e91/ghc >--------------------------------------------------------------- commit 77cdf60c8a68d2208cd8109d82b5f83b17bf0e91 Author: Simon Peyton Jones Date: Wed Jan 31 13:05:13 2018 +0000 Prioritise equalities when solving, incl deriveds We already prioritise equalities when solving, but Trac #14723 showed that we were not doing so consistently enough, and as a result the type checker could go into a loop. Yikes. See Note [Prioritise equalities] in TcSMonad. Fixng this bug changed the solve order enough to demonstrate a problem with fundeps: Trac #14745. (cherry picked from commit efba054640d3418d7477316ae0c1e992d0aa0f22) >--------------------------------------------------------------- 77cdf60c8a68d2208cd8109d82b5f83b17bf0e91 compiler/typecheck/TcSMonad.hs | 93 +++++++++++++++++----- testsuite/tests/polykinds/T14723.hs | 70 ++++++++++++++++ testsuite/tests/polykinds/all.T | 1 + testsuite/tests/typecheck/should_compile/T13651.hs | 21 +++++ .../tests/typecheck/should_compile/T13651.stderr | 16 ++++ .../should_compile/{T13651.hs => T13651a.hs} | 4 +- testsuite/tests/typecheck/should_compile/all.T | 3 +- 7 files changed, 184 insertions(+), 24 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 77cdf60c8a68d2208cd8109d82b5f83b17bf0e91 From git at git.haskell.org Thu Feb 1 04:51:50 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 1 Feb 2018 04:51:50 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: Look inside implications in simplifyRule (d3573e4) Message-ID: <20180201045150.2372B3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/d3573e4ae63d6ae1ac0cd4bf5692a9bcd39ba733/ghc >--------------------------------------------------------------- commit d3573e4ae63d6ae1ac0cd4bf5692a9bcd39ba733 Author: Simon Peyton Jones Date: Wed Jan 31 14:25:50 2018 +0000 Look inside implications in simplifyRule Trac #14732 was a perpelexing bug in which -fdefer-typed-holes caused a mysterious type error in a RULE. This turned out to be because we are more aggressive about creating implications when deferring (see TcUnify.implicationNeeded), and the rule mechanism hadn't caught up. This fixes it. (cherry picked from commit e9ae0cae9eb6a340473b339b5711ae76c6bdd045) >--------------------------------------------------------------- d3573e4ae63d6ae1ac0cd4bf5692a9bcd39ba733 compiler/typecheck/TcRules.hs | 105 +++++++++++++++------ testsuite/tests/typecheck/should_compile/T14732.hs | 34 +++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 3 files changed, 109 insertions(+), 31 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d3573e4ae63d6ae1ac0cd4bf5692a9bcd39ba733 From git at git.haskell.org Thu Feb 1 04:51:52 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 1 Feb 2018 04:51:52 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: SysTools: Add detection support for LLD linker (2d1f6af) Message-ID: <20180201045152.DF2AB3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/2d1f6af42410e21c5425675213cfd34295139ab9/ghc >--------------------------------------------------------------- commit 2d1f6af42410e21c5425675213cfd34295139ab9 Author: Ben Gamari Date: Sun Jan 21 13:31:29 2018 -0500 SysTools: Add detection support for LLD linker I noticed while trying to test against LLVM 5.0 that GHC would throw "Couldn't figure out linker information" warnings due to LLD being chosen by configure. Adding detection support to silence these is simple enough, let's just do it. (cherry picked from commit 6c0db98bc5d1dceb8fa48544532f85d386900e4a) >--------------------------------------------------------------- 2d1f6af42410e21c5425675213cfd34295139ab9 compiler/main/DynFlags.hs | 1 + compiler/main/SysTools/Info.hs | 4 ++++ 2 files changed, 5 insertions(+) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 552c0b5..5e9003a 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -5478,6 +5478,7 @@ isBmi2Enabled dflags = case platformArch (targetPlatform dflags) of data LinkerInfo = GnuLD [Option] | GnuGold [Option] + | LlvmLLD [Option] | DarwinLD [Option] | SolarisLD [Option] | AixLD [Option] diff --git a/compiler/main/SysTools/Info.hs b/compiler/main/SysTools/Info.hs index e9dc685..6b31057 100644 --- a/compiler/main/SysTools/Info.hs +++ b/compiler/main/SysTools/Info.hs @@ -96,6 +96,7 @@ https://gcc.gnu.org/onlinedocs/gcc-5.2.0/gcc.pdf : neededLinkArgs :: LinkerInfo -> [Option] neededLinkArgs (GnuLD o) = o neededLinkArgs (GnuGold o) = o +neededLinkArgs (LlvmLLD o) = o neededLinkArgs (DarwinLD o) = o neededLinkArgs (SolarisLD o) = o neededLinkArgs (AixLD o) = o @@ -140,6 +141,9 @@ getLinkerInfo' dflags = do -- ELF specific flag, see Note [ELF needed shared libs] return (GnuGold [Option "-Wl,--no-as-needed"]) + | any ("LLD" `isPrefixOf`) stdo = + return (LlvmLLD []) + -- Unknown linker. | otherwise = fail "invalid --version output, or linker is unsupported" From git at git.haskell.org Thu Feb 1 04:51:55 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 1 Feb 2018 04:51:55 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: rts: Ensure that forkOS releases Task on termination (f026b1c) Message-ID: <20180201045155.A827D3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/f026b1c75003737845d9e46c538df9ada9906b13/ghc >--------------------------------------------------------------- commit f026b1c75003737845d9e46c538df9ada9906b13 Author: Ben Gamari Date: Wed Jan 31 21:37:21 2018 -0500 rts: Ensure that forkOS releases Task on termination Test Plan: validate Reviewers: simonmar, erikd Reviewed By: simonmar Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14725 Differential Revision: https://phabricator.haskell.org/D4346 (cherry picked from commit 382c12d18f3d64e01502a5c8bbc64d4aa4842e3e) >--------------------------------------------------------------- f026b1c75003737845d9e46c538df9ada9906b13 rts/posix/OSThreads.c | 1 + rts/win32/OSThreads.c | 1 + 2 files changed, 2 insertions(+) diff --git a/rts/posix/OSThreads.c b/rts/posix/OSThreads.c index e2471a2..9cf42aa 100644 --- a/rts/posix/OSThreads.c +++ b/rts/posix/OSThreads.c @@ -223,6 +223,7 @@ forkOS_createThreadWrapper ( void * entry ) cap = rts_lock(); rts_evalStableIO(&cap, (HsStablePtr) entry, NULL); rts_unlock(cap); + rts_done(); return NULL; } diff --git a/rts/win32/OSThreads.c b/rts/win32/OSThreads.c index ad42340..b1a98ce 100644 --- a/rts/win32/OSThreads.c +++ b/rts/win32/OSThreads.c @@ -236,6 +236,7 @@ forkOS_createThreadWrapper ( void * entry ) cap = rts_lock(); rts_evalStableIO(&cap, (HsStablePtr) entry, NULL); rts_unlock(cap); + rts_done(); return 0; } From git at git.haskell.org Thu Feb 1 04:51:58 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 1 Feb 2018 04:51:58 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: testsuite: Fix test output broken by efba054640d3 (233c5ce) Message-ID: <20180201045158.96CFE3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/233c5ced6e9e9ac9f8f91f4bfecb73a6274daefd/ghc >--------------------------------------------------------------- commit 233c5ced6e9e9ac9f8f91f4bfecb73a6274daefd Author: Ben Gamari Date: Wed Jan 31 23:02:52 2018 -0500 testsuite: Fix test output broken by efba054640d3 Looks right to me. (cherry picked from commit 7d9812e8f4e8723c94a8ee9f7ba629ac9f1d4e71) >--------------------------------------------------------------- 233c5ced6e9e9ac9f8f91f4bfecb73a6274daefd testsuite/tests/typecheck/should_fail/T10619.stderr | 4 ++-- testsuite/tests/typecheck/should_fail/T5691.stderr | 10 +++++----- 2 files changed, 7 insertions(+), 7 deletions(-) diff --git a/testsuite/tests/typecheck/should_fail/T10619.stderr b/testsuite/tests/typecheck/should_fail/T10619.stderr index 0cd5364..fde2daf 100644 --- a/testsuite/tests/typecheck/should_fail/T10619.stderr +++ b/testsuite/tests/typecheck/should_fail/T10619.stderr @@ -1,6 +1,6 @@ T10619.hs:9:15: error: - • Couldn't match type ‘b -> b’ with ‘forall a. a -> a’ + • Couldn't match type ‘forall a. a -> a’ with ‘b -> b’ Expected type: (b -> b) -> b -> b Actual type: (forall a. a -> a) -> b -> b • In the expression: @@ -40,7 +40,7 @@ T10619.hs:14:15: error: bar :: p -> (b -> b) -> b -> b (bound at T10619.hs:12:1) T10619.hs:16:13: error: - • Couldn't match type ‘b -> b’ with ‘forall a. a -> a’ + • Couldn't match type ‘forall a. a -> a’ with ‘b -> b’ Expected type: (b -> b) -> b -> b Actual type: (forall a. a -> a) -> b -> b • In the expression: diff --git a/testsuite/tests/typecheck/should_fail/T5691.stderr b/testsuite/tests/typecheck/should_fail/T5691.stderr index 9d4e587..ad5c7e4 100644 --- a/testsuite/tests/typecheck/should_fail/T5691.stderr +++ b/testsuite/tests/typecheck/should_fail/T5691.stderr @@ -1,12 +1,12 @@ -T5691.hs:15:24: error: +T5691.hs:14:9: error: • Couldn't match type ‘p’ with ‘PrintRuleInterp’ Expected type: PrintRuleInterp a Actual type: p a - • In the first argument of ‘printRule_’, namely ‘f’ - In the second argument of ‘($)’, namely ‘printRule_ f’ - In the expression: MkPRI $ printRule_ f - • Relevant bindings include f :: p a (bound at T5691.hs:14:9) + • When checking that the pattern signature: p a + fits the type of its context: PrintRuleInterp a + In the pattern: f :: p a + In an equation for ‘test’: test (f :: p a) = MkPRI $ printRule_ f T5691.hs:24:10: error: • No instance for (Alternative RecDecParser) From git at git.haskell.org Thu Feb 1 04:52:01 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 1 Feb 2018 04:52:01 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: Mark xmm6 as caller saved in the register allocator for windows. (fe485f2) Message-ID: <20180201045201.C392F3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/fe485f2961324d3b798d4dc8b1ccd27e887fa213/ghc >--------------------------------------------------------------- commit fe485f2961324d3b798d4dc8b1ccd27e887fa213 Author: klebinger.andreas at gmx.at Date: Wed Jan 31 21:39:19 2018 -0500 Mark xmm6 as caller saved in the register allocator for windows. This prevents the register being picked up as a scratch register. Otherwise the allocator would be free to use it before a call. This fixes #14619. Test Plan: ci, repro case on #14619 Reviewers: bgamari, Phyx, erikd, simonmar, RyanGlScott, simonpj Reviewed By: Phyx, RyanGlScott, simonpj Subscribers: simonpj, RyanGlScott, Phyx, rwbarton, thomie, carter GHC Trac Issues: #14619 Differential Revision: https://phabricator.haskell.org/D4348 (cherry picked from commit add4e1f11b88cd603f6c01bc135eb576e1922a8e) >--------------------------------------------------------------- fe485f2961324d3b798d4dc8b1ccd27e887fa213 compiler/nativeGen/X86/Regs.hs | 6 ++-- includes/rts/Constants.h | 8 +++-- rts/StgCRun.c | 33 ++++++++++++++--- testsuite/tests/codeGen/should_run/T14619.hs | 46 ++++++++++++++++++++++++ testsuite/tests/codeGen/should_run/T14619.stdout | 1 + testsuite/tests/codeGen/should_run/all.T | 1 + 6 files changed, 86 insertions(+), 9 deletions(-) diff --git a/compiler/nativeGen/X86/Regs.hs b/compiler/nativeGen/X86/Regs.hs index 169d402..d6983b7 100644 --- a/compiler/nativeGen/X86/Regs.hs +++ b/compiler/nativeGen/X86/Regs.hs @@ -238,7 +238,6 @@ xmmregnos platform = [firstxmm .. lastxmm platform] floatregnos :: Platform -> [RegNo] floatregnos platform = fakeregnos ++ xmmregnos platform - -- argRegs is the set of regs which are read for an n-argument call to C. -- For archs which pass all args on the stack (x86), is empty. -- Sparc passes up to the first 6 args in regs. @@ -408,7 +407,10 @@ 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) + -- Only xmm0-5 are caller-saves registers on 64bit windows. + -- ( https://docs.microsoft.com/en-us/cpp/build/register-usage ) + -- For details check the Win64 ABI. + ++ map regSingle fakeregnos ++ map xmm [0 .. 5] | otherwise -- all xmm regs are caller-saves -- caller-saves registers diff --git a/includes/rts/Constants.h b/includes/rts/Constants.h index 27097bf..5774bd7 100644 --- a/includes/rts/Constants.h +++ b/includes/rts/Constants.h @@ -113,11 +113,15 @@ /* ----------------------------------------------------------------------------- How large is the stack frame saved by StgRun? world. Used in StgCRun.c. + + The size has to be enough to save the registers (see StgCRun) + plus padding if the result is not 16 byte aligned. + See the Note [Stack Alignment on X86] in StgCRun.c for details. + -------------------------------------------------------------------------- */ #if defined(x86_64_HOST_ARCH) # if defined(mingw32_HOST_OS) -/* 8 larger than necessary to make the alignment right*/ -# define STG_RUN_STACK_FRAME_SIZE 80 +# define STG_RUN_STACK_FRAME_SIZE 144 # else # define STG_RUN_STACK_FRAME_SIZE 48 # endif diff --git a/rts/StgCRun.c b/rts/StgCRun.c index 4ce0c44..010af44 100644 --- a/rts/StgCRun.c +++ b/rts/StgCRun.c @@ -236,7 +236,7 @@ StgRunIsImplementedInAssembler(void) ); } -#endif +#endif // defined(i386_HOST_ARCH) /* ---------------------------------------------------------------------------- x86-64 is almost the same as plain x86. @@ -279,9 +279,23 @@ StgRunIsImplementedInAssembler(void) "movq %%r14,32(%%rax)\n\t" "movq %%r15,40(%%rax)\n\t" #if defined(mingw32_HOST_OS) + /* + * Additional callee saved registers on Win64. This must match + * callClobberedRegisters in compiler/nativeGen/X86/Regs.hs as + * both represent the Win64 calling convention. + */ "movq %%rdi,48(%%rax)\n\t" "movq %%rsi,56(%%rax)\n\t" - "movq %%xmm6,64(%%rax)\n\t" + "movq %%xmm6, 64(%%rax)\n\t" + "movq %%xmm7, 72(%%rax)\n\t" + "movq %%xmm8, 80(%%rax)\n\t" + "movq %%xmm9, 88(%%rax)\n\t" + "movq %%xmm10, 96(%%rax)\n\t" + "movq %%xmm11,104(%%rax)\n\t" + "movq %%xmm12,112(%%rax)\n\t" + "movq %%xmm13,120(%%rax)\n\t" + "movq %%xmm14,128(%%rax)\n\t" + "movq %%xmm15,136(%%rax)\n\t" #endif /* * Set BaseReg @@ -317,9 +331,18 @@ StgRunIsImplementedInAssembler(void) "movq 32(%%rsp),%%r14\n\t" "movq 40(%%rsp),%%r15\n\t" #if defined(mingw32_HOST_OS) - "movq 48(%%rsp),%%rdi\n\t" - "movq 56(%%rsp),%%rsi\n\t" - "movq 64(%%rsp),%%xmm6\n\t" + "movq 48(%%rsp),%%rdi\n\t" + "movq 56(%%rsp),%%rsi\n\t" + "movq 64(%%rsp),%%xmm6\n\t" + "movq 72(%%rax),%%xmm7\n\t" + "movq 80(%%rax),%%xmm8\n\t" + "movq 88(%%rax),%%xmm9\n\t" + "movq 96(%%rax),%%xmm10\n\t" + "movq 104(%%rax),%%xmm11\n\t" + "movq 112(%%rax),%%xmm12\n\t" + "movq 120(%%rax),%%xmm13\n\t" + "movq 128(%%rax),%%xmm14\n\t" + "movq 136(%%rax),%%xmm15\n\t" #endif "addq %1, %%rsp\n\t" "retq" diff --git a/testsuite/tests/codeGen/should_run/T14619.hs b/testsuite/tests/codeGen/should_run/T14619.hs new file mode 100644 index 0000000..7af16df --- /dev/null +++ b/testsuite/tests/codeGen/should_run/T14619.hs @@ -0,0 +1,46 @@ +{-# OPTIONS_GHC -O1 #-} + +{- + On windows some xmm registers are callee saved. This means + they can't be used as scratch registers before a call to C. + + In #14619 this wasn't respected which lead to a wrong value + ending up in xmm6 and being returned in the final result. + + This code compiles to a non trivial fp computation followed + by a call to sqrt at O1+. If xmm6 isn't properly handled it + will be used as a scratch register failing the test. + + The original code used regular sqrt which on 8.2 generated + a C call in the backend. To imitate this behaviour on 8.4+ + we force a call to a C function instead. +-} + +module Main (main) where + + + +import Prelude hiding((*>), (<*)) +import Foreign.C +import Unsafe.Coerce + +foreign import ccall unsafe "sqrt" call_sqrt :: CDouble -> CDouble + +type V3 = (Double, Double, Double) + +absf :: V3 -> V3 -> Double +absf (x, y, z) (x', y', z') = x*x' +y*y'+z*z' + + +{-# NOINLINE sphereIntersection #-} +sphereIntersection :: V3 -> V3 -> (V3) +sphereIntersection orig dir@(_, _, dirz) + | b < 0 = undefined + | t1 > 0 = dir + | t1 < 0 = orig + | otherwise = undefined + where b = orig `absf` dir + sqrtDisc = realToFrac . call_sqrt $ CDouble b + t1 = b - sqrtDisc + +main = print $ sphereIntersection (11, 22, 33) (44, 55, 66) diff --git a/testsuite/tests/codeGen/should_run/T14619.stdout b/testsuite/tests/codeGen/should_run/T14619.stdout new file mode 100644 index 0000000..a11c04d --- /dev/null +++ b/testsuite/tests/codeGen/should_run/T14619.stdout @@ -0,0 +1 @@ +(44.0,55.0,66.0) diff --git a/testsuite/tests/codeGen/should_run/all.T b/testsuite/tests/codeGen/should_run/all.T index 42d8a2f..145365e 100644 --- a/testsuite/tests/codeGen/should_run/all.T +++ b/testsuite/tests/codeGen/should_run/all.T @@ -165,3 +165,4 @@ test('T13825-unit', extra_run_opts('"' + config.libdir + '"'), compile_and_run, ['-package ghc']) +test('T14619', normal, compile_and_run, ['']) From git at git.haskell.org Thu Feb 1 04:52:05 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 1 Feb 2018 04:52:05 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: Don't add targets that can't be found in GHCi (8f668bd) Message-ID: <20180201045205.150FC3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/8f668bdaa1909c28a041db1680585bbf7d833987/ghc >--------------------------------------------------------------- commit 8f668bdaa1909c28a041db1680585bbf7d833987 Author: Julian Priestley Date: Wed Jan 31 21:35:00 2018 -0500 Don't add targets that can't be found in GHCi When using the :add command in haxlsh/ghci, a module/file that can't be found is still added to the list of targets, resulting in an error message for the bad module/file for every subsequent usage of the command. The add command should verify that the module/file can be found before adding it to the list of targets. Also add a ":show targets" command to show the currently added list of commands, and an ":unadd" command to remove a target. Test Plan: Add a new GHCi testcase that checks that :add doesn't remember either files or modules that could not be found, and that both the new :show and :unadd commands work as expected. Reviewers: simonmar, bgamari Reviewed By: simonmar Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14676 Differential Revision: https://phabricator.haskell.org/D4321 (cherry picked from commit 0bff9e677f0569bc8a7207c20cddddfd67e2448f) >--------------------------------------------------------------- 8f668bdaa1909c28a041db1680585bbf7d833987 ghc/GHCi/UI.hs | 45 +++++++++++++++++++++++++++++- testsuite/tests/ghci/scripts/T14676.script | 7 +++++ testsuite/tests/ghci/scripts/T14676.stdout | 3 ++ testsuite/tests/ghci/scripts/all.T | 1 + 4 files changed, 55 insertions(+), 1 deletion(-) diff --git a/ghc/GHCi/UI.hs b/ghc/GHCi/UI.hs index 01c8505..b83ceeb 100644 --- a/ghc/GHCi/UI.hs +++ b/ghc/GHCi/UI.hs @@ -43,6 +43,7 @@ import GHCi.RemoteTypes import GHCi.BreakArray import DynFlags import ErrUtils hiding (traceCmd) +import Finder import GhcMonad ( modifySession ) import qualified GHC import GHC ( LoadHowMuch(..), Target(..), TargetId(..), InteractiveImport(..), @@ -208,6 +209,7 @@ ghciCommands = map mkCmd [ ("stepmodule",keepGoing stepModuleCmd, completeIdentifier), ("type", keepGoing' typeOfExpr, completeExpression), ("trace", keepGoing traceCmd, completeExpression), + ("unadd", keepGoingPaths unAddModule, completeFilename), ("undef", keepGoing undefineMacro, completeMacro), ("unset", keepGoing unsetOptions, completeSetOptions), ("where", keepGoing whereCmd, noCompletion) @@ -305,6 +307,7 @@ defFullHelpText = " :type show the type of \n" ++ " :type +d show the type of , defaulting type variables\n" ++ " :type +v show the type of , with its specified tyvars\n" ++ + " :unadd ... remove module(s) from the current target set\n" ++ " :undef undefine user-defined command :\n" ++ " :! run the shell command \n" ++ "\n" ++ @@ -371,6 +374,7 @@ defFullHelpText = " :show packages show the currently active package flags\n" ++ " :show paths show the currently active search paths\n" ++ " :show language show the currently active language flags\n" ++ + " :show targets show the current set of targets\n" ++ " :show show value of , which is one of\n" ++ " [args, prog, editor, stop]\n" ++ " :showi language show language flags for interactive evaluation\n" ++ @@ -1657,9 +1661,39 @@ addModule files = do lift revertCAFs -- always revert CAFs on load/add. files' <- mapM expandPath files targets <- mapM (\m -> GHC.guessTarget m Nothing) files' + targets' <- filterM checkTarget targets -- remove old targets with the same id; e.g. for :add *M + mapM_ GHC.removeTarget [ tid | Target tid _ _ <- targets' ] + mapM_ GHC.addTarget targets' + _ <- doLoadAndCollectInfo False LoadAllTargets + return () + where + checkTarget :: Target -> InputT GHCi Bool + checkTarget (Target (TargetModule m) _ _) = checkTargetModule m + checkTarget (Target (TargetFile f _) _ _) = liftIO $ checkTargetFile f + + checkTargetModule :: ModuleName -> InputT GHCi Bool + checkTargetModule m = do + hsc_env <- GHC.getSession + result <- liftIO $ + Finder.findImportedModule hsc_env m (Just (fsLit "this")) + case result of + Found _ _ -> return True + _ -> (liftIO $ putStrLn $ + "Module " ++ moduleNameString m ++ " not found") >> return False + + checkTargetFile :: String -> IO Bool + checkTargetFile f = do + exists <- (doesFileExist f) :: IO Bool + unless exists $ putStrLn $ "File " ++ f ++ " not found" + return exists + +-- | @:unadd@ command +unAddModule :: [FilePath] -> InputT GHCi () +unAddModule files = do + files' <- mapM expandPath files + targets <- mapM (\m -> GHC.guessTarget m Nothing) files' mapM_ GHC.removeTarget [ tid | Target tid _ _ <- targets ] - mapM_ GHC.addTarget targets _ <- doLoadAndCollectInfo False LoadAllTargets return () @@ -2779,6 +2813,7 @@ showCmd str = do , action "language" $ showLanguages , hidden "languages" $ showLanguages -- backwards compat , hidden "lang" $ showLanguages -- useful abbreviation + , action "targets" $ showTargets ] case words str of @@ -2941,6 +2976,14 @@ showLanguages' show_all dflags = Nothing -> Just Haskell2010 other -> other +showTargets :: GHCi () +showTargets = mapM_ showTarget =<< GHC.getTargets + where + showTarget :: Target -> GHCi () + showTarget (Target (TargetFile f _) _ _) = liftIO (putStrLn f) + showTarget (Target (TargetModule m) _ _) = + liftIO (putStrLn $ moduleNameString m) + -- ----------------------------------------------------------------------------- -- Completion diff --git a/testsuite/tests/ghci/scripts/T14676.script b/testsuite/tests/ghci/scripts/T14676.script new file mode 100644 index 0000000..9cfe693 --- /dev/null +++ b/testsuite/tests/ghci/scripts/T14676.script @@ -0,0 +1,7 @@ +:add Notfound.hs +:add NotFound +:show targets +:add prog002/A1.hs +:show targets +:unadd prog002/A1.hs +:show targets diff --git a/testsuite/tests/ghci/scripts/T14676.stdout b/testsuite/tests/ghci/scripts/T14676.stdout new file mode 100644 index 0000000..c3e9fbd --- /dev/null +++ b/testsuite/tests/ghci/scripts/T14676.stdout @@ -0,0 +1,3 @@ +File Notfound.hs not found +Module NotFound not found +prog002/A1.hs diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T index e453591..016c482 100755 --- a/testsuite/tests/ghci/scripts/all.T +++ b/testsuite/tests/ghci/scripts/all.T @@ -262,3 +262,4 @@ test('T13407', normal, ghci_script, ['T13407.script']) test('T13963', normal, ghci_script, ['T13963.script']) test('T14342', [extra_hc_opts("-XOverloadedStrings -XRebindableSyntax")], ghci_script, ['T14342.script']) +test('T14676', extra_files(['../prog002']), ghci_script, ['T14676.script']) From git at git.haskell.org Thu Feb 1 04:52:07 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 1 Feb 2018 04:52:07 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: testsuite: Fix test output of T14715 (d6f2f23) Message-ID: <20180201045207.D95F53A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/d6f2f231bfd556256efa408663e277a963ea4deb/ghc >--------------------------------------------------------------- commit d6f2f231bfd556256efa408663e277a963ea4deb Author: Ben Gamari Date: Wed Jan 31 22:53:16 2018 -0500 testsuite: Fix test output of T14715 Arguably the warning should just be disabled for this test to eliminate unnecessary wiggle in the future. (cherry picked from commit fe6fdf689853f5d6e4ef01ba9952e4be48a92f45) >--------------------------------------------------------------- d6f2f231bfd556256efa408663e277a963ea4deb testsuite/tests/partial-sigs/should_compile/T14715.stderr | 11 ++++++++++- 1 file changed, 10 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/partial-sigs/should_compile/T14715.stderr b/testsuite/tests/partial-sigs/should_compile/T14715.stderr index 0519ecb..c846b47 100644 --- a/testsuite/tests/partial-sigs/should_compile/T14715.stderr +++ b/testsuite/tests/partial-sigs/should_compile/T14715.stderr @@ -1 +1,10 @@ - \ No newline at end of file +T14715.hs:13:53: warning: [-Wpartial-type-signatures (in -Wdefault)] + Found type wildcard ‘_’ standing for ‘Reduce (LiftOf zq) zq’ + Where: ‘zq’ is a rigid type variable bound by + the inferred type of + bench_mulPublic :: (z ~ LiftOf zq, Reduce (LiftOf zq) zq) => + Cyc zp -> Cyc z -> IO (zp, zq) + at T14715.hs:(14,1)-(16,14) + In the type signature: + bench_mulPublic :: forall z zp zq. + (z ~ LiftOf zq, _) => Cyc zp -> Cyc z -> IO (zp, zq) From git at git.haskell.org Thu Feb 1 12:19:33 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 1 Feb 2018 12:19:33 +0000 (UTC) Subject: [commit: ghc] master: Re-center improved perf for T3064 (db5a4b8) Message-ID: <20180201121933.824723A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/db5a4b83b14bf4f1adb417b7664347fdaf637fd6/ghc >--------------------------------------------------------------- commit db5a4b83b14bf4f1adb417b7664347fdaf637fd6 Author: Simon Peyton Jones Date: Thu Feb 1 12:16:40 2018 +0000 Re-center improved perf for T3064 There's a 6% reduction in allocation on T3064. I think it's due to commit e4ab65bd57b2c39f4af52879654514bb6d5b42a0 Author: Tobias Dammers Date: Wed Jan 31 21:39:45 2018 -0500 Optimize coercionKind (Trac #11735) I'm not certain -- but, hey, it's good news >--------------------------------------------------------------- db5a4b83b14bf4f1adb417b7664347fdaf637fd6 testsuite/tests/perf/compiler/all.T | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index 84bfd75..1ac19e5 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -336,7 +336,7 @@ test('T3064', # 2016-04-06: 153261024 (x86/Linux) probably wildcard refactor # 2017-03-24: 134044092 (x86/Linux, 64-bit machine) Update - (wordsize(64), 281509496, 5)]), + (wordsize(64), 258505536, 5)]), # (amd64/Linux) (2011-06-28): 73259544 # (amd64/Linux) (2013-02-07): 224798696 # (amd64/Linux) (2013-08-02): 236404384, increase from roles @@ -363,6 +363,7 @@ test('T3064', # (amd64/Linux) (2017-02-14): 259815560 Early inline patch: 9% improvement # (amd64/Linux) (2017-03-31): 265950920 Fix memory leak in simplifier # (amd64/Linux) (2017-05-01): 281509496 Avoid excessive space usage from unfoldings in CoreTidy + # (amd64/Linux) (2017-05-01): 258505536 I think this is improvement in coercionKind e4ab65bd ################################### # deactivated for now, as this metric became too volatile recently From git at git.haskell.org Thu Feb 1 12:19:30 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 1 Feb 2018 12:19:30 +0000 (UTC) Subject: [commit: ghc] master: Experiment with eliminating the younger tyvar (618a805) Message-ID: <20180201121930.ACFE93A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/618a805b0313ce256fa7b8293f851b32913bace5/ghc >--------------------------------------------------------------- commit 618a805b0313ce256fa7b8293f851b32913bace5 Author: Simon Peyton Jones Date: Wed Jan 31 15:58:12 2018 +0000 Experiment with eliminating the younger tyvar This patch is comments only, plus a minor refactor that does not change behaviour. It just records an idea I had for reducing kick-out in the type constraint-solver. See Note [Eliminate younger unification variables] in TcUnify. Sadly, it didn't improve perf, so I've put it aside, leaving some breadcrumbs for future generations of GHC hackers. >--------------------------------------------------------------- 618a805b0313ce256fa7b8293f851b32913bace5 compiler/basicTypes/Unique.hs | 4 ++++ compiler/typecheck/TcCanonical.hs | 13 ---------- compiler/typecheck/TcUnify.hs | 50 +++++++++++++++++++++++++++++++++++---- 3 files changed, 49 insertions(+), 18 deletions(-) diff --git a/compiler/basicTypes/Unique.hs b/compiler/basicTypes/Unique.hs index 30de08e..bd7ed3e 100644 --- a/compiler/basicTypes/Unique.hs +++ b/compiler/basicTypes/Unique.hs @@ -32,6 +32,7 @@ module Unique ( mkUniqueGrimily, -- Used in UniqSupply only! getKey, -- Used in Var, UniqFM, Name only! mkUnique, unpkUnique, -- Used in BinIface only + eqUnique, ltUnique, deriveUnique, -- Ditto newTagUnique, -- Used in CgCase @@ -240,6 +241,9 @@ use `deriving' because we want {\em precise} control of ordering eqUnique :: Unique -> Unique -> Bool eqUnique (MkUnique u1) (MkUnique u2) = u1 == u2 +ltUnique :: Unique -> Unique -> Bool +ltUnique (MkUnique u1) (MkUnique u2) = u1 < u2 + -- Provided here to make it explicit at the call-site that it can -- introduce non-determinism. -- See Note [Unique Determinism] diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index 60f4497..1e1fa39 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -1623,19 +1623,6 @@ canEqTyVarTyVar, are these substituted out Note [Elminate flat-skols] fsk ~ a -Note [Avoid unnecessary swaps] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -If we swap without actually improving matters, we can get an infinite loop. -Consider - work item: a ~ b - inert item: b ~ c -We canonicalise the work-time to (a ~ c). If we then swap it before -aeding to the inert set, we'll add (c ~ a), and therefore kick out the -inert guy, so we get - new work item: b ~ c - inert item: c ~ a -And now the cycle just repeats - Note [Eliminate flat-skols] ~~~~~~~~~~~~~~~~~~~~~~~~~~~ Suppose we have [G] Num (F [a]) diff --git a/compiler/typecheck/TcUnify.hs b/compiler/typecheck/TcUnify.hs index 2c37428..b7031df 100644 --- a/compiler/typecheck/TcUnify.hs +++ b/compiler/typecheck/TcUnify.hs @@ -48,7 +48,7 @@ import TcType import Type import Coercion import TcEvidence -import Name ( isSystemName ) +import Name( isSystemName ) import Inst import TyCon import TysWiredIn @@ -1589,7 +1589,7 @@ swapOverTyVars tv1 tv2 Nothing -> False Just lvl2 | lvl2 `strictlyDeeperThan` lvl1 -> True | lvl1 `strictlyDeeperThan` lvl2 -> False - | otherwise -> nicer_to_update tv2 + | otherwise -> nicer_to_update_tv2 -- So tv1 is not a meta tyvar -- If only one is a meta tyvar, put it on the left @@ -1606,9 +1606,17 @@ swapOverTyVars tv1 tv2 | otherwise = False where - nicer_to_update tv2 - = (isSigTyVar tv1 && not (isSigTyVar tv2)) - || (isSystemName (Var.varName tv2) && not (isSystemName (Var.varName tv1))) + tv1_name = Var.varName tv1 + tv2_name = Var.varName tv2 + + nicer_to_update_tv2 + | isSigTyVar tv1, not (isSigTyVar tv2) = True + | isSystemName tv2_name, not (isSystemName tv1_name) = True +-- | nameUnique tv1_name `ltUnique` nameUnique tv2_name = True +-- -- See Note [Eliminate younger unification variables] +-- (which also explains why it's commented out) + | otherwise = False + -- @trySpontaneousSolve wi@ solves equalities where one side is a -- touchable unification variable. @@ -1674,6 +1682,38 @@ left, giving Now we get alpha:=a, and everything works out +Note [Avoid unnecessary swaps] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +If we swap without actually improving matters, we can get an infinite loop. +Consider + work item: a ~ b + inert item: b ~ c +We canonicalise the work-item to (a ~ c). If we then swap it before +adding to the inert set, we'll add (c ~ a), and therefore kick out the +inert guy, so we get + new work item: b ~ c + inert item: c ~ a +And now the cycle just repeats + +Note [Eliminate younger unification variables] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Given a choice of unifying + alpha := beta or beta := alpha +we try, if possible, to elimiate the "younger" one, as determined +by `ltUnique`. Reason: the younger one is less likely to appear free in +an existing inert constraint, and hence we are less likely to be forced +into kicking out and rewriting inert constraints. + +This is a performance optimisation only. It turns out to fix +Trac #14723 all by itself, but clearly not reliably so! + +It's simple to implement (see nicer_to_update_tv2 in swapOverTyVars). +But, to my surprise, it didn't seem to make any significant difference +to the compiler's performance, so I didn't take it any further. Still +it seemed to too nice to discard altogether, so I'm leaving these +notes. SLPJ Jan 18. + + Note [Prevent unification with type families] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ We prevent unification with type families because of an uneasy compromise. From git at git.haskell.org Thu Feb 1 12:53:51 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 1 Feb 2018 12:53:51 +0000 (UTC) Subject: [commit: ghc] master: Add -ddump-ds-preopt (efce943) Message-ID: <20180201125351.6EF9E3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/efce943ca20b55b18f948681e6b44fd892dbddd2/ghc >--------------------------------------------------------------- commit efce943ca20b55b18f948681e6b44fd892dbddd2 Author: Simon Peyton Jones Date: Thu Feb 1 09:19:30 2018 +0000 Add -ddump-ds-preopt This allows you to see the output immediately after desugaring but before any optimisation. I've wanted this for some time, but I was triggered into action by Trac #13032 comment:9. Interestingly, the change means that with -dcore-lint we will now Lint the output before the very simple optimiser; and this showed up Trac #14749. But that's not the fault of -ddump-ds-preopt! >--------------------------------------------------------------- efce943ca20b55b18f948681e6b44fd892dbddd2 compiler/coreSyn/CoreLint.hs | 2 +- compiler/deSugar/Desugar.hs | 3 --- compiler/main/DynFlags.hs | 3 +++ docs/users_guide/debugging.rst | 11 ++++++++--- testsuite/tests/typecheck/should_compile/all.T | 2 +- 5 files changed, 13 insertions(+), 8 deletions(-) diff --git a/compiler/coreSyn/CoreLint.hs b/compiler/coreSyn/CoreLint.hs index e866f0d..e83f839 100644 --- a/compiler/coreSyn/CoreLint.hs +++ b/compiler/coreSyn/CoreLint.hs @@ -275,7 +275,7 @@ coreDumpFlag CoreDoSpecialising = Just Opt_D_dump_spec coreDumpFlag CoreDoSpecConstr = Just Opt_D_dump_spec coreDumpFlag CoreCSE = Just Opt_D_dump_cse coreDumpFlag CoreDoVectorisation = Just Opt_D_dump_vect -coreDumpFlag CoreDesugar = Just Opt_D_dump_ds +coreDumpFlag CoreDesugar = Just Opt_D_dump_ds_preopt coreDumpFlag CoreDesugarOpt = Just Opt_D_dump_ds coreDumpFlag CoreTidy = Just Opt_D_dump_simpl coreDumpFlag CorePrep = Just Opt_D_dump_prep diff --git a/compiler/deSugar/Desugar.hs b/compiler/deSugar/Desugar.hs index 518f02f..05d3226 100644 --- a/compiler/deSugar/Desugar.hs +++ b/compiler/deSugar/Desugar.hs @@ -160,10 +160,7 @@ deSugar hsc_env -- You might think it doesn't matter, but the simplifier brings all top-level -- things into the in-scope set before simplifying; so we get no unfolding for F#! -#if defined(DEBUG) - -- Debug only as pre-simple-optimisation program may be really big ; endPassIO hsc_env print_unqual CoreDesugar final_pgm rules_for_imps -#endif ; (ds_binds, ds_rules_for_imps, ds_vects) <- simpleOptPgm dflags mod final_pgm rules_for_imps vects0 -- The simpleOptPgm gets rid of type diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index cf889ec..6cea932 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -347,6 +347,7 @@ data DumpFlag | Opt_D_dump_core_stats | Opt_D_dump_deriv | Opt_D_dump_ds + | Opt_D_dump_ds_preopt | Opt_D_dump_foreign | Opt_D_dump_inlinings | Opt_D_dump_rule_firings @@ -3058,6 +3059,8 @@ dynamic_flags_deps = [ (setDumpFlag Opt_D_dump_deriv) , make_ord_flag defGhcFlag "ddump-ds" (setDumpFlag Opt_D_dump_ds) + , make_ord_flag defGhcFlag "ddump-ds-preopt" + (setDumpFlag Opt_D_dump_ds_preopt) , make_ord_flag defGhcFlag "ddump-foreign" (setDumpFlag Opt_D_dump_foreign) , make_ord_flag defGhcFlag "ddump-inlinings" diff --git a/docs/users_guide/debugging.rst b/docs/users_guide/debugging.rst index 3997919..48222ae 100644 --- a/docs/users_guide/debugging.rst +++ b/docs/users_guide/debugging.rst @@ -212,11 +212,16 @@ subexpression elimination pass. Print a one-line summary of the size of the Core program at the end of the optimisation pipeline. -.. ghc-flag:: -ddump-ds - :shortdesc: Dump desugarer output +.. ghc-flag:: -ddump-ds -ddump-ds-preopt + :shortdesc: Dump desugarer output. :type: dynamic - Dump desugarer output + Dump desugarer output. `-ddump-ds` dumps the output after the very simple + optimiser has run (which discards a lot of clutter and + hence is a sensible default. `-ddump-ds-preopt` shows + the output after desugaring but before the very simple + optimiser. + .. ghc-flag:: -ddump-simpl-iterations :shortdesc: Dump output from each simplifier iteration diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index 795e173..49683b7 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -566,7 +566,7 @@ test('T13651a', normal, compile, ['']) test('T13680', normal, compile, ['']) test('T13785', normal, compile, ['']) test('T13804', normal, compile, ['']) -test('T13822', normal, compile, ['']) +test('T13822', expect_broken(14749), compile, ['']) test('T13848', normal, compile, ['']) test('T13871', normal, compile, ['']) test('T13879', normal, compile, ['']) From git at git.haskell.org Sat Feb 3 00:56:29 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 3 Feb 2018 00:56:29 +0000 (UTC) Subject: [commit: ghc] master: Hoopl.Collections: change right folds to strict left folds (2974b2b) Message-ID: <20180203005629.80D0F3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2974b2b873b4bad007c619c6e32706123a612428/ghc >--------------------------------------------------------------- commit 2974b2b873b4bad007c619c6e32706123a612428 Author: Michal Terepeta Date: Thu Feb 1 00:30:22 2018 -0500 Hoopl.Collections: change right folds to strict left folds It seems that most uses of these folds should be strict left folds (I could only find a single place that benefits from a right fold). So this removes the existing `setFold`/`mapFold`/`mapFoldWihKey` replaces them with: - `setFoldl`/`mapFoldl`/`mapFoldlWithKey` (strict left folds) - `setFoldr`/`mapFoldr` (for the less common case where a right fold actually makes sense, e.g., `CmmProcPoint`) Signed-off-by: Michal Terepeta Test Plan: ./validate Reviewers: bgamari, simonmar Reviewed By: bgamari Subscribers: rwbarton, thomie, carter, kavon Differential Revision: https://phabricator.haskell.org/D4356 >--------------------------------------------------------------- 2974b2b873b4bad007c619c6e32706123a612428 compiler/cmm/CmmCommonBlockElim.hs | 4 ++-- compiler/cmm/CmmContFlowOpt.hs | 6 +++--- compiler/cmm/CmmProcPoint.hs | 20 ++++++++++---------- compiler/cmm/CmmUtils.hs | 6 +++--- compiler/cmm/Hoopl/Collections.hs | 16 ++++++++++------ compiler/cmm/Hoopl/Dataflow.hs | 8 ++++---- compiler/cmm/Hoopl/Graph.hs | 6 +++--- compiler/cmm/Hoopl/Label.hs | 9 ++++++--- compiler/nativeGen/RegAlloc/Graph/Spill.hs | 9 ++++----- 9 files changed, 45 insertions(+), 39 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 2974b2b873b4bad007c619c6e32706123a612428 From git at git.haskell.org Sat Feb 3 00:56:32 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 3 Feb 2018 00:56:32 +0000 (UTC) Subject: [commit: ghc] master: Flag `-fdefer-typed-holes` also implies `-fdefer-out-of-scope-variables`. (e31b41b) Message-ID: <20180203005632.4EFF93A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e31b41bd6abbf08b1463f4ea08c50e8059f06263/ghc >--------------------------------------------------------------- commit e31b41bd6abbf08b1463f4ea08c50e8059f06263 Author: HE, Tao Date: Thu Feb 1 00:30:04 2018 -0500 Flag `-fdefer-typed-holes` also implies `-fdefer-out-of-scope-variables`. Reviewers: bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4361 >--------------------------------------------------------------- e31b41bd6abbf08b1463f4ea08c50e8059f06263 docs/users_guide/using-warnings.rst | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/docs/users_guide/using-warnings.rst b/docs/users_guide/using-warnings.rst index bd3c41d..8106003 100644 --- a/docs/users_guide/using-warnings.rst +++ b/docs/users_guide/using-warnings.rst @@ -239,7 +239,7 @@ of ``-W(no-)*``. :reverse: -fno-defer-type-errors :category: - :implies: :ghc-flag:`-fdefer-typed-holes` + :implies: :ghc-flag:`-fdefer-typed-holes`, :ghc-flag:`-fdefer-out-of-scope-variables` Defer as many type errors as possible until runtime. At compile time you get a warning (instead of an error). At runtime, if you use a From git at git.haskell.org Sat Feb 3 01:31:16 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 3 Feb 2018 01:31:16 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Fix scc001 profile output (c3ccd83) Message-ID: <20180203013116.074283A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c3ccd8356a8d50998ab3b9960f70a2f602dc03ca/ghc >--------------------------------------------------------------- commit c3ccd8356a8d50998ab3b9960f70a2f602dc03ca Author: Ben Gamari Date: Thu Feb 1 01:17:59 2018 -0500 testsuite: Fix scc001 profile output CircleCI seems to suggest that the cost center ordering is wrong in the prof way. I'm beginning to wonder whether there is some non-determinism here. If only I know what this test was supposed to be testing. >--------------------------------------------------------------- c3ccd8356a8d50998ab3b9960f70a2f602dc03ca testsuite/tests/profiling/should_run/scc001.prof.sample | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/profiling/should_run/scc001.prof.sample b/testsuite/tests/profiling/should_run/scc001.prof.sample index f2e55d5..8b33d6b 100644 --- a/testsuite/tests/profiling/should_run/scc001.prof.sample +++ b/testsuite/tests/profiling/should_run/scc001.prof.sample @@ -21,9 +21,9 @@ MAIN MAIN 111 0 0.0 CAF Main 221 0 0.0 0.0 0.0 0.6 (...) Main scc001.hs:16:1-16 227 1 0.0 0.0 0.0 0.0 main Main scc001.hs:(5,1)-(7,23) 222 1 0.0 0.5 0.0 0.5 + h Main scc001.hs:16:1-16 226 1 0.0 0.0 0.0 0.0 f Main scc001.hs:10:1-7 224 1 0.0 0.0 0.0 0.0 g Main scc001.hs:13:1-7 225 1 0.0 0.0 0.0 0.0 - h Main scc001.hs:16:1-16 226 1 0.0 0.0 0.0 0.0 CAF GHC.Conc.Signal 216 0 0.0 1.3 0.0 1.3 CAF GHC.IO.Encoding 206 0 0.0 5.4 0.0 5.4 CAF GHC.IO.Encoding.Iconv 204 0 0.0 0.4 0.0 0.4 From git at git.haskell.org Sat Feb 3 01:31:18 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 3 Feb 2018 01:31:18 +0000 (UTC) Subject: [commit: ghc] master: Add HasDebugCallStack to nameModule (7fb3287) Message-ID: <20180203013118.C250E3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7fb3287f7e3dabcbc1c76297bd4e9ed6de39599a/ghc >--------------------------------------------------------------- commit 7fb3287f7e3dabcbc1c76297bd4e9ed6de39599a Author: Simon Peyton Jones Date: Fri Feb 2 13:57:20 2018 -0500 Add HasDebugCallStack to nameModule This function is called in lots of places, so if it every fails it's good to know from where it was called. This is Simon's patch, part of his `wip/T2893` branch. Test Plan: Validate Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4352 >--------------------------------------------------------------- 7fb3287f7e3dabcbc1c76297bd4e9ed6de39599a compiler/basicTypes/Name.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/basicTypes/Name.hs b/compiler/basicTypes/Name.hs index 637fc69..02eb067 100644 --- a/compiler/basicTypes/Name.hs +++ b/compiler/basicTypes/Name.hs @@ -194,7 +194,7 @@ instance HasOccName Name where nameUnique :: Name -> Unique nameOccName :: Name -> OccName -nameModule :: Name -> Module +nameModule :: HasDebugCallStack => Name -> Module nameSrcLoc :: Name -> SrcLoc nameSrcSpan :: Name -> SrcSpan From git at git.haskell.org Sat Feb 3 02:22:45 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 3 Feb 2018 02:22:45 +0000 (UTC) Subject: [commit: ghc] master: DriverPhases: Fix flipped input extensions for cmm and cmmcpp (4f52bc1) Message-ID: <20180203022245.4E0013A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4f52bc17d888339b6bc3b9d27cd589aeee3b0b59/ghc >--------------------------------------------------------------- commit 4f52bc17d888339b6bc3b9d27cd589aeee3b0b59 Author: Ben Gamari Date: Fri Feb 2 13:57:51 2018 -0500 DriverPhases: Fix flipped input extensions for cmm and cmmcpp Test Plan: Validate Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4349 >--------------------------------------------------------------- 4f52bc17d888339b6bc3b9d27cd589aeee3b0b59 compiler/main/DriverPhases.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/main/DriverPhases.hs b/compiler/main/DriverPhases.hs index 177c15e..57455a5 100644 --- a/compiler/main/DriverPhases.hs +++ b/compiler/main/DriverPhases.hs @@ -289,8 +289,8 @@ phaseInputExt LlvmOpt = "ll" phaseInputExt LlvmLlc = "bc" phaseInputExt LlvmMangle = "lm_s" phaseInputExt SplitAs = "split_s" -phaseInputExt CmmCpp = "cmm" -phaseInputExt Cmm = "cmmcpp" +phaseInputExt CmmCpp = "cmmcpp" +phaseInputExt Cmm = "cmm" phaseInputExt MergeForeign = "o" phaseInputExt StopLn = "o" From git at git.haskell.org Sat Feb 3 02:58:51 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 3 Feb 2018 02:58:51 +0000 (UTC) Subject: [commit: ghc] master: integer-gmp: Simplify gmp/configure invocation (3441b14) Message-ID: <20180203025851.C02BC3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3441b1455bf9f2e7cc9e064e3edae3607c70a1c0/ghc >--------------------------------------------------------------- commit 3441b1455bf9f2e7cc9e064e3edae3607c70a1c0 Author: Ben Gamari Date: Fri Feb 2 13:58:14 2018 -0500 integer-gmp: Simplify gmp/configure invocation There weas lots of historical cruft to be found here. The `export SHELLOPTS` breaks on NixOS due to bash syntax in the gcc wrapper script. Reviewers: hvr Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4347 >--------------------------------------------------------------- 3441b1455bf9f2e7cc9e064e3edae3607c70a1c0 libraries/integer-gmp/gmp/ghc.mk | 5 +---- 1 file changed, 1 insertion(+), 4 deletions(-) diff --git a/libraries/integer-gmp/gmp/ghc.mk b/libraries/integer-gmp/gmp/ghc.mk index 8a74f76..794942c 100644 --- a/libraries/integer-gmp/gmp/ghc.mk +++ b/libraries/integer-gmp/gmp/ghc.mk @@ -130,10 +130,7 @@ libraries/integer-gmp/gmp/libgmp.a libraries/integer-gmp/gmp/gmp.h: # Note: We must pass `TARGETPLATFORM` to the `--host` argument of GMP's # `./configure`, not `HOSTPLATFORM`: the 'host' on which GMP will # run is the 'target' platform of the compiler we're building. - cd libraries/integer-gmp/gmp; (set -o igncr 2>/dev/null) && set -o igncr; export SHELLOPTS; \ - PATH=`pwd`:$$PATH; \ - export PATH; \ - cd gmpbuild && \ + cd libraries/integer-gmp/gmp/gmpbuild; \ CC=$(CCX) NM=$(NM) AR=$(AR_STAGE1) ./configure \ --enable-shared=no \ --host=$(TARGETPLATFORM) --build=$(BUILDPLATFORM) From git at git.haskell.org Sat Feb 3 03:30:11 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 3 Feb 2018 03:30:11 +0000 (UTC) Subject: [commit: ghc] master: Upgrade containers submodule (fdf518c) Message-ID: <20180203033011.1916E3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fdf518c708dc5a34ae810c5d5f3a4db812d226f0/ghc >--------------------------------------------------------------- commit fdf518c708dc5a34ae810c5d5f3a4db812d226f0 Author: David Feuer Date: Fri Feb 2 13:58:28 2018 -0500 Upgrade containers submodule Reviewers: bgamari Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4340 >--------------------------------------------------------------- fdf518c708dc5a34ae810c5d5f3a4db812d226f0 libraries/containers | 2 +- testsuite/tests/backpack/should_run/bkprun05.stderr | 2 +- testsuite/tests/driver/T10970.stdout | 2 +- testsuite/tests/package/package01e.stderr | 4 ++-- 4 files changed, 5 insertions(+), 5 deletions(-) diff --git a/libraries/containers b/libraries/containers index c07e484..a57e7dd 160000 --- a/libraries/containers +++ b/libraries/containers @@ -1 +1 @@ -Subproject commit c07e4848e1b4458265e30cfb6265f9b6bd2bf053 +Subproject commit a57e7dd0c0aa6a719a73085ae30edef8206ccea0 diff --git a/testsuite/tests/backpack/should_run/bkprun05.stderr b/testsuite/tests/backpack/should_run/bkprun05.stderr index 854de8b..2c24fda 100644 --- a/testsuite/tests/backpack/should_run/bkprun05.stderr +++ b/testsuite/tests/backpack/should_run/bkprun05.stderr @@ -1,4 +1,4 @@ bkprun05: Prelude.undefined CallStack (from HasCallStack): error, called at libraries/base/GHC/Err.hs:79:14 in base:GHC.Err - undefined, called at bkprun05.bkp:138:30 in app+app-89WS9ScvjQd9lPG2oW0wWM:App + undefined, called at bkprun05.bkp:138:30 in app+app-0UPCJKIsbig160BXB4AqAb:App diff --git a/testsuite/tests/driver/T10970.stdout b/testsuite/tests/driver/T10970.stdout index 9636217..3a25dc5 100644 --- a/testsuite/tests/driver/T10970.stdout +++ b/testsuite/tests/driver/T10970.stdout @@ -1,2 +1,2 @@ -0.5.10.2 +0.5.11.0 OK diff --git a/testsuite/tests/package/package01e.stderr b/testsuite/tests/package/package01e.stderr index cfde9a7..7dd9f69 100644 --- a/testsuite/tests/package/package01e.stderr +++ b/testsuite/tests/package/package01e.stderr @@ -1,10 +1,10 @@ package01e.hs:2:1: error: Could not find module ‘Data.Map’ - It is a member of the hidden package ‘containers-0.5.10.2’. + It is a member of the hidden package ‘containers-0.5.11.0’. Use -v to see a list of the files searched for. package01e.hs:3:1: error: Could not find module ‘Data.IntMap’ - It is a member of the hidden package ‘containers-0.5.10.2’. + It is a member of the hidden package ‘containers-0.5.11.0’. Use -v to see a list of the files searched for. From git at git.haskell.org Sat Feb 3 16:58:11 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 3 Feb 2018 16:58:11 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: Option for LINE pragmas to get lexed into tokens (0e073e5) Message-ID: <20180203165811.079D53A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/0e073e558ffd6dd4a5184d41a68189ac541501df/ghc >--------------------------------------------------------------- commit 0e073e558ffd6dd4a5184d41a68189ac541501df Author: Alec Theriault Date: Fri Jan 26 13:09:58 2018 -0500 Option for LINE pragmas to get lexed into tokens This adds a parser-level switch to have 'LINE' and 'COLUMN' pragmas lexed into actual tokens (as opposed to updating the position information in the parser). 'lexTokenStream' is the only place where this option is enabled. Reviewers: bgamari, alexbiehl, mpickering Reviewed By: mpickering Subscribers: alanz, rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4336 (cherry picked from commit 9a57cfebd2e65109884712a27a0f29d1a71f57b7) >--------------------------------------------------------------- 0e073e558ffd6dd4a5184d41a68189ac541501df compiler/parser/Lexer.x | 35 +++++++++++++++++++++++++++++++---- 1 file changed, 31 insertions(+), 4 deletions(-) diff --git a/compiler/parser/Lexer.x b/compiler/parser/Lexer.x index b2004a6..44c5c9d 100644 --- a/compiler/parser/Lexer.x +++ b/compiler/parser/Lexer.x @@ -640,7 +640,8 @@ data Token | ITrules_prag SourceText | ITwarning_prag SourceText | ITdeprecated_prag SourceText - | ITline_prag + | ITline_prag SourceText -- not usually produced, see 'use_pos_prags' + | ITcolumn_prag SourceText -- not usually produced, see 'use_pos_prags' | ITscc_prag SourceText | ITgenerated_prag SourceText | ITcore_prag SourceText -- hdaume: core annotations @@ -1140,6 +1141,27 @@ rulePrag span buf len = do let !src = lexemeToString buf len return (L span (ITrules_prag (SourceText src))) +-- When 'use_pos_prags' is not set, it is expected that we emit a token instead +-- of updating the position in 'PState' +linePrag :: Action +linePrag span buf len = do + ps <- getPState + if use_pos_prags ps + then begin line_prag2 span buf len + else let !src = lexemeToString buf len + in return (L span (ITline_prag (SourceText src))) + +-- When 'use_pos_prags' is not set, it is expected that we emit a token instead +-- of updating the position in 'PState' +columnPrag :: Action +columnPrag span buf len = do + ps <- getPState + let !src = lexemeToString buf len + if use_pos_prags ps + then begin column_prag span buf len + else let !src = lexemeToString buf len + in return (L span (ITcolumn_prag (SourceText src))) + endPrag :: Action endPrag span _buf _len = do setExts (.&. complement (xbit InRulePragBit)) @@ -1873,6 +1895,10 @@ data PState = PState { -- token doesn't need to close anything: alr_justClosedExplicitLetBlock :: Bool, + -- If this is enabled, '{-# LINE ... -#}' and '{-# COLUMN ... #-}' + -- update the 'loc' field. Otherwise, those pragmas are lexed as tokens. + use_pos_prags :: Bool, + -- The next three are used to implement Annotations giving the -- locations of 'noise' tokens in the source, so that users of -- the GHC API can do source to source conversions. @@ -2375,6 +2401,7 @@ mkPStatePure options buf loc = alr_context = [], alr_expecting_ocurly = Nothing, alr_justClosedExplicitLetBlock = False, + use_pos_prags = True, annotations = [], comment_q = [], annotations_comments = [] @@ -2786,14 +2813,14 @@ reportLexError loc1 loc2 buf str lexTokenStream :: StringBuffer -> RealSrcLoc -> DynFlags -> ParseResult [Located Token] lexTokenStream buf loc dflags = unP go initState where dflags' = gopt_set (gopt_unset dflags Opt_Haddock) Opt_KeepRawTokenStream - initState = mkPState dflags' buf loc + initState = (mkPState dflags' buf loc) { use_pos_prags = False } go = do ltok <- lexer False return case ltok of L _ ITeof -> return [] _ -> liftM (ltok:) go -linePrags = Map.singleton "line" (begin line_prag2) +linePrags = Map.singleton "line" linePrag fileHeaderPrags = Map.fromList([("options", lex_string_prag IToptions_prag), ("options_ghc", lex_string_prag IToptions_prag), @@ -2838,7 +2865,7 @@ oneWordPrags = Map.fromList [ ("incoherent", strtoken (\s -> ITincoherent_prag (SourceText s))), ("ctype", strtoken (\s -> ITctype (SourceText s))), ("complete", strtoken (\s -> ITcomplete_prag (SourceText s))), - ("column", begin column_prag) + ("column", columnPrag) ] twoWordPrags = Map.fromList([ From git at git.haskell.org Sat Feb 3 16:58:13 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 3 Feb 2018 16:58:13 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: Haddock needs to pass visible modules for instance filtering (42a82cf) Message-ID: <20180203165813.C0DB03A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/42a82cf4c8fa95195b4ab55795c919512f92d5f4/ghc >--------------------------------------------------------------- commit 42a82cf4c8fa95195b4ab55795c919512f92d5f4 Author: Alec Theriault Date: Fri Jan 26 13:05:31 2018 -0500 Haddock needs to pass visible modules for instance filtering The GHC-side `getNameToInstancesIndex` filters out incorrectly some instances because it is not aware of what modules are visible. Using `runTcInteractive` means that `ie_visible` gets initialized to a one module set containing some dummy GHCi module. This is clearly not the module set we want to check against to see if a given orphan instance is visible or not. In fact, GHC has no way of knowing what we want that module set to be since it doesn't know ahead of time which modules Haddock is making its docs for. The fix is just to pass that set in as an argument. Bumps haddock submodule. Reviewers: bgamari Reviewed By: bgamari Subscribers: duog, alexbiehl, rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4290 (cherry picked from commit a47438e88e685971a81874565f2914043c8233c3) >--------------------------------------------------------------- 42a82cf4c8fa95195b4ab55795c919512f92d5f4 compiler/main/GHC.hs | 11 +++++++---- testsuite/tests/perf/haddock/all.T | 3 ++- utils/haddock | 2 +- 3 files changed, 10 insertions(+), 6 deletions(-) diff --git a/compiler/main/GHC.hs b/compiler/main/GHC.hs index 343ef37..1e54f0e 100644 --- a/compiler/main/GHC.hs +++ b/compiler/main/GHC.hs @@ -1244,12 +1244,15 @@ getGRE = withSession $ \hsc_env-> return $ ic_rn_gbl_env (hsc_IC hsc_env) -- by 'Name'. Each name's lists will contain every instance in which that name -- is mentioned in the instance head. getNameToInstancesIndex :: GhcMonad m - => m (Messages, Maybe (NameEnv ([ClsInst], [FamInst]))) -getNameToInstancesIndex = do + => [Module] -- ^ visible modules. An orphan instance will be returned if and + -- only it is visible from at least one module in the list. + -> m (Messages, Maybe (NameEnv ([ClsInst], [FamInst]))) +getNameToInstancesIndex visible_mods = do hsc_env <- getSession liftIO $ runTcInteractive hsc_env $ do { loadUnqualIfaces hsc_env (hsc_IC hsc_env) - ; InstEnvs {ie_global, ie_local, ie_visible} <- tcGetInstEnvs + ; InstEnvs {ie_global, ie_local} <- tcGetInstEnvs + ; let visible_mods' = mkModuleSet visible_mods ; (pkg_fie, home_fie) <- tcGetFamInstEnvs -- We use Data.Sequence.Seq because we are creating left associated -- mappends. @@ -1257,7 +1260,7 @@ getNameToInstancesIndex = do ; let cls_index = Map.fromListWith mappend [ (n, Seq.singleton ispec) | ispec <- instEnvElts ie_local ++ instEnvElts ie_global - , instIsVisible ie_visible ispec + , instIsVisible visible_mods' ispec , n <- nameSetElemsStable $ orphNamesOfClsInst ispec ] ; let fam_index = Map.fromListWith mappend diff --git a/testsuite/tests/perf/haddock/all.T b/testsuite/tests/perf/haddock/all.T index b7e6b21..576ac38 100644 --- a/testsuite/tests/perf/haddock/all.T +++ b/testsuite/tests/perf/haddock/all.T @@ -69,7 +69,7 @@ test('haddock.Cabal', [extra_files(['../../../../libraries/Cabal/Cabal/dist-install/haddock.t']), unless(in_tree_compiler(), skip), req_haddock ,stats_num_field('bytes allocated', - [(wordsize(64), 20104611952, 5) + [(wordsize(64), 25699561072, 5) # 2012-08-14: 3255435248 (amd64/Linux) # 2012-08-29: 3324606664 (amd64/Linux, new codegen) # 2012-10-08: 3373401360 (amd64/Linux) @@ -121,6 +121,7 @@ test('haddock.Cabal', # 2017-11-02: 17133915848 (amd64/Linux) - Phabricator D4144 # 2017-11-06: 18936339648 (amd64/Linux) - Unknown # 2017-11-09: 20104611952 (amd64/Linux) - Bump Cabal + # 2018-02-03: 25699561072 (x86_64/Linux) - Bump haddock submodule ,(platform('i386-unknown-mingw32'), 3293415576, 5) # 2012-10-30: 1733638168 (x86/Windows) diff --git a/utils/haddock b/utils/haddock index e329a73..ac33472 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit e329a73765c510774e3a3f54472bcdeca48613f6 +Subproject commit ac33472e834d381f95fd56586e57e6653263055c From git at git.haskell.org Sat Feb 3 16:58:16 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 3 Feb 2018 16:58:16 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: Upgrade containers submodule (445554b) Message-ID: <20180203165816.8DE053A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/445554b6d9a2263f969e25bb9f532dd0c3a9dc8c/ghc >--------------------------------------------------------------- commit 445554b6d9a2263f969e25bb9f532dd0c3a9dc8c Author: David Feuer Date: Fri Feb 2 13:58:28 2018 -0500 Upgrade containers submodule Reviewers: bgamari Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4340 (cherry picked from commit fdf518c708dc5a34ae810c5d5f3a4db812d226f0) >--------------------------------------------------------------- 445554b6d9a2263f969e25bb9f532dd0c3a9dc8c libraries/containers | 2 +- testsuite/tests/backpack/should_run/bkprun05.stderr | 2 +- testsuite/tests/driver/T10970.stdout | 2 +- testsuite/tests/package/package01e.stderr | 4 ++-- 4 files changed, 5 insertions(+), 5 deletions(-) diff --git a/libraries/containers b/libraries/containers index c07e484..a57e7dd 160000 --- a/libraries/containers +++ b/libraries/containers @@ -1 +1 @@ -Subproject commit c07e4848e1b4458265e30cfb6265f9b6bd2bf053 +Subproject commit a57e7dd0c0aa6a719a73085ae30edef8206ccea0 diff --git a/testsuite/tests/backpack/should_run/bkprun05.stderr b/testsuite/tests/backpack/should_run/bkprun05.stderr index 854de8b..2c24fda 100644 --- a/testsuite/tests/backpack/should_run/bkprun05.stderr +++ b/testsuite/tests/backpack/should_run/bkprun05.stderr @@ -1,4 +1,4 @@ bkprun05: Prelude.undefined CallStack (from HasCallStack): error, called at libraries/base/GHC/Err.hs:79:14 in base:GHC.Err - undefined, called at bkprun05.bkp:138:30 in app+app-89WS9ScvjQd9lPG2oW0wWM:App + undefined, called at bkprun05.bkp:138:30 in app+app-0UPCJKIsbig160BXB4AqAb:App diff --git a/testsuite/tests/driver/T10970.stdout b/testsuite/tests/driver/T10970.stdout index 9636217..3a25dc5 100644 --- a/testsuite/tests/driver/T10970.stdout +++ b/testsuite/tests/driver/T10970.stdout @@ -1,2 +1,2 @@ -0.5.10.2 +0.5.11.0 OK diff --git a/testsuite/tests/package/package01e.stderr b/testsuite/tests/package/package01e.stderr index cfde9a7..7dd9f69 100644 --- a/testsuite/tests/package/package01e.stderr +++ b/testsuite/tests/package/package01e.stderr @@ -1,10 +1,10 @@ package01e.hs:2:1: error: Could not find module ‘Data.Map’ - It is a member of the hidden package ‘containers-0.5.10.2’. + It is a member of the hidden package ‘containers-0.5.11.0’. Use -v to see a list of the files searched for. package01e.hs:3:1: error: Could not find module ‘Data.IntMap’ - It is a member of the hidden package ‘containers-0.5.10.2’. + It is a member of the hidden package ‘containers-0.5.11.0’. Use -v to see a list of the files searched for. From git at git.haskell.org Sat Feb 3 17:30:16 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 3 Feb 2018 17:30:16 +0000 (UTC) Subject: [commit: ghc] master: ghc-prim: Emulate C11 atomics when not available (217e417) Message-ID: <20180203173016.00F113A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/217e4170bdce3df28a667803ce5e619553bfecdd/ghc >--------------------------------------------------------------- commit 217e4170bdce3df28a667803ce5e619553bfecdd Author: Ben Gamari Date: Sat Feb 3 11:37:01 2018 -0500 ghc-prim: Emulate C11 atomics when not available GCC's __sync primitives apparently "usually" imply a full barrier, meaning they can be used to emulate the more precise C11 atomics albeit with a loss of efficiency. This restores compatibility with GCC 4.4. This partially reverts commit 59de290928e6903337f31c1f8107ac8a98ea145d. Test Plan: Validate on Centos Reviewers: hvr, simonmar, trommler Subscribers: rwbarton, thomie, erikd, carter GHC Trac Issues: #14244 Differential Revision: https://phabricator.haskell.org/D4364 >--------------------------------------------------------------- 217e4170bdce3df28a667803ce5e619553bfecdd aclocal.m4 | 25 +++++++++++++++++++++++-- configure.ac | 5 +++++ libraries/ghc-prim/cbits/atomic.c | 36 ++++++++++++++++++++++++++++++++++++ mk/config.mk.in | 1 + mk/warnings.mk | 4 +++- rts/ghc.mk | 2 ++ 6 files changed, 70 insertions(+), 3 deletions(-) diff --git a/aclocal.m4 b/aclocal.m4 index 5989a13..2ed2c08 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -1237,15 +1237,18 @@ if test -z "$CC" then AC_MSG_ERROR([gcc is required]) fi +GccLT46=NO AC_CACHE_CHECK([version of gcc], [fp_cv_gcc_version], [ # Be sure only to look at the first occurrence of the "version " string; # Some Apple compilers emit multiple messages containing this string. fp_cv_gcc_version="`$CC -v 2>&1 | sed -n -e '1,/version /s/.*version [[^0-9]]*\([[0-9.]]*\).*/\1/p'`" - FP_COMPARE_VERSIONS([$fp_cv_gcc_version], [-lt], [4.7], - [AC_MSG_ERROR([Need at least gcc version 4.7])]) + FP_COMPARE_VERSIONS([$fp_cv_gcc_version], [-lt], [4.4], + [AC_MSG_ERROR([Need at least gcc version 4.4 (4.7+ recommended)])]) + FP_COMPARE_VERSIONS([$fp_cv_gcc_version], [-lt], [4.6], GccLT46=YES) ]) AC_SUBST([GccVersion], [$fp_cv_gcc_version]) +AC_SUBST(GccLT46) ])# FP_GCC_VERSION dnl Check to see if the C compiler is clang or llvm-gcc @@ -1278,6 +1281,24 @@ AC_SUBST(GccIsClang) rm -f conftest.txt ]) +# FP_GCC_SUPPORTS__ATOMICS +# ------------------------ +# Does gcc support the __atomic_* family of builtins? +AC_DEFUN([FP_GCC_SUPPORTS__ATOMICS], +[ + AC_REQUIRE([AC_PROG_CC]) + AC_MSG_CHECKING([whether GCC supports __atomic_ builtins]) + echo 'int test(int *x) { int y; __atomic_load(&x, &y, __ATOMIC_SEQ_CST); return x; }' > conftest.c + if $CC -c conftest.c > /dev/null 2>&1; then + CONF_GCC_SUPPORTS__ATOMICS=YES + AC_MSG_RESULT([yes]) + else + CONF_GCC_SUPPORTS__ATOMICS=NO + AC_MSG_RESULT([no]) + fi + rm -f conftest.c conftest.o +]) + # FP_GCC_SUPPORTS_NO_PIE # ---------------------- # Does gcc support the -no-pie option? If so we should pass it to gcc when diff --git a/configure.ac b/configure.ac index 216a97f..5bf096b 100644 --- a/configure.ac +++ b/configure.ac @@ -712,6 +712,11 @@ FP_GCC_VERSION dnl ** See whether gcc supports -no-pie FP_GCC_SUPPORTS_NO_PIE +dnl ** Used to determine how to compile ghc-prim's atomics.c, used by +dnl unregisterised, Sparc, and PPC backends. +FP_GCC_SUPPORTS__ATOMICS +AC_DEFINE([HAVE_C11_ATOMICS], [$CONF_GCC_SUPPORTS__ATOMICS], [Does GCC support __atomic primitives?]) + FP_GCC_EXTRA_FLAGS dnl ** look to see if we have a C compiler using an llvm back end. diff --git a/libraries/ghc-prim/cbits/atomic.c b/libraries/ghc-prim/cbits/atomic.c index b091d22..2ded465 100644 --- a/libraries/ghc-prim/cbits/atomic.c +++ b/libraries/ghc-prim/cbits/atomic.c @@ -264,33 +264,53 @@ hs_cmpxchg64(StgWord x, StgWord64 old, StgWord64 new) // __ATOMIC_SEQ_CST: Full barrier in both directions (hoisting and sinking // of code) and synchronizes with acquire loads and release stores in // all threads. +// +// When we lack C11 atomics support we emulate these using the old GCC __sync +// primitives which the GCC documentation claims "usually" implies a full +// barrier. extern StgWord hs_atomicread8(StgWord x); StgWord hs_atomicread8(StgWord x) { +#if HAVE_C11_ATOMICS return __atomic_load_n((StgWord8 *) x, __ATOMIC_SEQ_CST); +#else + return __sync_add_and_fetch((StgWord8 *) x, 0); +#endif } extern StgWord hs_atomicread16(StgWord x); StgWord hs_atomicread16(StgWord x) { +#if HAVE_C11_ATOMICS return __atomic_load_n((StgWord16 *) x, __ATOMIC_SEQ_CST); +#else + return __sync_add_and_fetch((StgWord16 *) x, 0); +#endif } extern StgWord hs_atomicread32(StgWord x); StgWord hs_atomicread32(StgWord x) { +#if HAVE_C11_ATOMICS return __atomic_load_n((StgWord32 *) x, __ATOMIC_SEQ_CST); +#else + return __sync_add_and_fetch((StgWord32 *) x, 0); +#endif } extern StgWord64 hs_atomicread64(StgWord x); StgWord64 hs_atomicread64(StgWord x) { +#if HAVE_C11_ATOMICS return __atomic_load_n((StgWord64 *) x, __ATOMIC_SEQ_CST); +#else + return __sync_add_and_fetch((StgWord64 *) x, 0); +#endif } // AtomicWriteByteArrayOp_Int @@ -301,26 +321,42 @@ extern void hs_atomicwrite8(StgWord x, StgWord val); void hs_atomicwrite8(StgWord x, StgWord val) { +#if HAVE_C11_ATOMICS __atomic_store_n((StgWord8 *) x, (StgWord8) val, __ATOMIC_SEQ_CST); +#else + while (!__sync_bool_compare_and_swap((StgWord8 *) x, *(StgWord8 *) x, (StgWord8) val)); +#endif } extern void hs_atomicwrite16(StgWord x, StgWord val); void hs_atomicwrite16(StgWord x, StgWord val) { +#if HAVE_C11_ATOMICS __atomic_store_n((StgWord16 *) x, (StgWord16) val, __ATOMIC_SEQ_CST); +#else + while (!__sync_bool_compare_and_swap((StgWord16 *) x, *(StgWord16 *) x, (StgWord16) val)); +#endif } extern void hs_atomicwrite32(StgWord x, StgWord val); void hs_atomicwrite32(StgWord x, StgWord val) { +#if HAVE_C11_ATOMICS __atomic_store_n((StgWord32 *) x, (StgWord32) val, __ATOMIC_SEQ_CST); +#else + while (!__sync_bool_compare_and_swap((StgWord32 *) x, *(StgWord32 *) x, (StgWord32) val)); +#endif } extern void hs_atomicwrite64(StgWord x, StgWord64 val); void hs_atomicwrite64(StgWord x, StgWord64 val) { +#if HAVE_C11_ATOMICS __atomic_store_n((StgWord64 *) x, (StgWord64) val, __ATOMIC_SEQ_CST); +#else + while (!__sync_bool_compare_and_swap((StgWord64 *) x, *(StgWord64 *) x, (StgWord64) val)); +#endif } diff --git a/mk/config.mk.in b/mk/config.mk.in index b046abe..86c626d 100644 --- a/mk/config.mk.in +++ b/mk/config.mk.in @@ -522,6 +522,7 @@ GccVersion = @GccVersion@ # TargetPlatformFull retains the string passed to configure so we have it in # the necessary format to pass to libffi's configure. TargetPlatformFull = @TargetPlatformFull@ +GccLT46 = @GccLT46@ GccIsClang = @GccIsClang@ CC = @CC@ diff --git a/mk/warnings.mk b/mk/warnings.mk index 9426db2..0ae81bf 100644 --- a/mk/warnings.mk +++ b/mk/warnings.mk @@ -20,11 +20,13 @@ GhcStage2HcOpts += -Wcpp-undef ifneq "$(GccIsClang)" "YES" # Debian doesn't turn -Werror=unused-but-set-variable on by default, so -# we turn it on explicitly for consistency with other users. +# we turn it on explicitly for consistency with other users +ifeq "$(GccLT46)" "NO" # Never set the flag on Windows as the host gcc may be too old. ifneq "$(HostOS_CPP)" "mingw32" SRC_CC_WARNING_OPTS += -Werror=unused-but-set-variable endif +endif # Suppress the warning about __sync_fetch_and_nand (#9678). libraries/ghc-prim/cbits/atomic_CC_OPTS += -Wno-sync-nand diff --git a/rts/ghc.mk b/rts/ghc.mk index 690a883..761cc43 100644 --- a/rts/ghc.mk +++ b/rts/ghc.mk @@ -311,7 +311,9 @@ WARNING_OPTS += -Wpointer-arith WARNING_OPTS += -Wmissing-noreturn WARNING_OPTS += -Wnested-externs WARNING_OPTS += -Wredundant-decls +ifeq "$(GccLT46)" "NO" WARNING_OPTS += -Wundef +endif # These ones are hard to avoid: #WARNING_OPTS += -Wconversion From git at git.haskell.org Sat Feb 3 17:30:19 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 3 Feb 2018 17:30:19 +0000 (UTC) Subject: [commit: ghc] master: Don't apply dataToTag's caseRules for data families (d8a0e6d) Message-ID: <20180203173019.34D6D3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d8a0e6d322deaa3743c95a11a6b7272577d1f86e/ghc >--------------------------------------------------------------- commit d8a0e6d322deaa3743c95a11a6b7272577d1f86e Author: Ryan Scott Date: Sat Feb 3 11:40:43 2018 -0500 Don't apply dataToTag's caseRules for data families Commit 193664d42dbceadaa1e4689dfa17ff1cf5a405a0 added a special caseRule for `dataToTag`, but this transformation completely broke when `dataToTag` was applied to somewith with a type headed by a data family, leading to #14680. For now at least, the simplest solution is to simply not apply this transformation when the type is headed by a data family. Test Plan: make test TEST=T14680 Reviewers: simonpj, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14680 Differential Revision: https://phabricator.haskell.org/D4371 >--------------------------------------------------------------- d8a0e6d322deaa3743c95a11a6b7272577d1f86e compiler/prelude/PrelRules.hs | 12 ++++++++++-- .../tests/indexed-types/should_compile/T14680.hs | 19 +++++++++++++++++++ testsuite/tests/indexed-types/should_compile/all.T | 1 + 3 files changed, 30 insertions(+), 2 deletions(-) diff --git a/compiler/prelude/PrelRules.hs b/compiler/prelude/PrelRules.hs index db79589..49cd9fa 100644 --- a/compiler/prelude/PrelRules.hs +++ b/compiler/prelude/PrelRules.hs @@ -37,8 +37,8 @@ import CoreOpt ( exprIsLiteral_maybe ) import PrimOp ( PrimOp(..), tagToEnumKey ) import TysWiredIn import TysPrim -import TyCon ( tyConDataCons_maybe, isEnumerationTyCon, isNewTyCon - , unwrapNewTyCon_maybe, tyConDataCons ) +import TyCon ( tyConDataCons_maybe, isAlgTyCon, isEnumerationTyCon + , isNewTyCon, unwrapNewTyCon_maybe, tyConDataCons ) import DataCon ( DataCon, dataConTagZ, dataConTyCon, dataConWorkId ) import CoreUtils ( cheapEqExpr, exprIsHNF, exprType ) import CoreUnfold ( exprIsConApp_maybe ) @@ -1449,6 +1449,8 @@ caseRules dflags (App (App (Var f) type_arg) v) -- See Note [caseRules for dataToTag] caseRules _ (App (App (Var f) (Type ty)) v) -- dataToTag x | Just DataToTagOp <- isPrimOpId_maybe f + , Just (tc, _) <- tcSplitTyConApp_maybe ty + , isAlgTyCon tc = Just (v, tx_con_dtt ty , \v -> App (App (Var f) (Type ty)) (Var v)) @@ -1549,4 +1551,10 @@ into Note the need for some wildcard binders in the 'cons' case. + +For the time, we only apply this transformation when the type of `x` is a type +headed by a normal tycon. In particular, we do not apply this in the case of a +data family tycon, since that would require carefully applying coercion(s) +between the data family and the data family instance's representation type, +which caseRules isn't currently engineered to handle (#14680). -} diff --git a/testsuite/tests/indexed-types/should_compile/T14680.hs b/testsuite/tests/indexed-types/should_compile/T14680.hs new file mode 100644 index 0000000..9694c0a --- /dev/null +++ b/testsuite/tests/indexed-types/should_compile/T14680.hs @@ -0,0 +1,19 @@ +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE TypeFamilies #-} +{-# OPTIONS_GHC -O1 #-} +module T14680 where + +import GHC.Base (getTag) +import GHC.Exts (Int(..), tagToEnum#) + +data family TyFamilyEnum +data instance TyFamilyEnum = TyFamilyEnum1 | TyFamilyEnum2 | TyFamilyEnum3 + +suc :: TyFamilyEnum -> TyFamilyEnum +suc a_aaf8 + = case getTag a_aaf8 of + a_aaf9 + -> if 2 == I# a_aaf9 + then error "succ{TyFamilyEnum}: tried to take `succ' of last tag in enumeration" + else case I# a_aaf9 + 1 of + I# i_aafa -> tagToEnum# i_aafa :: TyFamilyEnum diff --git a/testsuite/tests/indexed-types/should_compile/all.T b/testsuite/tests/indexed-types/should_compile/all.T index 9250fa2..8e89ecf 100644 --- a/testsuite/tests/indexed-types/should_compile/all.T +++ b/testsuite/tests/indexed-types/should_compile/all.T @@ -272,3 +272,4 @@ test('T14131', normal, compile, ['']) test('T14162', normal, compile, ['']) test('T14237', normal, compile, ['']) test('T14554', normal, compile, ['']) +test('T14680', normal, compile, ['']) From git at git.haskell.org Sun Feb 4 01:36:00 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Feb 2018 01:36:00 +0000 (UTC) Subject: [commit: ghc] master: base: Deprecate STM invariant checking primitives (e5d0101) Message-ID: <20180204013600.761633A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e5d0101121cf4ce4dffe59025360096ee57c5372/ghc >--------------------------------------------------------------- commit e5d0101121cf4ce4dffe59025360096ee57c5372 Author: Ben Gamari Date: Sat Feb 3 13:11:17 2018 -0500 base: Deprecate STM invariant checking primitives >--------------------------------------------------------------- e5d0101121cf4ce4dffe59025360096ee57c5372 libraries/base/GHC/Conc/Sync.hs | 12 ++++++++++++ libraries/base/changelog.md | 3 +++ 2 files changed, 15 insertions(+) diff --git a/libraries/base/GHC/Conc/Sync.hs b/libraries/base/GHC/Conc/Sync.hs index de77792..0bd2900 100644 --- a/libraries/base/GHC/Conc/Sync.hs +++ b/libraries/base/GHC/Conc/Sync.hs @@ -782,6 +782,18 @@ catchSTM (STM m) handler = STM $ catchSTM# m handler' Just e' -> unSTM (handler e') Nothing -> raiseIO# e +-- Invariant checking has been removed. See #14324 and +-- https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0011-deprecate-stm-invariants.rst +{-# DEPRECATED checkInv, always, alwaysSucceeds + [ "The STM invariant-checking mechanism is deprecated in GHC 8.4" + , "and will be removed in GHC 8.10. See " + , "." + , "" + , "Existing users are encouraged to encapsulate their STM" + , "operations in safe abstractions which can perform the invariant" + , "checking without help from the runtime system." + ] #-} + -- | Low-level primitive on which 'always' and 'alwaysSucceeds' are built. -- 'checkInv' differs from these in that, -- diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index fdeb7de..ad8767f 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -76,6 +76,9 @@ * `getExecutablePath` now resolves symlinks on Windows (#14483) + * Deprecated STM invariant checking primitives (`checkInv`, `always`, and + `alwaysSucceeds`) in `GHC.Conc.Sync` (#14324). + ## 4.10.1.0 *November 2017* * Bundled with GHC 8.2.2 From git at git.haskell.org Sun Feb 4 01:36:03 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Feb 2018 01:36:03 +0000 (UTC) Subject: [commit: ghc] master: cmm: Revert more aggressive CBE due to #14226 (50adbd7) Message-ID: <20180204013603.49FF33A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/50adbd7c5fe5894d3e6e2a58b353ed07e5f8949d/ghc >--------------------------------------------------------------- commit 50adbd7c5fe5894d3e6e2a58b353ed07e5f8949d Author: Ben Gamari Date: Sat Feb 3 19:49:21 2018 -0500 cmm: Revert more aggressive CBE due to #14226 Trac #14226 noted that the C-- CBE pass frequently fails to common up semantically identical blocks due to the differences in local register naming. These patches fixed this by making the pass consider equality up to alpha-renaming. However, the new logic failed to consider the possibility that local register naming *may* matter across multiple blocks. This lead to the regression #14754. I'll need to do a bit of thinking on a proper solution to this but in the meantime I'm reverting all four patches. This reverts commit a27056f9823f8bbe2302f1924b3ab38fd6752e37. This reverts commit 6f990c54f922beae80362fe62426beededc21290. This reverts commit 9aa73892e10e90a1799b9277da593e816a827364. This reverts commit 7920a7d9c53083b234e060a3e72f00b601a46808. >--------------------------------------------------------------- 50adbd7c5fe5894d3e6e2a58b353ed07e5f8949d compiler/cmm/CmmCommonBlockElim.hs | 320 ++++++++++--------------------------- compiler/cmm/CmmPipeline.hs | 2 +- compiler/cmm/Hoopl/Block.hs | 1 - 3 files changed, 86 insertions(+), 237 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 50adbd7c5fe5894d3e6e2a58b353ed07e5f8949d From git at git.haskell.org Sun Feb 4 01:36:06 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Feb 2018 01:36:06 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Add testcase for #14754 (606edbf) Message-ID: <20180204013606.AC3443A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/606edbfba14b025ce85a02e5ed7c03e8a097d692/ghc >--------------------------------------------------------------- commit 606edbfba14b025ce85a02e5ed7c03e8a097d692 Author: Ben Gamari Date: Sat Feb 3 19:19:08 2018 -0500 testsuite: Add testcase for #14754 >--------------------------------------------------------------- 606edbfba14b025ce85a02e5ed7c03e8a097d692 testsuite/tests/codeGen/should_run/T14754.hs | 15 +++++++++++++++ testsuite/tests/codeGen/should_run/T14754.stderr | 2 ++ .../bkprun02.stdout => codeGen/should_run/T14754.stdout} | 0 testsuite/tests/codeGen/should_run/all.T | 1 + 4 files changed, 18 insertions(+) diff --git a/testsuite/tests/codeGen/should_run/T14754.hs b/testsuite/tests/codeGen/should_run/T14754.hs new file mode 100644 index 0000000..181659d --- /dev/null +++ b/testsuite/tests/codeGen/should_run/T14754.hs @@ -0,0 +1,15 @@ +module Main where + +import Debug.Trace + +main :: IO () +main = print (alg 3 1) + +alg :: Word -> Word -> Word +alg a b + | traceShow (a, b) False = undefined + | c < b = alg b c + | c > b = alg c b + | otherwise = c + where + c = a - b diff --git a/testsuite/tests/codeGen/should_run/T14754.stderr b/testsuite/tests/codeGen/should_run/T14754.stderr new file mode 100644 index 0000000..42c78ed --- /dev/null +++ b/testsuite/tests/codeGen/should_run/T14754.stderr @@ -0,0 +1,2 @@ +(3,1) +(2,1) diff --git a/testsuite/tests/backpack/should_run/bkprun02.stdout b/testsuite/tests/codeGen/should_run/T14754.stdout similarity index 100% copy from testsuite/tests/backpack/should_run/bkprun02.stdout copy to testsuite/tests/codeGen/should_run/T14754.stdout diff --git a/testsuite/tests/codeGen/should_run/all.T b/testsuite/tests/codeGen/should_run/all.T index 145365e..9403c4b 100644 --- a/testsuite/tests/codeGen/should_run/all.T +++ b/testsuite/tests/codeGen/should_run/all.T @@ -166,3 +166,4 @@ test('T13825-unit', compile_and_run, ['-package ghc']) test('T14619', normal, compile_and_run, ['']) +test('T14754', normal, compile_and_run, ['']) From git at git.haskell.org Sun Feb 4 02:11:06 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Feb 2018 02:11:06 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: Don't apply dataToTag's caseRules for data families (b7f9139) Message-ID: <20180204021106.B0FBD3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/b7f9139ccddf4a1ca5839cd50ad8dba4f5e2e1dc/ghc >--------------------------------------------------------------- commit b7f9139ccddf4a1ca5839cd50ad8dba4f5e2e1dc Author: Ryan Scott Date: Sat Feb 3 11:40:43 2018 -0500 Don't apply dataToTag's caseRules for data families Commit 193664d42dbceadaa1e4689dfa17ff1cf5a405a0 added a special caseRule for `dataToTag`, but this transformation completely broke when `dataToTag` was applied to somewith with a type headed by a data family, leading to #14680. For now at least, the simplest solution is to simply not apply this transformation when the type is headed by a data family. Test Plan: make test TEST=T14680 Reviewers: simonpj, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14680 Differential Revision: https://phabricator.haskell.org/D4371 (cherry picked from commit d8a0e6d322deaa3743c95a11a6b7272577d1f86e) >--------------------------------------------------------------- b7f9139ccddf4a1ca5839cd50ad8dba4f5e2e1dc compiler/prelude/PrelRules.hs | 12 ++++++++++-- .../tests/indexed-types/should_compile/T14680.hs | 19 +++++++++++++++++++ testsuite/tests/indexed-types/should_compile/all.T | 1 + 3 files changed, 30 insertions(+), 2 deletions(-) diff --git a/compiler/prelude/PrelRules.hs b/compiler/prelude/PrelRules.hs index 8838c4a..80a1145 100644 --- a/compiler/prelude/PrelRules.hs +++ b/compiler/prelude/PrelRules.hs @@ -37,8 +37,8 @@ import CoreOpt ( exprIsLiteral_maybe ) import PrimOp ( PrimOp(..), tagToEnumKey ) import TysWiredIn import TysPrim -import TyCon ( tyConDataCons_maybe, isEnumerationTyCon, isNewTyCon - , unwrapNewTyCon_maybe, tyConDataCons ) +import TyCon ( tyConDataCons_maybe, isAlgTyCon, isEnumerationTyCon + , isNewTyCon, unwrapNewTyCon_maybe, tyConDataCons ) import DataCon ( DataCon, dataConTagZ, dataConTyCon, dataConWorkId ) import CoreUtils ( cheapEqExpr, exprIsHNF ) import CoreUnfold ( exprIsConApp_maybe ) @@ -1449,6 +1449,8 @@ caseRules dflags (App (App (Var f) type_arg) v) -- See Note [caseRules for dataToTag] caseRules _ (App (App (Var f) (Type ty)) v) -- dataToTag x | Just DataToTagOp <- isPrimOpId_maybe f + , Just (tc, _) <- tcSplitTyConApp_maybe ty + , isAlgTyCon tc = Just (v, tx_con_dtt ty , \v -> App (App (Var f) (Type ty)) (Var v)) @@ -1549,4 +1551,10 @@ into Note the need for some wildcard binders in the 'cons' case. + +For the time, we only apply this transformation when the type of `x` is a type +headed by a normal tycon. In particular, we do not apply this in the case of a +data family tycon, since that would require carefully applying coercion(s) +between the data family and the data family instance's representation type, +which caseRules isn't currently engineered to handle (#14680). -} diff --git a/testsuite/tests/indexed-types/should_compile/T14680.hs b/testsuite/tests/indexed-types/should_compile/T14680.hs new file mode 100644 index 0000000..9694c0a --- /dev/null +++ b/testsuite/tests/indexed-types/should_compile/T14680.hs @@ -0,0 +1,19 @@ +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE TypeFamilies #-} +{-# OPTIONS_GHC -O1 #-} +module T14680 where + +import GHC.Base (getTag) +import GHC.Exts (Int(..), tagToEnum#) + +data family TyFamilyEnum +data instance TyFamilyEnum = TyFamilyEnum1 | TyFamilyEnum2 | TyFamilyEnum3 + +suc :: TyFamilyEnum -> TyFamilyEnum +suc a_aaf8 + = case getTag a_aaf8 of + a_aaf9 + -> if 2 == I# a_aaf9 + then error "succ{TyFamilyEnum}: tried to take `succ' of last tag in enumeration" + else case I# a_aaf9 + 1 of + I# i_aafa -> tagToEnum# i_aafa :: TyFamilyEnum diff --git a/testsuite/tests/indexed-types/should_compile/all.T b/testsuite/tests/indexed-types/should_compile/all.T index 6407324..d470a9b 100644 --- a/testsuite/tests/indexed-types/should_compile/all.T +++ b/testsuite/tests/indexed-types/should_compile/all.T @@ -271,3 +271,4 @@ test('T12938', normal, compile, ['']) test('T14131', normal, compile, ['']) test('T14162', normal, compile, ['']) test('T14237', normal, compile, ['']) +test('T14680', normal, compile, ['']) From git at git.haskell.org Sun Feb 4 02:11:03 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Feb 2018 02:11:03 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: ghc-prim: Emulate C11 atomics when not available (7a3a7ee) Message-ID: <20180204021103.7BD013A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/7a3a7ee938b05a297e4b624cae86e4f0caefb88a/ghc >--------------------------------------------------------------- commit 7a3a7ee938b05a297e4b624cae86e4f0caefb88a Author: Ben Gamari Date: Sat Feb 3 11:37:01 2018 -0500 ghc-prim: Emulate C11 atomics when not available GCC's __sync primitives apparently "usually" imply a full barrier, meaning they can be used to emulate the more precise C11 atomics albeit with a loss of efficiency. This restores compatibility with GCC 4.4. This partially reverts commit 59de290928e6903337f31c1f8107ac8a98ea145d. Test Plan: Validate on Centos Reviewers: hvr, simonmar, trommler Subscribers: rwbarton, thomie, erikd, carter GHC Trac Issues: #14244 Differential Revision: https://phabricator.haskell.org/D4364 (cherry picked from commit 217e4170bdce3df28a667803ce5e619553bfecdd) >--------------------------------------------------------------- 7a3a7ee938b05a297e4b624cae86e4f0caefb88a aclocal.m4 | 25 +++++++++++++++++++++++-- configure.ac | 5 +++++ libraries/ghc-prim/cbits/atomic.c | 36 ++++++++++++++++++++++++++++++++++++ mk/config.mk.in | 1 + mk/warnings.mk | 4 +++- rts/ghc.mk | 2 ++ 6 files changed, 70 insertions(+), 3 deletions(-) diff --git a/aclocal.m4 b/aclocal.m4 index 5dc618d..99ff1bf 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -1237,15 +1237,18 @@ if test -z "$CC" then AC_MSG_ERROR([gcc is required]) fi +GccLT46=NO AC_CACHE_CHECK([version of gcc], [fp_cv_gcc_version], [ # Be sure only to look at the first occurrence of the "version " string; # Some Apple compilers emit multiple messages containing this string. fp_cv_gcc_version="`$CC -v 2>&1 | sed -n -e '1,/version /s/.*version [[^0-9]]*\([[0-9.]]*\).*/\1/p'`" - FP_COMPARE_VERSIONS([$fp_cv_gcc_version], [-lt], [4.7], - [AC_MSG_ERROR([Need at least gcc version 4.7])]) + FP_COMPARE_VERSIONS([$fp_cv_gcc_version], [-lt], [4.4], + [AC_MSG_ERROR([Need at least gcc version 4.4 (4.7+ recommended)])]) + FP_COMPARE_VERSIONS([$fp_cv_gcc_version], [-lt], [4.6], GccLT46=YES) ]) AC_SUBST([GccVersion], [$fp_cv_gcc_version]) +AC_SUBST(GccLT46) ])# FP_GCC_VERSION dnl Check to see if the C compiler is clang or llvm-gcc @@ -1278,6 +1281,24 @@ AC_SUBST(GccIsClang) rm -f conftest.txt ]) +# FP_GCC_SUPPORTS__ATOMICS +# ------------------------ +# Does gcc support the __atomic_* family of builtins? +AC_DEFUN([FP_GCC_SUPPORTS__ATOMICS], +[ + AC_REQUIRE([AC_PROG_CC]) + AC_MSG_CHECKING([whether GCC supports __atomic_ builtins]) + echo 'int test(int *x) { int y; __atomic_load(&x, &y, __ATOMIC_SEQ_CST); return x; }' > conftest.c + if $CC -c conftest.c > /dev/null 2>&1; then + CONF_GCC_SUPPORTS__ATOMICS=YES + AC_MSG_RESULT([yes]) + else + CONF_GCC_SUPPORTS__ATOMICS=NO + AC_MSG_RESULT([no]) + fi + rm -f conftest.c conftest.o +]) + # FP_GCC_SUPPORTS_NO_PIE # ---------------------- # Does gcc support the -no-pie option? If so we should pass it to gcc when diff --git a/configure.ac b/configure.ac index a2c0a3c..ec96d2c 100644 --- a/configure.ac +++ b/configure.ac @@ -712,6 +712,11 @@ FP_GCC_VERSION dnl ** See whether gcc supports -no-pie FP_GCC_SUPPORTS_NO_PIE +dnl ** Used to determine how to compile ghc-prim's atomics.c, used by +dnl unregisterised, Sparc, and PPC backends. +FP_GCC_SUPPORTS__ATOMICS +AC_DEFINE([HAVE_C11_ATOMICS], [$CONF_GCC_SUPPORTS__ATOMICS], [Does GCC support __atomic primitives?]) + FP_GCC_EXTRA_FLAGS dnl ** look to see if we have a C compiler using an llvm back end. diff --git a/libraries/ghc-prim/cbits/atomic.c b/libraries/ghc-prim/cbits/atomic.c index b091d22..2ded465 100644 --- a/libraries/ghc-prim/cbits/atomic.c +++ b/libraries/ghc-prim/cbits/atomic.c @@ -264,33 +264,53 @@ hs_cmpxchg64(StgWord x, StgWord64 old, StgWord64 new) // __ATOMIC_SEQ_CST: Full barrier in both directions (hoisting and sinking // of code) and synchronizes with acquire loads and release stores in // all threads. +// +// When we lack C11 atomics support we emulate these using the old GCC __sync +// primitives which the GCC documentation claims "usually" implies a full +// barrier. extern StgWord hs_atomicread8(StgWord x); StgWord hs_atomicread8(StgWord x) { +#if HAVE_C11_ATOMICS return __atomic_load_n((StgWord8 *) x, __ATOMIC_SEQ_CST); +#else + return __sync_add_and_fetch((StgWord8 *) x, 0); +#endif } extern StgWord hs_atomicread16(StgWord x); StgWord hs_atomicread16(StgWord x) { +#if HAVE_C11_ATOMICS return __atomic_load_n((StgWord16 *) x, __ATOMIC_SEQ_CST); +#else + return __sync_add_and_fetch((StgWord16 *) x, 0); +#endif } extern StgWord hs_atomicread32(StgWord x); StgWord hs_atomicread32(StgWord x) { +#if HAVE_C11_ATOMICS return __atomic_load_n((StgWord32 *) x, __ATOMIC_SEQ_CST); +#else + return __sync_add_and_fetch((StgWord32 *) x, 0); +#endif } extern StgWord64 hs_atomicread64(StgWord x); StgWord64 hs_atomicread64(StgWord x) { +#if HAVE_C11_ATOMICS return __atomic_load_n((StgWord64 *) x, __ATOMIC_SEQ_CST); +#else + return __sync_add_and_fetch((StgWord64 *) x, 0); +#endif } // AtomicWriteByteArrayOp_Int @@ -301,26 +321,42 @@ extern void hs_atomicwrite8(StgWord x, StgWord val); void hs_atomicwrite8(StgWord x, StgWord val) { +#if HAVE_C11_ATOMICS __atomic_store_n((StgWord8 *) x, (StgWord8) val, __ATOMIC_SEQ_CST); +#else + while (!__sync_bool_compare_and_swap((StgWord8 *) x, *(StgWord8 *) x, (StgWord8) val)); +#endif } extern void hs_atomicwrite16(StgWord x, StgWord val); void hs_atomicwrite16(StgWord x, StgWord val) { +#if HAVE_C11_ATOMICS __atomic_store_n((StgWord16 *) x, (StgWord16) val, __ATOMIC_SEQ_CST); +#else + while (!__sync_bool_compare_and_swap((StgWord16 *) x, *(StgWord16 *) x, (StgWord16) val)); +#endif } extern void hs_atomicwrite32(StgWord x, StgWord val); void hs_atomicwrite32(StgWord x, StgWord val) { +#if HAVE_C11_ATOMICS __atomic_store_n((StgWord32 *) x, (StgWord32) val, __ATOMIC_SEQ_CST); +#else + while (!__sync_bool_compare_and_swap((StgWord32 *) x, *(StgWord32 *) x, (StgWord32) val)); +#endif } extern void hs_atomicwrite64(StgWord x, StgWord64 val); void hs_atomicwrite64(StgWord x, StgWord64 val) { +#if HAVE_C11_ATOMICS __atomic_store_n((StgWord64 *) x, (StgWord64) val, __ATOMIC_SEQ_CST); +#else + while (!__sync_bool_compare_and_swap((StgWord64 *) x, *(StgWord64 *) x, (StgWord64) val)); +#endif } diff --git a/mk/config.mk.in b/mk/config.mk.in index b046abe..86c626d 100644 --- a/mk/config.mk.in +++ b/mk/config.mk.in @@ -522,6 +522,7 @@ GccVersion = @GccVersion@ # TargetPlatformFull retains the string passed to configure so we have it in # the necessary format to pass to libffi's configure. TargetPlatformFull = @TargetPlatformFull@ +GccLT46 = @GccLT46@ GccIsClang = @GccIsClang@ CC = @CC@ diff --git a/mk/warnings.mk b/mk/warnings.mk index 69990a7..297fabe 100644 --- a/mk/warnings.mk +++ b/mk/warnings.mk @@ -20,11 +20,13 @@ GhcStage2HcOpts += -Wcpp-undef ifneq "$(GccIsClang)" "YES" # Debian doesn't turn -Werror=unused-but-set-variable on by default, so -# we turn it on explicitly for consistency with other users. +# we turn it on explicitly for consistency with other users +ifeq "$(GccLT46)" "NO" # Never set the flag on Windows as the host gcc may be too old. ifneq "$(HostOS_CPP)" "mingw32" SRC_CC_WARNING_OPTS += -Werror=unused-but-set-variable endif +endif # Suppress the warning about __sync_fetch_and_nand (#9678). libraries/ghc-prim/cbits/atomic_CC_OPTS += -Wno-sync-nand diff --git a/rts/ghc.mk b/rts/ghc.mk index 690a883..761cc43 100644 --- a/rts/ghc.mk +++ b/rts/ghc.mk @@ -311,7 +311,9 @@ WARNING_OPTS += -Wpointer-arith WARNING_OPTS += -Wmissing-noreturn WARNING_OPTS += -Wnested-externs WARNING_OPTS += -Wredundant-decls +ifeq "$(GccLT46)" "NO" WARNING_OPTS += -Wundef +endif # These ones are hard to avoid: #WARNING_OPTS += -Wconversion From git at git.haskell.org Sun Feb 4 02:11:09 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Feb 2018 02:11:09 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: integer-gmp: Simplify gmp/configure invocation (89830a3) Message-ID: <20180204021109.80DA83A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/89830a3423aca7492155dae5a800e1478967e254/ghc >--------------------------------------------------------------- commit 89830a3423aca7492155dae5a800e1478967e254 Author: Ben Gamari Date: Fri Feb 2 13:58:14 2018 -0500 integer-gmp: Simplify gmp/configure invocation There weas lots of historical cruft to be found here. The `export SHELLOPTS` breaks on NixOS due to bash syntax in the gcc wrapper script. Reviewers: hvr Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4347 (cherry picked from commit 3441b1455bf9f2e7cc9e064e3edae3607c70a1c0) >--------------------------------------------------------------- 89830a3423aca7492155dae5a800e1478967e254 libraries/integer-gmp/gmp/ghc.mk | 5 +---- 1 file changed, 1 insertion(+), 4 deletions(-) diff --git a/libraries/integer-gmp/gmp/ghc.mk b/libraries/integer-gmp/gmp/ghc.mk index 8a74f76..794942c 100644 --- a/libraries/integer-gmp/gmp/ghc.mk +++ b/libraries/integer-gmp/gmp/ghc.mk @@ -130,10 +130,7 @@ libraries/integer-gmp/gmp/libgmp.a libraries/integer-gmp/gmp/gmp.h: # Note: We must pass `TARGETPLATFORM` to the `--host` argument of GMP's # `./configure`, not `HOSTPLATFORM`: the 'host' on which GMP will # run is the 'target' platform of the compiler we're building. - cd libraries/integer-gmp/gmp; (set -o igncr 2>/dev/null) && set -o igncr; export SHELLOPTS; \ - PATH=`pwd`:$$PATH; \ - export PATH; \ - cd gmpbuild && \ + cd libraries/integer-gmp/gmp/gmpbuild; \ CC=$(CCX) NM=$(NM) AR=$(AR_STAGE1) ./configure \ --enable-shared=no \ --host=$(TARGETPLATFORM) --build=$(BUILDPLATFORM) From git at git.haskell.org Sun Feb 4 02:11:12 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Feb 2018 02:11:12 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: Bump stm submodule to 2.4.5.0 (5acecda) Message-ID: <20180204021112.54DD63A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/5acecda09076663aaf64d0b33f228170f97c841d/ghc >--------------------------------------------------------------- commit 5acecda09076663aaf64d0b33f228170f97c841d Author: Ben Gamari Date: Sat Feb 3 16:23:05 2018 -0500 Bump stm submodule to 2.4.5.0 >--------------------------------------------------------------- 5acecda09076663aaf64d0b33f228170f97c841d libraries/stm | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/stm b/libraries/stm index 8194700..5ea70d4 160000 --- a/libraries/stm +++ b/libraries/stm @@ -1 +1 @@ -Subproject commit 819470093eccb81d058408076df8903e781f551c +Subproject commit 5ea70d4e15d461888866796a164bf9c177a1e8b8 From git at git.haskell.org Sun Feb 4 02:11:15 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Feb 2018 02:11:15 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: cmm: Revert more aggressive CBE due to #14226 (f0cae1f) Message-ID: <20180204021115.26DAA3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/f0cae1f24ecc34ab06e87c6c7423d45917ba593e/ghc >--------------------------------------------------------------- commit f0cae1f24ecc34ab06e87c6c7423d45917ba593e Author: Ben Gamari Date: Sat Feb 3 19:49:21 2018 -0500 cmm: Revert more aggressive CBE due to #14226 Trac #14226 noted that the C-- CBE pass frequently fails to common up semantically identical blocks due to the differences in local register naming. These patches fixed this by making the pass consider equality up to alpha-renaming. However, the new logic failed to consider the possibility that local register naming *may* matter across multiple blocks. This lead to the regression #14754. I'll need to do a bit of thinking on a proper solution to this but in the meantime I'm reverting all four patches. This reverts commit a27056f9823f8bbe2302f1924b3ab38fd6752e37. This reverts commit 6f990c54f922beae80362fe62426beededc21290. This reverts commit 9aa73892e10e90a1799b9277da593e816a827364. This reverts commit 7920a7d9c53083b234e060a3e72f00b601a46808. (cherry picked from commit 50adbd7c5fe5894d3e6e2a58b353ed07e5f8949d) >--------------------------------------------------------------- f0cae1f24ecc34ab06e87c6c7423d45917ba593e compiler/cmm/CmmCommonBlockElim.hs | 320 ++++++++++--------------------------- compiler/cmm/CmmPipeline.hs | 2 +- compiler/cmm/Hoopl/Block.hs | 1 - 3 files changed, 86 insertions(+), 237 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc f0cae1f24ecc34ab06e87c6c7423d45917ba593e From git at git.haskell.org Sun Feb 4 02:11:18 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Feb 2018 02:11:18 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: testsuite: Add testcase for #14754 (054abe3) Message-ID: <20180204021118.808633A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/054abe3de4a44b112f1f8155fa6be9fd19b03e1d/ghc >--------------------------------------------------------------- commit 054abe3de4a44b112f1f8155fa6be9fd19b03e1d Author: Ben Gamari Date: Sat Feb 3 19:19:08 2018 -0500 testsuite: Add testcase for #14754 (cherry picked from commit 606edbfba14b025ce85a02e5ed7c03e8a097d692) >--------------------------------------------------------------- 054abe3de4a44b112f1f8155fa6be9fd19b03e1d testsuite/tests/codeGen/should_run/T14754.hs | 15 +++++++++++++++ testsuite/tests/codeGen/should_run/T14754.stderr | 2 ++ .../bkprun02.stdout => codeGen/should_run/T14754.stdout} | 0 testsuite/tests/codeGen/should_run/all.T | 1 + 4 files changed, 18 insertions(+) diff --git a/testsuite/tests/codeGen/should_run/T14754.hs b/testsuite/tests/codeGen/should_run/T14754.hs new file mode 100644 index 0000000..181659d --- /dev/null +++ b/testsuite/tests/codeGen/should_run/T14754.hs @@ -0,0 +1,15 @@ +module Main where + +import Debug.Trace + +main :: IO () +main = print (alg 3 1) + +alg :: Word -> Word -> Word +alg a b + | traceShow (a, b) False = undefined + | c < b = alg b c + | c > b = alg c b + | otherwise = c + where + c = a - b diff --git a/testsuite/tests/codeGen/should_run/T14754.stderr b/testsuite/tests/codeGen/should_run/T14754.stderr new file mode 100644 index 0000000..42c78ed --- /dev/null +++ b/testsuite/tests/codeGen/should_run/T14754.stderr @@ -0,0 +1,2 @@ +(3,1) +(2,1) diff --git a/testsuite/tests/backpack/should_run/bkprun02.stdout b/testsuite/tests/codeGen/should_run/T14754.stdout similarity index 100% copy from testsuite/tests/backpack/should_run/bkprun02.stdout copy to testsuite/tests/codeGen/should_run/T14754.stdout diff --git a/testsuite/tests/codeGen/should_run/all.T b/testsuite/tests/codeGen/should_run/all.T index 145365e..9403c4b 100644 --- a/testsuite/tests/codeGen/should_run/all.T +++ b/testsuite/tests/codeGen/should_run/all.T @@ -166,3 +166,4 @@ test('T13825-unit', compile_and_run, ['-package ghc']) test('T14619', normal, compile_and_run, ['']) +test('T14754', normal, compile_and_run, ['']) From git at git.haskell.org Sun Feb 4 19:09:33 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Feb 2018 19:09:33 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: Bump transformers submodule to 0.5.5.0 (111737c) Message-ID: <20180204190933.1D7073A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/111737cd218751f06ea58d3cf2c7c144265b5dfc/ghc >--------------------------------------------------------------- commit 111737cd218751f06ea58d3cf2c7c144265b5dfc Author: Ben Gamari Date: Sun Jan 21 20:09:20 2018 -0500 Bump transformers submodule to 0.5.5.0 (cherry picked from commit 24e56ebd010846683b236b6ef3678c2217640120) >--------------------------------------------------------------- 111737cd218751f06ea58d3cf2c7c144265b5dfc libraries/transformers | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/transformers b/libraries/transformers index 36311d3..33b3c8a 160000 --- a/libraries/transformers +++ b/libraries/transformers @@ -1 +1 @@ -Subproject commit 36311d39bc545261dab85d4a27af562db1868ed6 +Subproject commit 33b3c8a71778ae37040088dfe022c648373777a8 From git at git.haskell.org Mon Feb 5 14:46:19 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 5 Feb 2018 14:46:19 +0000 (UTC) Subject: [commit: ghc] master: Improve unboxed sum documentation (d987f71) Message-ID: <20180205144619.5D6E53A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d987f71aa3200ce0c94bc57c43b4fcc92eaccf76/ghc >--------------------------------------------------------------- commit d987f71aa3200ce0c94bc57c43b4fcc92eaccf76 Author: David Feuer Date: Mon Feb 5 09:45:30 2018 -0500 Improve unboxed sum documentation * Clarify the representation of sums without fields. * Try to improve language, clarity, and examples. Fixes #14752 Reviewers: osa1, bgamari Reviewed By: osa1 Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14752 Differential Revision: https://phabricator.haskell.org/D4379 >--------------------------------------------------------------- d987f71aa3200ce0c94bc57c43b4fcc92eaccf76 docs/users_guide/glasgow_exts.rst | 67 +++++++++++++++++++++++---------------- 1 file changed, 39 insertions(+), 28 deletions(-) diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index 190c611..d213a5c 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -284,21 +284,21 @@ for an unboxed sum type with N alternatives is :: (# t_1 | t_2 | ... | t_N #) -where `t_1` ... `t_N` are types (which can be unlifted, including unboxed tuple -and sums). +where ``t_1`` ... ``t_N`` are types (which can be unlifted, including unboxed +tuples and sums). Unboxed tuples can be used for multi-arity alternatives. For example: :: (# (# Int, String #) | Bool #) -Term level syntax is similar. Leading and preceding bars (`|`) indicate which -alternative it is. Here is two terms of the type shown above: :: +The term level syntax is similar. Leading and preceding bars (`|`) indicate which +alternative it is. Here are two terms of the type shown above: :: (# (# 1, "foo" #) | #) -- first alternative (# | True #) -- second alternative -Pattern syntax reflects the term syntax: :: +The pattern syntax reflects the term syntax: :: case x of (# (# i, str #) | #) -> ... @@ -307,45 +307,56 @@ Pattern syntax reflects the term syntax: :: Unboxed sums are "unboxed" in the sense that, instead of allocating sums in the heap and representing values as pointers, unboxed sums are represented as their components, just like unboxed tuples. These "components" depend on alternatives -of a sum type. Code generator tries to generate as compact layout as possible. -In the best case, size of an unboxed sum is size of its biggest alternative + -one word (for tag). The algorithm for generating memory layout for a sum type -works like this: +of a sum type. Like unboxed tuples, unboxed sums are lazy in their lifted +components. + +The code generator tries to generate as compact layout as possible for each +unboxed sum. In the best case, size of an unboxed sum is size of its biggest +alternative plus one word (for a tag). The algorithm for generating the memory +layout for a sum type works like this: - All types are classified as one of these classes: 32bit word, 64bit word, 32bit float, 64bit float, pointer. - For each alternative of the sum type, a layout that consists of these fields - is generated. For example, if an alternative has `Int`, `Float#` and `String` - fields, the layout will have an 32bit word, 32bit float and pointer fields. + is generated. For example, if an alternative has ``Int``, ``Float#`` and + ``String`` fields, the layout will have an 32bit word, 32bit float and + pointer fields. - Layout fields are then overlapped so that the final layout will be as compact - as possible. E.g. say two alternatives have these fields: :: + as possible. For example, suppose we have the unboxed sum: :: - Word32, String, Float# - Float#, Float#, Maybe Int + (# (# Word32#, String, Float# #) + | (# Float#, Float#, Maybe Int #) #) - Final layout will be something like :: + The final layout will be something like :: Int32, Float32, Float32, Word32, Pointer - First `Int32` is for the tag. It has two `Float32` fields because floating - point types can't overlap with other types, because of limitations of the code - generator that we're hoping to overcome in the future, and second alternative - needs two `Float32` fields. `Word32` field is for the `Word32` in the first - alternative. `Pointer` field is shared between `String` and `Maybe Int` values - of the alternatives. - - In the case of enumeration types (like `Bool`), the unboxed sum layout only - has an `Int32` field (i.e. the whole thing is represented by an integer). + The first ``Int32`` is for the tag. There are two ``Float32`` fields because + floating point types can't overlap with other types, because of limitations of + the code generator that we're hoping to overcome in the future. The second + alternative needs two ``Float32`` fields: The ``Word32`` field is for the + ``Word32#`` in the first alternative. The ``Pointer`` field is shared between + ``String`` and ``Maybe Int`` values of the alternatives. -In the example above, a value of this type is thus represented as 5 values. As -an another example, this is the layout for unboxed version of `Maybe a` type: :: + As another example, this is the layout for the unboxed version of ``Maybe a`` + type, ``(# (# #) | a #)``: :: Int32, Pointer -The `Pointer` field is not used when tag says that it's `Nothing`. Otherwise -`Pointer` points to the value in `Just`. + The ``Pointer`` field is not used when tag says that it's ``Nothing``. + Otherwise ``Pointer`` points to the value in ``Just``. As mentioned + above, this type is lazy in its lifted field. Therefore, the type :: + + data Maybe' a = Maybe' (# (# #) | a #) + + is *precisely* isomorphic to the type ``Maybe a``, although its memory + representation is different. + + In the degenerate case where all the alternatives have zero width, such + as the ``Bool``-like ``(# (# #) | (# #) #)``, the unboxed sum layout only + has an ``Int32`` tag field (i.e., the whole thing is represented by an integer). .. _syntax-extns: From git at git.haskell.org Tue Feb 6 02:09:21 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 6 Feb 2018 02:09:21 +0000 (UTC) Subject: [commit: ghc] master: Bump Cabal submodule (326df5d) Message-ID: <20180206020921.4DCE63A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/326df5d137ec1a556d77248e16f55e41b7374b1e/ghc >--------------------------------------------------------------- commit 326df5d137ec1a556d77248e16f55e41b7374b1e Author: Ben Gamari Date: Mon Feb 5 20:27:10 2018 -0500 Bump Cabal submodule >--------------------------------------------------------------- 326df5d137ec1a556d77248e16f55e41b7374b1e libraries/Cabal | 2 +- testsuite/tests/driver/T4437.hs | 1 - 2 files changed, 1 insertion(+), 2 deletions(-) diff --git a/libraries/Cabal b/libraries/Cabal index d2cf3f1..578d3a5 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit d2cf3f13dad9f1172cf9371ea197d1204e9e17a2 +Subproject commit 578d3a50db818223017b8891df268d4200b8ffd3 diff --git a/testsuite/tests/driver/T4437.hs b/testsuite/tests/driver/T4437.hs index 14d9bf4..6a46e52 100644 --- a/testsuite/tests/driver/T4437.hs +++ b/testsuite/tests/driver/T4437.hs @@ -40,7 +40,6 @@ expectedGhcOnlyExtensions = ["RelaxedLayout", "AlternativeLayoutRule", "AlternativeLayoutRuleTransitional", "EmptyDataDeriving", - "BlockArguments", "NumericUnderscores"] expectedCabalOnlyExtensions :: [String] From git at git.haskell.org Tue Feb 6 15:54:37 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 6 Feb 2018 15:54:37 +0000 (UTC) Subject: [commit: ghc] wip/tdammers/T11735: Performance improvements based on Trac #11735 and #14683. (e6472a2) Message-ID: <20180206155437.987633A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tdammers/T11735 Link : http://ghc.haskell.org/trac/ghc/changeset/e6472a2787a3a1c7c465f142dc6d60da6a54b9d6/ghc >--------------------------------------------------------------- commit e6472a2787a3a1c7c465f142dc6d60da6a54b9d6 Author: Tobias Dammers Date: Tue Jan 30 17:04:47 2018 +0100 Performance improvements based on Trac #11735 and #14683. Summary: This includes: - Refactoring coercionKind / coercionKindRole - Caching role in NthCo constructor and mkNthCo - Discard reflexive casts during Simplify - Additional SCC's to hunt down performance bottlenecks in Coercion, CoreTidy, and Simplify Reviewers: goldfire, bgamari Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4385 >--------------------------------------------------------------- e6472a2787a3a1c7c465f142dc6d60da6a54b9d6 compiler/main/TidyPgm.hs | 61 +++++++++++++++++++++++++++++++++--------------- 1 file changed, 42 insertions(+), 19 deletions(-) diff --git a/compiler/main/TidyPgm.hs b/compiler/main/TidyPgm.hs index ce8ac53..c1bc57f 100644 --- a/compiler/main/TidyPgm.hs +++ b/compiler/main/TidyPgm.hs @@ -337,58 +337,80 @@ tidyProgram hsc_env (ModGuts { mg_module = mod = Err.withTiming (pure dflags) (text "CoreTidy"<+>brackets (ppr mod)) (const ()) $ - do { let { omit_prags = gopt Opt_OmitInterfacePragmas dflags - ; expose_all = gopt Opt_ExposeAllUnfoldings dflags - ; print_unqual = mkPrintUnqualified dflags rdr_env + do { let { omit_prags = + {-#SCC "omit_prags" #-} + gopt Opt_OmitInterfacePragmas dflags + ; expose_all = + {-#SCC "expose_all" #-} + gopt Opt_ExposeAllUnfoldings dflags + ; print_unqual = + {-#SCC "print_unqual" #-} + mkPrintUnqualified dflags rdr_env } - ; let { type_env = typeEnvFromEntities [] tcs fam_insts + ; let { type_env = {-#SCC "type_env" #-} + typeEnvFromEntities [] tcs fam_insts ; implicit_binds - = concatMap getClassImplicitBinds (typeEnvClasses type_env) ++ + = {-#SCC "implicit_binds" #-} + concatMap getClassImplicitBinds (typeEnvClasses type_env) ++ concatMap getTyConImplicitBinds (typeEnvTyCons type_env) } ; (unfold_env, tidy_occ_env) - <- chooseExternalIds hsc_env mod omit_prags expose_all + <- {-# SCC "chooseExternalIds" #-} + chooseExternalIds hsc_env mod omit_prags expose_all binds implicit_binds imp_rules (vectInfoVar vect_info) ; let { (trimmed_binds, trimmed_rules) - = findExternalRules omit_prags binds imp_rules unfold_env } + = {-#SCC "findExternalRules" #-} + findExternalRules omit_prags binds imp_rules unfold_env } ; (tidy_env, tidy_binds) - <- tidyTopBinds hsc_env mod unfold_env tidy_occ_env trimmed_binds + <- {-#SCC "tidyTopBinds" #-} + tidyTopBinds hsc_env mod unfold_env tidy_occ_env trimmed_binds - ; let { final_ids = [ id | id <- bindersOfBinds tidy_binds, + ; let { final_ids = {-#SCC "final_ids" #-} + [ id | id <- bindersOfBinds tidy_binds, isExternalName (idName id)] - ; type_env1 = extendTypeEnvWithIds type_env final_ids + ; type_env1 = {-#SCC "type_env1" #-} + extendTypeEnvWithIds type_env final_ids - ; tidy_cls_insts = map (tidyClsInstDFun (tidyVarOcc tidy_env)) cls_insts + ; tidy_cls_insts = {-#SCC "tidy_cls_insts" #-} + map (tidyClsInstDFun (tidyVarOcc tidy_env)) cls_insts -- A DFunId will have a binding in tidy_binds, and so will now be in -- tidy_type_env, replete with IdInfo. Its name will be unchanged since -- it was born, but we want Global, IdInfo-rich (or not) DFunId in the -- tidy_cls_insts. Similarly the Ids inside a PatSyn. - ; tidy_rules = tidyRules tidy_env trimmed_rules + ; tidy_rules = {-#SCC "tidy_rules" #-} + tidyRules tidy_env trimmed_rules -- You might worry that the tidy_env contains IdInfo-rich stuff -- and indeed it does, but if omit_prags is on, ext_rules is -- empty - ; tidy_vect_info = tidyVectInfo tidy_env vect_info + ; tidy_vect_info = {-#SCC "tidy_vect_info" #-} + tidyVectInfo tidy_env vect_info -- Tidy the Ids inside each PatSyn, very similarly to DFunIds -- and then override the PatSyns in the type_env with the new tidy ones -- This is really the only reason we keep mg_patsyns at all; otherwise -- they could just stay in type_env - ; tidy_patsyns = map (tidyPatSynIds (tidyVarOcc tidy_env)) patsyns - ; type_env2 = extendTypeEnvWithPatSyns tidy_patsyns type_env1 + ; tidy_patsyns = {-#SCC "tidy_patsyns" #-} + map (tidyPatSynIds (tidyVarOcc tidy_env)) patsyns + ; type_env2 = {-#SCC "type_env2" #-} + extendTypeEnvWithPatSyns tidy_patsyns type_env1 - ; tidy_type_env = tidyTypeEnv omit_prags type_env2 + ; tidy_type_env = {-#SCC "tidy_type_env" #-} + tidyTypeEnv omit_prags type_env2 } -- See Note [Grand plan for static forms] in StaticPtrTable. ; (spt_entries, tidy_binds') <- + {-#SCC "sptCreateStaticBinds" #-} sptCreateStaticBinds hsc_env mod tidy_binds - ; let { spt_init_code = sptModuleInitCode mod spt_entries + ; let { spt_init_code = {-#SCC "spt_init_code" #-} + sptModuleInitCode mod spt_entries ; add_spt_init_code = + {-#SCC "add_spt_init_code" #-} case hscTarget dflags of -- If we are compiling for the interpreter we will insert -- any necessary SPT entries dynamically @@ -411,7 +433,8 @@ tidyProgram hsc_env (ModGuts { mg_module = mod ; alg_tycons = filter isAlgTyCon (typeEnvTyCons type_env) } - ; endPassIO hsc_env print_unqual CoreTidy all_tidy_binds tidy_rules + ; {-#SCC "endPassIO" #-} + endPassIO hsc_env print_unqual CoreTidy all_tidy_binds tidy_rules -- If the endPass didn't print the rules, but ddump-rules is -- on, print now @@ -421,7 +444,7 @@ tidyProgram hsc_env (ModGuts { mg_module = mod (pprRulesForUser dflags tidy_rules) -- Print one-line size info - ; let cs = coreBindsStats tidy_binds + ; let cs = {-#SCC "coreBindStats" #-} coreBindsStats tidy_binds ; when (dopt Opt_D_dump_core_stats dflags) (putLogMsg dflags NoReason SevDump noSrcSpan (defaultDumpStyle dflags) From git at git.haskell.org Tue Feb 6 17:58:48 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 6 Feb 2018 17:58:48 +0000 (UTC) Subject: [commit: ghc] master: Compute the union of imp_finsts on the side (d2511e3) Message-ID: <20180206175848.071573A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d2511e3b61563ed3fc2c9aec2c90a4156373a24c/ghc >--------------------------------------------------------------- commit d2511e3b61563ed3fc2c9aec2c90a4156373a24c Author: Bartosz Nitka Date: Fri Feb 2 06:55:19 2018 -0800 Compute the union of imp_finsts on the side I've explained most of the rationale in a new Note. I'd happily add a test for this, but the difference is only visible in run time, allocations remain more or less the same. FWIW running `generateModules` from #14693 with DEPTH=16, WIDTH=30 finishes in `23s` before, and `11s` after. Test Plan: ./validate Reviewers: simonpj, simonmar, bgamari Reviewed By: simonpj Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14693 Differential Revision: https://phabricator.haskell.org/D4369 >--------------------------------------------------------------- d2511e3b61563ed3fc2c9aec2c90a4156373a24c compiler/rename/RnNames.hs | 67 +++++++++++++++++++++++++++++++++++++++++----- 1 file changed, 61 insertions(+), 6 deletions(-) diff --git a/compiler/rename/RnNames.hs b/compiler/rename/RnNames.hs index ae3f75b..769b34e 100644 --- a/compiler/rename/RnNames.hs +++ b/compiler/rename/RnNames.hs @@ -177,16 +177,71 @@ rnImports imports = do return (decls, rdr_env, imp_avails, hpc_usage) where + -- See Note [Combining ImportAvails] combine :: [(LImportDecl GhcRn, GlobalRdrEnv, ImportAvails, AnyHpcUsage)] -> ([LImportDecl GhcRn], GlobalRdrEnv, ImportAvails, AnyHpcUsage) - combine = foldr plus ([], emptyGlobalRdrEnv, emptyImportAvails, False) - - plus (decl, gbl_env1, imp_avails1,hpc_usage1) - (decls, gbl_env2, imp_avails2,hpc_usage2) + combine ss = + let (decls, rdr_env, imp_avails, hpc_usage, finsts) = foldr + plus + ([], emptyGlobalRdrEnv, emptyImportAvails, False, emptyModuleSet) + ss + in (decls, rdr_env, imp_avails { imp_finsts = moduleSetElts finsts }, + hpc_usage) + + plus (decl, gbl_env1, imp_avails1, hpc_usage1) + (decls, gbl_env2, imp_avails2, hpc_usage2, finsts_set) = ( decl:decls, gbl_env1 `plusGlobalRdrEnv` gbl_env2, - imp_avails1 `plusImportAvails` imp_avails2, - hpc_usage1 || hpc_usage2 ) + imp_avails1' `plusImportAvails` imp_avails2, + hpc_usage1 || hpc_usage2, + extendModuleSetList finsts_set new_finsts ) + where + imp_avails1' = imp_avails1 { imp_finsts = [] } + new_finsts = imp_finsts imp_avails1 + +{- +Note [Combine ImportAvails] +~~~~~~~~~~~~~~~~~~~~~~~~~~~ +imp_finsts in ImportAvails is a list of family instance modules +transitively depended on by an import. imp_finsts for a currently +compiled module is a union of all the imp_finsts of imports. +Computing the union of two lists of size N is O(N^2) and if we +do it to M imports we end up with O(M*N^2). That can get very +expensive for bigger module hierarchies. + +Union can be optimized to O(N log N) if we use a Set. +imp_finsts is converted back and forth between dep_finsts, so +changing a type of imp_finsts means either paying for the conversions +or changing the type of dep_finsts as well. + +I've measured that the conversions would cost 20% of allocations on my +test case, so that can be ruled out. + +Changing the type of dep_finsts forces checkFamInsts to +get the module lists in non-deterministic order. If we wanted to restore +the deterministic order, we'd have to sort there, which is an additional +cost. As far as I can tell, using a non-deterministic order is fine there, +but that's a brittle nonlocal property which I'd like to avoid. + +Additionally, dep_finsts is read from an interface file, so its "natural" +type is a list. Which makes it a natural type for imp_finsts. + +Since rnImports.combine is really the only place that would benefit from +it being a Set, it makes sense to optimize the hot loop in rnImports.combine +without changing the representation. + +So here's what we do: instead of naively merging ImportAvails with +plusImportAvails in a loop, we make plusImportAvails merge empty imp_finsts +and compute the union on the side using Sets. When we're done, we can +convert it back to a list. One nice side effect of this approach is that +if there's a lot of overlap in the imp_finsts of imports, the +Set doesn't really need to grow and we don't need to allocate. + +Running generateModules from Trac #14693 with DEPTH=16, WIDTH=30 finishes in +23s before, and 11s after. +-} + + -- | Given a located import declaration @decl@ from @this_mod@, -- calculate the following pieces of information: From git at git.haskell.org Tue Feb 6 19:22:01 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 6 Feb 2018 19:22:01 +0000 (UTC) Subject: [commit: ghc] master: rts: Use BITS_IN macro in bitmap calculations (3cd1305) Message-ID: <20180206192201.9355C3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3cd1305ffcc4a5e3269aeb2e0694dddb7ca480d0/ghc >--------------------------------------------------------------- commit 3cd1305ffcc4a5e3269aeb2e0694dddb7ca480d0 Author: Ömer Sinan Ağacan Date: Tue Feb 6 13:29:50 2018 -0500 rts: Use BITS_IN macro in bitmap calculations Reviewers: bgamari, erikd, simonmar Reviewed By: bgamari Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4386 >--------------------------------------------------------------- 3cd1305ffcc4a5e3269aeb2e0694dddb7ca480d0 rts/sm/Compact.h | 12 ++++++------ rts/sm/GC.c | 4 ++-- 2 files changed, 8 insertions(+), 8 deletions(-) diff --git a/rts/sm/Compact.h b/rts/sm/Compact.h index 6dcb50b..63abfc7 100644 --- a/rts/sm/Compact.h +++ b/rts/sm/Compact.h @@ -20,8 +20,8 @@ mark(StgPtr p, bdescr *bd) { uint32_t offset_within_block = p - bd->start; // in words StgPtr bitmap_word = (StgPtr)bd->u.bitmap + - (offset_within_block / (sizeof(W_)*BITS_PER_BYTE)); - StgWord bit_mask = (StgWord)1 << (offset_within_block & (sizeof(W_)*BITS_PER_BYTE - 1)); + (offset_within_block / BITS_IN(W_)); + StgWord bit_mask = (StgWord)1 << (offset_within_block & (BITS_IN(W_) - 1)); *bitmap_word |= bit_mask; } @@ -30,8 +30,8 @@ unmark(StgPtr p, bdescr *bd) { uint32_t offset_within_block = p - bd->start; // in words StgPtr bitmap_word = (StgPtr)bd->u.bitmap + - (offset_within_block / (sizeof(W_)*BITS_PER_BYTE)); - StgWord bit_mask = (StgWord)1 << (offset_within_block & (sizeof(W_)*BITS_PER_BYTE - 1)); + (offset_within_block / BITS_IN(W_)); + StgWord bit_mask = (StgWord)1 << (offset_within_block & (BITS_IN(W_) - 1)); *bitmap_word &= ~bit_mask; } @@ -40,8 +40,8 @@ is_marked(StgPtr p, bdescr *bd) { uint32_t offset_within_block = p - bd->start; // in words StgPtr bitmap_word = (StgPtr)bd->u.bitmap + - (offset_within_block / (sizeof(W_)*BITS_PER_BYTE)); - StgWord bit_mask = (StgWord)1 << (offset_within_block & (sizeof(W_)*BITS_PER_BYTE - 1)); + (offset_within_block / BITS_IN(W_)); + StgWord bit_mask = (StgWord)1 << (offset_within_block & (BITS_IN(W_)- 1)); return (*bitmap_word & bit_mask); } diff --git a/rts/sm/GC.c b/rts/sm/GC.c index 197b466..54797ba 100644 --- a/rts/sm/GC.c +++ b/rts/sm/GC.c @@ -1372,7 +1372,7 @@ prepare_collected_gen (generation *gen) bdescr *bitmap_bdescr; StgWord *bitmap; - bitmap_size = gen->n_old_blocks * BLOCK_SIZE / (sizeof(W_)*BITS_PER_BYTE); + bitmap_size = gen->n_old_blocks * BLOCK_SIZE / BITS_IN(W_); if (bitmap_size > 0) { bitmap_bdescr = allocGroup((StgWord)BLOCK_ROUND_UP(bitmap_size) @@ -1390,7 +1390,7 @@ prepare_collected_gen (generation *gen) // block descriptor. for (bd=gen->old_blocks; bd != NULL; bd = bd->link) { bd->u.bitmap = bitmap; - bitmap += BLOCK_SIZE_W / (sizeof(W_)*BITS_PER_BYTE); + bitmap += BLOCK_SIZE_W / BITS_IN(W_); // Also at this point we set the BF_MARKED flag // for this block. The invariant is that From git at git.haskell.org Tue Feb 6 19:22:04 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 6 Feb 2018 19:22:04 +0000 (UTC) Subject: [commit: ghc] master: Improve X86CodeGen's pprASCII. (2987b04) Message-ID: <20180206192204.7D9903A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2987b041a3811b25bcee402ce6fdab80827dc90e/ghc >--------------------------------------------------------------- commit 2987b041a3811b25bcee402ce6fdab80827dc90e Author: HE, Tao Date: Tue Feb 6 13:29:40 2018 -0500 Improve X86CodeGen's pprASCII. The original implementation generates a list of SDoc then concatenates them using `hcat`. For memory optimization, we can transform the given literal string into escaped string the construct SDoc directly. This optimization will decreate the memory allocation when there's big literal strings in haskell code, see Trac #14741. Signed-off-by: HE, Tao Reviewers: bgamari, mpickering, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, thomie, carter GHC Trac Issues: #14741 Differential Revision: https://phabricator.haskell.org/D4384 >--------------------------------------------------------------- 2987b041a3811b25bcee402ce6fdab80827dc90e compiler/nativeGen/X86/Ppr.hs | 47 +++++++++++++++++++++++++++++++------------ 1 file changed, 34 insertions(+), 13 deletions(-) diff --git a/compiler/nativeGen/X86/Ppr.hs b/compiler/nativeGen/X86/Ppr.hs index f5011b2..a295a47 100644 --- a/compiler/nativeGen/X86/Ppr.hs +++ b/compiler/nativeGen/X86/Ppr.hs @@ -175,23 +175,44 @@ pprLabel lbl = pprGloblDecl lbl $$ pprTypeAndSizeDecl lbl $$ (ppr lbl <> char ':') +{- +Note [Pretty print ASCII when AsmCodeGen] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Previously, when generating assembly code, we created SDoc with +`(ptext . sLit)` for every bytes in literal bytestring, then +combine them using `hcat`. + +When handling literal bytestrings with millions of bytes, +millions of SDoc would be created and to combine, leading to +high memory usage. + +Now we escape the given bytestring to string directly and construct +SDoc only once. This improvement could dramatically decrease the +memory allocation from 4.7GB to 1.3GB when embedding a 3MB literal +string in source code. See Trac #14741 for profiling results. +-} pprASCII :: [Word8] -> SDoc pprASCII str - = hcat (map (do1 . fromIntegral) str) + -- Transform this given literal bytestring to escaped string and construct + -- the literal SDoc directly. + -- See Trac #14741 + -- and Note [Pretty print ASCII when AsmCodeGen] + = ptext $ sLit $ foldr (\w s -> (do1 . fromIntegral) w ++ s) "" str where - do1 :: Int -> SDoc - do1 w | '\t' <- chr w = ptext (sLit "\\t") - do1 w | '\n' <- chr w = ptext (sLit "\\n") - do1 w | '"' <- chr w = ptext (sLit "\\\"") - do1 w | '\\' <- chr w = ptext (sLit "\\\\") - do1 w | isPrint (chr w) = char (chr w) - do1 w | otherwise = char '\\' <> octal w - - octal :: Int -> SDoc - octal w = int ((w `div` 64) `mod` 8) - <> int ((w `div` 8) `mod` 8) - <> int (w `mod` 8) + do1 :: Int -> String + do1 w | '\t' <- chr w = "\\t" + | '\n' <- chr w = "\\n" + | '"' <- chr w = "\\\"" + | '\\' <- chr w = "\\\\" + | isPrint (chr w) = [chr w] + | otherwise = '\\' : octal w + + octal :: Int -> String + octal w = [ chr (ord '0' + (w `div` 64) `mod` 8) + , chr (ord '0' + (w `div` 8) `mod` 8) + , chr (ord '0' + w `mod` 8) + ] pprAlign :: Int -> SDoc pprAlign bytes From git at git.haskell.org Tue Feb 6 19:22:10 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 6 Feb 2018 19:22:10 +0000 (UTC) Subject: [commit: ghc] master: rts: Add format attribute to barf (4d1c3b7) Message-ID: <20180206192210.2F4BC3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4d1c3b72ec27c8e51fb40809bba3ce35246a2966/ghc >--------------------------------------------------------------- commit 4d1c3b72ec27c8e51fb40809bba3ce35246a2966 Author: Ben Gamari Date: Tue Feb 6 13:27:35 2018 -0500 rts: Add format attribute to barf Test Plan: Validate Reviewers: erikd, simonmar Reviewed By: simonmar Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4374 >--------------------------------------------------------------- 4d1c3b72ec27c8e51fb40809bba3ce35246a2966 includes/rts/Messages.h | 3 ++- rts/Capability.c | 2 +- rts/Schedule.c | 2 +- rts/Threads.c | 2 +- 4 files changed, 5 insertions(+), 4 deletions(-) diff --git a/includes/rts/Messages.h b/includes/rts/Messages.h index 2a6a84b..206d40f 100644 --- a/includes/rts/Messages.h +++ b/includes/rts/Messages.h @@ -40,7 +40,8 @@ * expected to return. */ void barf(const char *s, ...) - GNUC3_ATTRIBUTE(__noreturn__); + GNUC3_ATTRIBUTE(__noreturn__) + GNUC3_ATTRIBUTE(format(printf, 1, 2)); void vbarf(const char *s, va_list ap) GNUC3_ATTRIBUTE(__noreturn__); diff --git a/rts/Capability.c b/rts/Capability.c index 0fcb0c9..03b2a86 100644 --- a/rts/Capability.c +++ b/rts/Capability.c @@ -362,7 +362,7 @@ void initCapabilities (void) } n_numa_nodes = logical; if (logical == 0) { - barf("%s: available NUMA node set is empty"); + barf("available NUMA node set is empty"); } } diff --git a/rts/Schedule.c b/rts/Schedule.c index 8002ac3..349a778 100644 --- a/rts/Schedule.c +++ b/rts/Schedule.c @@ -271,7 +271,7 @@ schedule (Capability *initialCapability, Task *task) } break; default: - barf("sched_state: %d", sched_state); + barf("sched_state: %ld", sched_state); } scheduleFindWork(&cap); diff --git a/rts/Threads.c b/rts/Threads.c index b09dfa8..b769177 100644 --- a/rts/Threads.c +++ b/rts/Threads.c @@ -876,7 +876,7 @@ printThreadBlockage(StgTSO *tso) debugBelch("is blocked on an STM operation"); break; default: - barf("printThreadBlockage: strange tso->why_blocked: %d for TSO %d (%d)", + barf("printThreadBlockage: strange tso->why_blocked: %d for TSO %d (%p)", tso->why_blocked, tso->id, tso); } } From git at git.haskell.org Tue Feb 6 19:22:13 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 6 Feb 2018 19:22:13 +0000 (UTC) Subject: [commit: ghc] master: rts: Fix format of failed memory commit message (1512b63) Message-ID: <20180206192213.10B5C3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1512b63347dff5aeae4a27d7421f7608cc43a196/ghc >--------------------------------------------------------------- commit 1512b63347dff5aeae4a27d7421f7608cc43a196 Author: Ben Gamari Date: Tue Feb 6 13:26:50 2018 -0500 rts: Fix format of failed memory commit message Test Plan: Validate Reviewers: erikd, simonmar Reviewed By: simonmar Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4373 >--------------------------------------------------------------- 1512b63347dff5aeae4a27d7421f7608cc43a196 rts/posix/OSMem.c | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/rts/posix/OSMem.c b/rts/posix/OSMem.c index 2f0bf3f..410b4d0 100644 --- a/rts/posix/OSMem.c +++ b/rts/posix/OSMem.c @@ -536,7 +536,7 @@ void osCommitMemory(void *at, W_ size) { void *r = my_mmap(at, size, MEM_COMMIT); if (r == NULL) { - barf("Unable to commit %d bytes of memory", size); + barf("Unable to commit %lu bytes of memory", size); } } From git at git.haskell.org Tue Feb 6 19:22:07 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 6 Feb 2018 19:22:07 +0000 (UTC) Subject: [commit: ghc] master: Restore 'It is a member of hidden package' message. (4c36440) Message-ID: <20180206192207.517AE3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4c364402ad9edade698863a3684f395e737b9de2/ghc >--------------------------------------------------------------- commit 4c364402ad9edade698863a3684f395e737b9de2 Author: Edward Z. Yang Date: Tue Feb 6 13:27:46 2018 -0500 Restore 'It is a member of hidden package' message. See comment in Packages for more details. Fixes #14717. Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: snoyberg, taylorfausak, bgamari Reviewed By: snoyberg, taylorfausak, bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14717 Differential Revision: https://phabricator.haskell.org/D4376 >--------------------------------------------------------------- 4c364402ad9edade698863a3684f395e737b9de2 compiler/main/Packages.hs | 29 ++++++++++++++++++++++++++++- testsuite/tests/package/package07e.stderr | 4 ++++ testsuite/tests/package/package08e.stderr | 4 ++++ testsuite/tests/plugins/T11244.stderr | 3 +-- 4 files changed, 37 insertions(+), 3 deletions(-) diff --git a/compiler/main/Packages.hs b/compiler/main/Packages.hs index 14407be..e8e9032 100644 --- a/compiler/main/Packages.hs +++ b/compiler/main/Packages.hs @@ -1596,8 +1596,35 @@ mkModuleToPkgConfAll -> VisibilityMap -> ModuleToPkgConfAll mkModuleToPkgConfAll dflags pkg_db vis_map = - Map.foldlWithKey extend_modmap emptyMap vis_map + -- What should we fold on? Both situations are awkward: + -- + -- * Folding on the visibility map means that we won't create + -- entries for packages that aren't mentioned in vis_map + -- (e.g., hidden packages, causing #14717) + -- + -- * Folding on pkg_db is awkward because if we have an + -- Backpack instantiation, we need to possibly add a + -- package from pkg_db multiple times to the actual + -- ModuleToPkgConfAll. Also, we don't really want + -- definite package instantiations to show up in the + -- list of possibilities. + -- + -- So what will we do instead? We'll extend vis_map with + -- entries for every definite (for non-Backpack) and + -- indefinite (for Backpack) package, so that we get the + -- hidden entries we need. + Map.foldlWithKey extend_modmap emptyMap vis_map_extended where + vis_map_extended = Map.union vis_map {- preferred -} default_vis + + default_vis = Map.fromList + [ (packageConfigId pkg, mempty) + | pkg <- eltsUDFM (unPackageConfigMap pkg_db) + -- Exclude specific instantiations of an indefinite + -- package + , indefinite pkg || null (instantiatedWith pkg) + ] + emptyMap = Map.empty sing pk m _ = Map.singleton (mkModule pk m) addListTo = foldl' merge diff --git a/testsuite/tests/package/package07e.stderr b/testsuite/tests/package/package07e.stderr index a446a47..9ca835f 100644 --- a/testsuite/tests/package/package07e.stderr +++ b/testsuite/tests/package/package07e.stderr @@ -1,16 +1,20 @@ package07e.hs:2:1: error: Could not find module ‘MyHsTypes’ + Perhaps you meant HsTypes (needs flag -package-key ghc-8.5) Use -v to see a list of the files searched for. package07e.hs:3:1: error: Could not find module ‘HsTypes’ + It is a member of the hidden package ‘ghc-8.5’. Use -v to see a list of the files searched for. package07e.hs:4:1: error: Could not find module ‘HsUtils’ + It is a member of the hidden package ‘ghc-8.5’. Use -v to see a list of the files searched for. package07e.hs:5:1: error: Could not find module ‘UniqFM’ + It is a member of the hidden package ‘ghc-8.5’. Use -v to see a list of the files searched for. diff --git a/testsuite/tests/package/package08e.stderr b/testsuite/tests/package/package08e.stderr index 3d8d232..5992a4c 100644 --- a/testsuite/tests/package/package08e.stderr +++ b/testsuite/tests/package/package08e.stderr @@ -1,16 +1,20 @@ package08e.hs:2:1: error: Could not find module ‘MyHsTypes’ + Perhaps you meant HsTypes (needs flag -package-key ghc-8.5) Use -v to see a list of the files searched for. package08e.hs:3:1: error: Could not find module ‘HsTypes’ + It is a member of the hidden package ‘ghc-8.5’. Use -v to see a list of the files searched for. package08e.hs:4:1: error: Could not find module ‘HsUtils’ + It is a member of the hidden package ‘ghc-8.5’. Use -v to see a list of the files searched for. package08e.hs:5:1: error: Could not find module ‘UniqFM’ + It is a member of the hidden package ‘ghc-8.5’. Use -v to see a list of the files searched for. diff --git a/testsuite/tests/plugins/T11244.stderr b/testsuite/tests/plugins/T11244.stderr index f489103..30c8c5b 100644 --- a/testsuite/tests/plugins/T11244.stderr +++ b/testsuite/tests/plugins/T11244.stderr @@ -1,4 +1,3 @@ : Could not find module ‘RuleDefiningPlugin’ -Perhaps you meant - RuleDefiningPlugin (from rule-defining-plugin-0.1) +It is a member of the hidden package ‘rule-defining-plugin-0.1’. Use -v to see a list of the files searched for. From git at git.haskell.org Tue Feb 6 19:22:15 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 6 Feb 2018 19:22:15 +0000 (UTC) Subject: [commit: ghc] master: cmm: Remove unnecessary HsVersion.h includes (7ad72eb) Message-ID: <20180206192215.D43163A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7ad72eb39d1becc9fdbc99d4969f5b9b182ddf93/ghc >--------------------------------------------------------------- commit 7ad72eb39d1becc9fdbc99d4969f5b9b182ddf93 Author: Michal Terepeta Date: Tue Feb 6 13:26:29 2018 -0500 cmm: Remove unnecessary HsVersion.h includes Test Plan: ./validate Reviewers: goldfire, bgamari, simonmar Reviewed By: bgamari Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4367 >--------------------------------------------------------------- 7ad72eb39d1becc9fdbc99d4969f5b9b182ddf93 compiler/cmm/Bitmap.hs | 5 +---- compiler/cmm/Cmm.hs | 2 -- compiler/cmm/CmmBuildInfoTables.hs | 4 +--- compiler/cmm/CmmCallConv.hs | 4 ---- compiler/cmm/CmmLayoutStack.hs | 4 +--- compiler/cmm/CmmMachOp.hs | 4 ---- compiler/cmm/CmmOpt.hs | 4 ---- compiler/cmm/CmmType.hs | 3 --- compiler/cmm/MkGraph.hs | 2 -- compiler/cmm/SMRep.hs | 3 --- 10 files changed, 3 insertions(+), 32 deletions(-) diff --git a/compiler/cmm/Bitmap.hs b/compiler/cmm/Bitmap.hs index 6ff6193..e6ac15f 100644 --- a/compiler/cmm/Bitmap.hs +++ b/compiler/cmm/Bitmap.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE CPP, BangPatterns #-} +{-# LANGUAGE BangPatterns #-} -- -- (c) The University of Glasgow 2003-2006 @@ -15,9 +15,6 @@ module Bitmap ( seqBitmap, ) where -#include "HsVersions.h" -#include "../includes/MachDeps.h" - import GhcPrelude import SMRep diff --git a/compiler/cmm/Cmm.hs b/compiler/cmm/Cmm.hs index c9ecda8..9f83273 100644 --- a/compiler/cmm/Cmm.hs +++ b/compiler/cmm/Cmm.hs @@ -41,8 +41,6 @@ import Outputable import Data.Word ( Word8 ) -#include "HsVersions.h" - ----------------------------------------------------------------------------- -- Cmm, GenCmm ----------------------------------------------------------------------------- diff --git a/compiler/cmm/CmmBuildInfoTables.hs b/compiler/cmm/CmmBuildInfoTables.hs index a482306..dc5cfd6 100644 --- a/compiler/cmm/CmmBuildInfoTables.hs +++ b/compiler/cmm/CmmBuildInfoTables.hs @@ -1,12 +1,10 @@ -{-# LANGUAGE BangPatterns, CPP, GADTs #-} +{-# LANGUAGE BangPatterns, GADTs #-} module CmmBuildInfoTables ( CAFSet, CAFEnv, cafAnal , doSRTs, TopSRT, emptySRT, isEmptySRT, srtToData ) where -#include "HsVersions.h" - import GhcPrelude hiding (succ) import Hoopl.Block diff --git a/compiler/cmm/CmmCallConv.hs b/compiler/cmm/CmmCallConv.hs index c32710e..e1067e9 100644 --- a/compiler/cmm/CmmCallConv.hs +++ b/compiler/cmm/CmmCallConv.hs @@ -1,5 +1,3 @@ -{-# LANGUAGE CPP #-} - module CmmCallConv ( ParamLocation(..), assignArgumentsPos, @@ -7,8 +5,6 @@ module CmmCallConv ( realArgRegsCover ) where -#include "HsVersions.h" - import GhcPrelude import CmmExpr diff --git a/compiler/cmm/CmmLayoutStack.hs b/compiler/cmm/CmmLayoutStack.hs index b2d74b2..6cf8f8e 100644 --- a/compiler/cmm/CmmLayoutStack.hs +++ b/compiler/cmm/CmmLayoutStack.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE BangPatterns, CPP, RecordWildCards, GADTs #-} +{-# LANGUAGE BangPatterns, RecordWildCards, GADTs #-} module CmmLayoutStack ( cmmLayoutStack, setInfoTableStackMap ) where @@ -39,8 +39,6 @@ import Data.Array as Array import Data.Bits import Data.List (nub) -#include "HsVersions.h" - {- Note [Stack Layout] The job of this pass is to diff --git a/compiler/cmm/CmmMachOp.hs b/compiler/cmm/CmmMachOp.hs index 8ac4a6f..9203911 100644 --- a/compiler/cmm/CmmMachOp.hs +++ b/compiler/cmm/CmmMachOp.hs @@ -1,5 +1,3 @@ -{-# LANGUAGE CPP #-} - module CmmMachOp ( MachOp(..) , pprMachOp, isCommutableMachOp, isAssociativeMachOp @@ -28,8 +26,6 @@ module CmmMachOp ) where -#include "HsVersions.h" - import GhcPrelude import CmmType diff --git a/compiler/cmm/CmmOpt.hs b/compiler/cmm/CmmOpt.hs index f9b1260..6b4d792 100644 --- a/compiler/cmm/CmmOpt.hs +++ b/compiler/cmm/CmmOpt.hs @@ -1,5 +1,3 @@ -{-# LANGUAGE CPP #-} - -- The default iteration limit is a bit too low for the definitions -- in this module. {-# OPTIONS_GHC -fmax-pmcheck-iterations=10000000 #-} @@ -19,8 +17,6 @@ module CmmOpt ( cmmMachOpFoldM ) where -#include "HsVersions.h" - import GhcPrelude import CmmUtils diff --git a/compiler/cmm/CmmType.hs b/compiler/cmm/CmmType.hs index cb15dc7..0538b9f 100644 --- a/compiler/cmm/CmmType.hs +++ b/compiler/cmm/CmmType.hs @@ -1,5 +1,3 @@ -{-# LANGUAGE CPP #-} - module CmmType ( CmmType -- Abstract , b8, b16, b32, b64, b128, b256, b512, f32, f64, bWord, bHalfWord, gcWord @@ -29,7 +27,6 @@ module CmmType ) where -#include "HsVersions.h" import GhcPrelude diff --git a/compiler/cmm/MkGraph.hs b/compiler/cmm/MkGraph.hs index f130f1b..d9f1402 100644 --- a/compiler/cmm/MkGraph.hs +++ b/compiler/cmm/MkGraph.hs @@ -42,8 +42,6 @@ import Control.Monad import Data.List import Data.Maybe -#include "HsVersions.h" - ----------------------------------------------------------------------------- -- Building Graphs diff --git a/compiler/cmm/SMRep.hs b/compiler/cmm/SMRep.hs index 1469ae1..9f8a49b 100644 --- a/compiler/cmm/SMRep.hs +++ b/compiler/cmm/SMRep.hs @@ -47,9 +47,6 @@ module SMRep ( pprWord8String, stringToWord8s ) where -#include "../HsVersions.h" -#include "../includes/MachDeps.h" - import GhcPrelude import BasicTypes( ConTagZ ) From git at git.haskell.org Tue Feb 6 22:28:26 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 6 Feb 2018 22:28:26 +0000 (UTC) Subject: [commit: ghc] master: rts: fix some barf format specifiers. (00f1a4a) Message-ID: <20180206222826.E9C403A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/00f1a4ab80b201ce15c509126f89c5a108786f32/ghc >--------------------------------------------------------------- commit 00f1a4ab80b201ce15c509126f89c5a108786f32 Author: Douglas Wilson Date: Tue Feb 6 17:27:32 2018 -0500 rts: fix some barf format specifiers. Reviewers: bgamari, erikd, simonmar Reviewed By: bgamari Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4390 >--------------------------------------------------------------- 00f1a4ab80b201ce15c509126f89c5a108786f32 rts/Schedule.c | 2 +- rts/posix/OSMem.c | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/rts/Schedule.c b/rts/Schedule.c index 349a778..f1363e4 100644 --- a/rts/Schedule.c +++ b/rts/Schedule.c @@ -271,7 +271,7 @@ schedule (Capability *initialCapability, Task *task) } break; default: - barf("sched_state: %ld", sched_state); + barf("sched_state: %" FMT_Word, sched_state); } scheduleFindWork(&cap); diff --git a/rts/posix/OSMem.c b/rts/posix/OSMem.c index 410b4d0..f603644 100644 --- a/rts/posix/OSMem.c +++ b/rts/posix/OSMem.c @@ -536,7 +536,7 @@ void osCommitMemory(void *at, W_ size) { void *r = my_mmap(at, size, MEM_COMMIT); if (r == NULL) { - barf("Unable to commit %lu bytes of memory", size); + barf("Unable to commit %" FMT_Word " bytes of memory", size); } } From git at git.haskell.org Tue Feb 6 23:07:02 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 6 Feb 2018 23:07:02 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Add test for #14768 (da46813) Message-ID: <20180206230702.71F3F3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/da4681303892804ea08b60bfd47cbb82ca8e6589/ghc >--------------------------------------------------------------- commit da4681303892804ea08b60bfd47cbb82ca8e6589 Author: Ben Gamari Date: Tue Feb 6 17:33:21 2018 -0500 testsuite: Add test for #14768 >--------------------------------------------------------------- da4681303892804ea08b60bfd47cbb82ca8e6589 testsuite/tests/simplCore/should_run/T14768.hs | 59 ++++++++++++++++++++++++++ testsuite/tests/simplCore/should_run/all.T | 1 + 2 files changed, 60 insertions(+) diff --git a/testsuite/tests/simplCore/should_run/T14768.hs b/testsuite/tests/simplCore/should_run/T14768.hs new file mode 100644 index 0000000..116cb82 --- /dev/null +++ b/testsuite/tests/simplCore/should_run/T14768.hs @@ -0,0 +1,59 @@ +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE TypeFamilies #-} + +module Main where + +import Control.Monad (forM_, liftM) +import qualified Data.Vector.Generic as G +import qualified Data.Vector.Generic.Mutable as M +import qualified Data.Vector.Primitive as P +import qualified Data.Vector.Unboxed as U +import qualified Data.Vector.Unboxed.Mutable as MU +import GHC.Exts + +vec :: U.Vector Moebius +vec = U.singleton Moebius0 + +main :: IO () +main = print $ U.head vec == U.head vec + +data Moebius = Moebius0 | Moebius1 | Moebius2 + deriving (Eq) + +fromMoebius :: Moebius -> Int +fromMoebius Moebius0 = 0 +fromMoebius Moebius1 = 1 +fromMoebius Moebius2 = 2 + +toMoebius :: Int -> Moebius +toMoebius (I# i#) = tagToEnum# i# + +newtype instance U.MVector s Moebius = MV_Moebius (P.MVector s Int) +newtype instance U.Vector Moebius = V_Moebius (P.Vector Int) + +instance U.Unbox Moebius + +instance M.MVector U.MVector Moebius where + basicLength (MV_Moebius v) = M.basicLength v + basicUnsafeSlice i n (MV_Moebius v) = MV_Moebius $ M.basicUnsafeSlice i n v + basicOverlaps (MV_Moebius v1) (MV_Moebius v2) = M.basicOverlaps v1 v2 + basicUnsafeNew n = MV_Moebius `liftM` M.basicUnsafeNew n + basicInitialize (MV_Moebius v) = M.basicInitialize v + basicUnsafeReplicate n x = MV_Moebius `liftM` M.basicUnsafeReplicate n (fromMoebius x) + basicUnsafeRead (MV_Moebius v) i = toMoebius `liftM` M.basicUnsafeRead v i + basicUnsafeWrite (MV_Moebius v) i x = M.basicUnsafeWrite v i (fromMoebius x) + basicClear (MV_Moebius v) = M.basicClear v + basicSet (MV_Moebius v) x = M.basicSet v (fromMoebius x) + basicUnsafeCopy (MV_Moebius v1) (MV_Moebius v2) = M.basicUnsafeCopy v1 v2 + basicUnsafeMove (MV_Moebius v1) (MV_Moebius v2) = M.basicUnsafeMove v1 v2 + basicUnsafeGrow (MV_Moebius v) n = MV_Moebius `liftM` M.basicUnsafeGrow v n + +instance G.Vector U.Vector Moebius where + basicUnsafeFreeze (MV_Moebius v) = V_Moebius `liftM` G.basicUnsafeFreeze v + basicUnsafeThaw (V_Moebius v) = MV_Moebius `liftM` G.basicUnsafeThaw v + basicLength (V_Moebius v) = G.basicLength v + basicUnsafeSlice i n (V_Moebius v) = V_Moebius $ G.basicUnsafeSlice i n v + basicUnsafeIndexM (V_Moebius v) i = toMoebius `liftM` G.basicUnsafeIndexM v i + basicUnsafeCopy (MV_Moebius mv) (V_Moebius v) = G.basicUnsafeCopy mv v + elemseq _ = seq diff --git a/testsuite/tests/simplCore/should_run/all.T b/testsuite/tests/simplCore/should_run/all.T index 4ba5a71..d922f90 100644 --- a/testsuite/tests/simplCore/should_run/all.T +++ b/testsuite/tests/simplCore/should_run/all.T @@ -78,3 +78,4 @@ test('T13429', normal, compile_and_run, ['']) test('T13429_2', normal, compile_and_run, ['']) test('T13750', normal, compile_and_run, ['']) test('T14178', normal, compile_and_run, ['']) +test('T14768', reqlib('vector'), compile_and_run, ['']) From git at git.haskell.org Wed Feb 7 06:39:43 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Feb 2018 06:39:43 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: Adds `smp` flag to rts.cabal. (3c276b5) Message-ID: <20180207063943.628C23A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/3c276b599396da4326cd33ed0ce4e0ce31612e21/ghc >--------------------------------------------------------------- commit 3c276b599396da4326cd33ed0ce4e0ce31612e21 Author: Moritz Angermann Date: Sat Nov 25 20:49:56 2017 +0800 Adds `smp` flag to rts.cabal. >--------------------------------------------------------------- 3c276b599396da4326cd33ed0ce4e0ce31612e21 rts/rts.cabal.in | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/rts/rts.cabal.in b/rts/rts.cabal.in index 71aef3d..b33a5f4 100644 --- a/rts/rts.cabal.in +++ b/rts/rts.cabal.in @@ -24,6 +24,8 @@ flag 64bit default: @Cabal64bit@ flag leading-underscore default: @CabalLeadingUnderscore@ +flag smp + default: True library -- rts is a wired in package and @@ -72,6 +74,8 @@ library if flag(libdw) -- for backtraces extra-libraries: elf dw + if !flag(smp) + cpp-options: -DNOSMP include-dirs: build ../includes includes includes/dist-derivedconstants/header @FFIIncludeDir@ From git at git.haskell.org Wed Feb 7 06:39:46 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Feb 2018 06:39:46 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: adds -latomic to. ghc-prim (79b25d1) Message-ID: <20180207063946.267963A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/79b25d14d22b6b596d90f853f3f748327c449a32/ghc >--------------------------------------------------------------- commit 79b25d14d22b6b596d90f853f3f748327c449a32 Author: Moritz Angermann Date: Mon Dec 4 10:56:13 2017 +0800 adds -latomic to. ghc-prim >--------------------------------------------------------------- 79b25d14d22b6b596d90f853f3f748327c449a32 libraries/ghc-prim/ghc-prim.cabal | 3 +++ 1 file changed, 3 insertions(+) diff --git a/libraries/ghc-prim/ghc-prim.cabal b/libraries/ghc-prim/ghc-prim.cabal index f395c9f..2b860e6 100644 --- a/libraries/ghc-prim/ghc-prim.cabal +++ b/libraries/ghc-prim/ghc-prim.cabal @@ -66,6 +66,9 @@ Library -- on Windows. Required because of mingw32. extra-libraries: user32, mingw32, mingwex + if os(linux) + extra-libraries: atomic + c-sources: cbits/atomic.c cbits/bswap.c From git at git.haskell.org Wed Feb 7 06:39:50 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Feb 2018 06:39:50 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: Move `iserv` into `utils` and change package name from `iserv-bin` to `iserv` (afedb46) Message-ID: <20180207063950.3AC663A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/afedb461e2ab699b8f0eca5d02bdbf81a1ba5a9c/ghc >--------------------------------------------------------------- commit afedb461e2ab699b8f0eca5d02bdbf81a1ba5a9c Author: Moritz Angermann Date: Sat Nov 25 15:10:52 2017 +0800 Move `iserv` into `utils` and change package name from `iserv-bin` to `iserv` This is done for consistency. We usually call the package file the same name the folder has. The move into `utils` is done so that we can move the library into `libraries/iserv` and the proxy into `utils/iserv-proxy` and then break the `iserv.cabal` apart. This will make building the cross compiler with TH simpler, because we can build the library and proxy as separate packages. >--------------------------------------------------------------- afedb461e2ab699b8f0eca5d02bdbf81a1ba5a9c ghc.mk | 13 +-- {iserv => libraries/libiserv}/Makefile | 0 {iserv => libraries/libiserv}/cbits/iservmain.c | 0 libraries/libiserv/ghc.mk | 5 + libraries/libiserv/libiserv.cabal | 39 +++++++ {iserv => libraries/libiserv}/proxy-src/Remote.hs | 0 {iserv => libraries/libiserv}/src/GHCi/Utils.hsc | 0 {iserv => libraries/libiserv}/src/Lib.hs | 0 {iserv => libraries/libiserv}/src/Main.hs | 0 .../libiserv}/src/Remote/Message.hs | 0 {iserv => libraries/libiserv}/src/Remote/Slave.hs | 0 {iserv => utils/iserv-proxy}/Makefile | 0 utils/iserv-proxy/ghc.mk | 113 +++++++++++++++++++++ .../iserv-proxy/iserv-proxy.cabal | 72 +------------ .../Remote.hs => utils/iserv-proxy/src/Main.hs | 0 {iserv => utils/iserv}/Makefile | 0 {iserv => utils/iserv}/cbits/iservmain.c | 0 {iserv => utils/iserv}/ghc.mk | 66 ++++++------ utils/iserv/iserv.cabal | 44 ++++++++ {iserv => utils/iserv}/src/Main.hs | 0 20 files changed, 246 insertions(+), 106 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc afedb461e2ab699b8f0eca5d02bdbf81a1ba5a9c From git at git.haskell.org Wed Feb 7 06:39:53 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Feb 2018 06:39:53 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: Adds test (4eac8fe) Message-ID: <20180207063953.7F1723A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/4eac8fe493ab00da87ce1fa059fed12271e8f0a5/ghc >--------------------------------------------------------------- commit 4eac8fe493ab00da87ce1fa059fed12271e8f0a5 Author: Moritz Angermann Date: Thu Sep 21 22:07:44 2017 +0800 Adds test >--------------------------------------------------------------- 4eac8fe493ab00da87ce1fa059fed12271e8f0a5 testsuite/tests/codeGen/should_run/T14251.hs | 22 ++++++++++++++++++++++ testsuite/tests/codeGen/should_run/T14251.stdout | 1 + testsuite/tests/codeGen/should_run/all.T | 2 +- 3 files changed, 24 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/codeGen/should_run/T14251.hs b/testsuite/tests/codeGen/should_run/T14251.hs new file mode 100644 index 0000000..6f552e1 --- /dev/null +++ b/testsuite/tests/codeGen/should_run/T14251.hs @@ -0,0 +1,22 @@ +{-# LANGUAGE MagicHash, BangPatterns #-} +module Main where + +-- A minor modification from T8064.hs. +-- +-- The key here is that we ensure that +-- subsequently passed floats do not +-- accidentally end up in previous +-- registers. +-- + +import GHC.Exts + +{-# NOINLINE f #-} +f :: (Int# -> Float# -> Double# -> Float# -> Double# -> String) -> String +f g = g 3# 4.0# 5.0## 6.0# 6.9## ++ " World!" + +{-# NOINLINE q #-} +q :: Int# -> Float# -> Double# -> Float# -> Double# -> String +q i j k l m = "Hello " ++ show (F# l) ++ " " ++ show (D# m) + +main = putStrLn (f $ q) diff --git a/testsuite/tests/codeGen/should_run/T14251.stdout b/testsuite/tests/codeGen/should_run/T14251.stdout new file mode 100644 index 0000000..8ec577b --- /dev/null +++ b/testsuite/tests/codeGen/should_run/T14251.stdout @@ -0,0 +1 @@ +Hello 6.0 6.9 World! diff --git a/testsuite/tests/codeGen/should_run/all.T b/testsuite/tests/codeGen/should_run/all.T index 9403c4b..1711260 100644 --- a/testsuite/tests/codeGen/should_run/all.T +++ b/testsuite/tests/codeGen/should_run/all.T @@ -166,4 +166,4 @@ test('T13825-unit', compile_and_run, ['-package ghc']) test('T14619', normal, compile_and_run, ['']) -test('T14754', normal, compile_and_run, ['']) +test('T14754', normal, compile_and_run, ['-O2']) From git at git.haskell.org Wed Feb 7 06:39:59 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Feb 2018 06:39:59 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: Adds distrib/Makefile from @alpmestan (41d9d2e) Message-ID: <20180207063959.7B9F83A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/41d9d2ec975de39bf74c69f6b12c25ac2cd59a4c/ghc >--------------------------------------------------------------- commit 41d9d2ec975de39bf74c69f6b12c25ac2cd59a4c Author: Moritz Angermann Date: Fri Dec 8 12:58:53 2017 +0800 Adds distrib/Makefile from @alpmestan >--------------------------------------------------------------- 41d9d2ec975de39bf74c69f6b12c25ac2cd59a4c distrib/Makefile | 34 ++++++++++++++++++++++++++++++++++ 1 file changed, 34 insertions(+) diff --git a/distrib/Makefile b/distrib/Makefile new file mode 100644 index 0000000..e806ff8 --- /dev/null +++ b/distrib/Makefile @@ -0,0 +1,34 @@ +MAKEFLAGS += --no-builtin-rules +.SUFFIXES: + +ProjectVersion:=$(shell bin/ghc --numeric-version) + +include mk/install.mk + +define GHC_WRAPPER +#!/bin/sh +exec "$(libdir)/bin/ghc" -B"$(libdir)" $${1+"$$@"} +endef + +export GHC_WRAPPER + +.PHONY: default +default: + @echo 'Run "make install" to install' + @false + +.PHONY: install +install: + @cp settings lib/ + @echo $(prefix) $(bindir) $(libdir) + @mkdir -p $(prefix) $(libdir) $(bindir) + @cp -R lib/* $(libdir)/ + # cp the rest to $(prefix) ? or maybe handle $(datadir) etc too? + @if [ "$(bindir)" = "$(prefix)/bin" ] || [ "$(libdir)" != "$(prefix)/lib" ]; then \ + echo "custom bindir or libdir"; \ + mkdir -p $(libdir)/bin; \ + cp bin/* $(libdir)/bin/; \ + echo "$$GHC_WRAPPER" > $(bindir)/ghc; \ + fi + @echo "ghc available at $(bindir)/ghc" + @echo done From git at git.haskell.org Wed Feb 7 06:40:02 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Feb 2018 06:40:02 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: Adds x86_64 android layout (5f7ea11) Message-ID: <20180207064002.47A093A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/5f7ea110da8533b8d614c4cbba362e974b8ac923/ghc >--------------------------------------------------------------- commit 5f7ea110da8533b8d614c4cbba362e974b8ac923 Author: Moritz Angermann Date: Sun Dec 10 07:36:20 2017 +0800 Adds x86_64 android layout >--------------------------------------------------------------- 5f7ea110da8533b8d614c4cbba362e974b8ac923 llvm-targets | 1 + utils/llvm-targets/gen-data-layout.sh | 2 +- 2 files changed, 2 insertions(+), 1 deletion(-) diff --git a/llvm-targets b/llvm-targets index 3c9da1e..6dd5a60 100644 --- a/llvm-targets +++ b/llvm-targets @@ -11,6 +11,7 @@ ,("i386-unknown-linux", ("e-m:e-p:32:32-f64:32:64-f80:32-n8:16:32-S128", "pentium4", "")) ,("x86_64-unknown-linux-gnu", ("e-m:e-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) ,("x86_64-unknown-linux", ("e-m:e-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) +,("x86_64-unknown-linux-android", ("e-m:e-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "+sse4.2 +popcnt")) ,("armv7-unknown-linux-androideabi", ("e-m:e-p:32:32-i64:64-v128:64:128-a:0:32-n32-S64", "generic", "")) ,("aarch64-unknown-linux-android", ("e-m:e-i8:8:32-i16:16:32-i64:64-i128:128-n32:64-S128", "generic", "+neon")) ,("arm-unknown-nto-qnx-eabi", ("e-m:e-p:32:32-i64:64-v128:64:128-a:0:32-n32-S64", "arm7tdmi", "+strict-align")) diff --git a/utils/llvm-targets/gen-data-layout.sh b/utils/llvm-targets/gen-data-layout.sh index 6f2aafc..05ab085 100755 --- a/utils/llvm-targets/gen-data-layout.sh +++ b/utils/llvm-targets/gen-data-layout.sh @@ -20,7 +20,7 @@ WINDOWS_x86="i386-unknown-windows i686-unknown-windows x86_64-unknown-windows" LINUX_ARM="arm-unknown-linux-gnueabihf armv6-unknown-linux-gnueabihf armv7-unknown-linux-gnueabihf aarch64-unknown-linux-gnu aarch64-unknown-linux armv7a-unknown-linux-gnueabi" LINUX_x86="i386-unknown-linux-gnu i386-unknown-linux x86_64-unknown-linux-gnu x86_64-unknown-linux" -ANDROID="armv7-unknown-linux-androideabi aarch64-unknown-linux-android" +ANDROID="x86_64-unknown-linux-android armv7-unknown-linux-androideabi aarch64-unknown-linux-android" QNX="arm-unknown-nto-qnx-eabi" MACOS="i386-apple-darwin x86_64-apple-darwin" IOS="armv7-apple-ios arm64-apple-ios i386-apple-ios x86_64-apple-ios" From git at git.haskell.org Wed Feb 7 06:39:56 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Feb 2018 06:39:56 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: replace git subtree with submodule. (7aa6057) Message-ID: <20180207063956.4E9573A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/7aa6057b2e0847a3c66ace6dd160f7f0e1c352ba/ghc >--------------------------------------------------------------- commit 7aa6057b2e0847a3c66ace6dd160f7f0e1c352ba Author: Moritz Angermann Date: Fri Dec 8 13:12:09 2017 +0800 replace git subtree with submodule. >--------------------------------------------------------------- 7aa6057b2e0847a3c66ace6dd160f7f0e1c352ba .gitmodules | 10 ++++++++++ hadrian | 2 +- 2 files changed, 11 insertions(+), 1 deletion(-) diff --git a/.gitmodules b/.gitmodules index 2125a92..9d5608a 100644 --- a/.gitmodules +++ b/.gitmodules @@ -132,3 +132,13 @@ [submodule "hadrian"] path = hadrian url = ../hadrian.git +[submodule "libraries/data-bitcode"] + path = libraries/data-bitcode + url = https://github.com/angerman/data-bitcode.git +[submodule "libraries/data-bitcode-llvm"] + path = libraries/data-bitcode-llvm + url = https://github.com/angerman/data-bitcode-llvm.git +[submodule "libraries/data-bitcode-edsl"] + path = libraries/data-bitcode-edsl + url = https://github.com/angerman/data-bitcode-edsl.git + diff --git a/hadrian b/hadrian index 86216e2..323212d 160000 --- a/hadrian +++ b/hadrian @@ -1 +1 @@ -Subproject commit 86216e249f307a778bef3755afb7474910bc60cc +Subproject commit 323212d071d02e9435fb2c1eb3c47edd13cba195 From git at git.haskell.org Wed Feb 7 06:40:07 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Feb 2018 06:40:07 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: Adds `-llvmng` (bc80dbe) Message-ID: <20180207064007.08C6A3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/bc80dbee4a3d41fcdc5cb0e968eae3d548eaac63/ghc >--------------------------------------------------------------- commit bc80dbee4a3d41fcdc5cb0e968eae3d548eaac63 Author: Moritz Angermann Date: Mon Jul 31 15:18:49 2017 +0800 Adds `-llvmng` >--------------------------------------------------------------- bc80dbee4a3d41fcdc5cb0e968eae3d548eaac63 compiler/cmm/CmmSwitch.hs | 1 + compiler/codeGen/StgCmmPrim.hs | 3 +- compiler/ghc.cabal.in | 8 +- compiler/llvmGen-ng/Data/BitCode/LLVM/Gen.hs | 1788 ++++++++++++++++++++ compiler/llvmGen-ng/Data/BitCode/LLVM/Gen/Monad.hs | 83 + compiler/main/CodeOutput.hs | 10 + compiler/main/DriverPipeline.hs | 5 +- compiler/main/DynFlags.hs | 12 +- compiler/typecheck/TcForeign.hs | 4 +- ghc.mk | 8 + libraries/base/tests/all.T | 2 +- libraries/data-bitcode | 1 + libraries/data-bitcode-edsl | 1 + libraries/data-bitcode-llvm | 1 + mk/build.mk.sample | 13 +- mk/flavours/{prof.mk => prof-llvmng.mk} | 6 +- mk/flavours/{quick-cross.mk => quick-cross-ng.mk} | 4 +- mk/flavours/{quick.mk => quick-llvmng.mk} | 4 +- packages | 3 + testsuite/config/ghc | 16 +- 20 files changed, 1954 insertions(+), 19 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc bc80dbee4a3d41fcdc5cb0e968eae3d548eaac63 From git at git.haskell.org Wed Feb 7 06:40:12 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Feb 2018 06:40:12 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: no tbaa (3cf9fd9) Message-ID: <20180207064012.987E63A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/3cf9fd96271328f8121484f15ccd2b72c227b64e/ghc >--------------------------------------------------------------- commit 3cf9fd96271328f8121484f15ccd2b72c227b64e Author: Moritz Angermann Date: Sat Dec 2 14:09:03 2017 +0800 no tbaa >--------------------------------------------------------------- 3cf9fd96271328f8121484f15ccd2b72c227b64e compiler/main/DriverPipeline.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs index 180f362..af64874 100644 --- a/compiler/main/DriverPipeline.hs +++ b/compiler/main/DriverPipeline.hs @@ -812,8 +812,8 @@ fastLlvmPipeline dflags llvmOptions :: DynFlags -> [(String, String)] -- ^ pairs of (opt, llc) arguments llvmOptions dflags = - [("-enable-tbaa -tbaa", "-enable-tbaa") | gopt Opt_LlvmTBAA dflags ] - ++ [("-relocation-model=" ++ rmodel +-- [("-enable-tbaa -tbaa", "-enable-tbaa") | gopt Opt_LlvmTBAA dflags ] + [("-relocation-model=" ++ rmodel ,"-relocation-model=" ++ rmodel) | not (null rmodel)] ++ [("-stack-alignment=" ++ (show align) ,"-stack-alignment=" ++ (show align)) | align > 0 ] From git at git.haskell.org Wed Feb 7 06:40:15 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Feb 2018 06:40:15 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: Add network submodule. (ddf45c0) Message-ID: <20180207064015.5F41C3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/ddf45c07d0d6c31232605da1c2409c864f99fc9a/ghc >--------------------------------------------------------------- commit ddf45c07d0d6c31232605da1c2409c864f99fc9a Author: Moritz Angermann Date: Mon Nov 27 11:44:46 2017 +0800 Add network submodule. >--------------------------------------------------------------- ddf45c07d0d6c31232605da1c2409c864f99fc9a .gitmodules | 3 +++ libraries/network | 1 + 2 files changed, 4 insertions(+) diff --git a/.gitmodules b/.gitmodules index 9d5608a..27dd68f 100644 --- a/.gitmodules +++ b/.gitmodules @@ -141,4 +141,7 @@ [submodule "libraries/data-bitcode-edsl"] path = libraries/data-bitcode-edsl url = https://github.com/angerman/data-bitcode-edsl.git +[submodule "libraries/network"] + path = libraries/network + url = https://github.com/haskell/network.git diff --git a/libraries/network b/libraries/network new file mode 160000 index 0000000..fe70032 --- /dev/null +++ b/libraries/network @@ -0,0 +1 @@ +Subproject commit fe7003293c9a08497a9df6cc18bb3868c96bda8f From git at git.haskell.org Wed Feb 7 06:40:09 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Feb 2018 06:40:09 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: Use packed structs. (d91524d) Message-ID: <20180207064009.D1E353A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/d91524debd11e5bfeecabc454e356934f1847a89/ghc >--------------------------------------------------------------- commit d91524debd11e5bfeecabc454e356934f1847a89 Author: Moritz Angermann Date: Sun Dec 3 20:28:55 2017 +0800 Use packed structs. GHC computes offsets into structs, and we do not use getElementPointer. If we had used gep, we could use unpacked structs as well. >--------------------------------------------------------------- d91524debd11e5bfeecabc454e356934f1847a89 compiler/llvmGen-ng/Data/BitCode/LLVM/Gen.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/llvmGen-ng/Data/BitCode/LLVM/Gen.hs b/compiler/llvmGen-ng/Data/BitCode/LLVM/Gen.hs index c1c9e8c..09ffd99 100644 --- a/compiler/llvmGen-ng/Data/BitCode/LLVM/Gen.hs +++ b/compiler/llvmGen-ng/Data/BitCode/LLVM/Gen.hs @@ -299,7 +299,7 @@ llvmCodeGen' prc@(CmmProc{}) = Right $ do case mb_info of Nothing -> EDSL.ghcdefT (pure link) lbl sig body Just (Statics _ statics) - -> do prefixData <- EDSL.struct =<< mapM genData statics + -> do prefixData <- EDSL.packedStruct =<< mapM genData statics EDSL.ghcdefT (pure $ EDSL.withPrefixData prefixData . link) lbl sig body -- llvmCodeGen' _ = panic "LlvmCodeGen': unhandled raw cmm group" @@ -427,7 +427,7 @@ genStatics s@(Statics l statics) = do let link | externallyVisibleCLabel l = Val.external -- External | otherwise = Val.private -- Internal - struct <- EDSL.struct body + struct <- EDSL.packedStruct body -- make statics mutable. -- E.g. -- x :: T From git at git.haskell.org Wed Feb 7 06:40:18 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Feb 2018 06:40:18 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: bump submodules (9fe4375) Message-ID: <20180207064018.2756E3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/9fe4375231d008efa95ac58a71e88d5365d3e83f/ghc >--------------------------------------------------------------- commit 9fe4375231d008efa95ac58a71e88d5365d3e83f Author: Moritz Angermann Date: Fri Dec 8 13:16:48 2017 +0800 bump submodules >--------------------------------------------------------------- 9fe4375231d008efa95ac58a71e88d5365d3e83f libraries/data-bitcode | 2 +- libraries/data-bitcode-edsl | 2 +- libraries/data-bitcode-llvm | 2 +- utils/hsc2hs | 2 +- 4 files changed, 4 insertions(+), 4 deletions(-) diff --git a/libraries/data-bitcode b/libraries/data-bitcode index c9818de..b4cdbc1 160000 --- a/libraries/data-bitcode +++ b/libraries/data-bitcode @@ -1 +1 @@ -Subproject commit c9818debd3dae774967c0507882b6b3bec7f0ee4 +Subproject commit b4cdbc17e77771c1c3c833625b92776aa5bc854b diff --git a/libraries/data-bitcode-edsl b/libraries/data-bitcode-edsl index bc2e3e0..3b11b02 160000 --- a/libraries/data-bitcode-edsl +++ b/libraries/data-bitcode-edsl @@ -1 +1 @@ -Subproject commit bc2e3e0a8bfc438ae3ee6ebe5feaa37920e78e43 +Subproject commit 3b11b02c138f672590a026c29af6f87432f17c11 diff --git a/libraries/data-bitcode-llvm b/libraries/data-bitcode-llvm index d03a9b5..b717895 160000 --- a/libraries/data-bitcode-llvm +++ b/libraries/data-bitcode-llvm @@ -1 +1 @@ -Subproject commit d03a9b5c90787910242e8a295f6201d71c6d3a9a +Subproject commit b717895d5e1add7f908fe09b528c7524511ec6f5 diff --git a/utils/hsc2hs b/utils/hsc2hs index 9483ad1..738f366 160000 --- a/utils/hsc2hs +++ b/utils/hsc2hs @@ -1 +1 @@ -Subproject commit 9483ad10064fbbb97ab525280623826b1ef63959 +Subproject commit 738f3666c878ee9e79c3d5e819ef8b3460288edf From git at git.haskell.org Wed Feb 7 06:40:20 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Feb 2018 06:40:20 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: bump hadrian & Cabal (d260eb5) Message-ID: <20180207064020.F25653A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/d260eb5541a5cad422c51bd0667db57cfb0d3f09/ghc >--------------------------------------------------------------- commit d260eb5541a5cad422c51bd0667db57cfb0d3f09 Author: Moritz Angermann Date: Mon Feb 5 10:30:53 2018 +0800 bump hadrian & Cabal >--------------------------------------------------------------- d260eb5541a5cad422c51bd0667db57cfb0d3f09 hadrian | 2 +- libraries/Cabal | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/hadrian b/hadrian index 323212d..13989a1 160000 --- a/hadrian +++ b/hadrian @@ -1 +1 @@ -Subproject commit 323212d071d02e9435fb2c1eb3c47edd13cba195 +Subproject commit 13989a1bc03eb86733f57e3199011ee319af97c9 diff --git a/libraries/Cabal b/libraries/Cabal index d2cf3f1..173d608 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit d2cf3f13dad9f1172cf9371ea197d1204e9e17a2 +Subproject commit 173d608a33784dab64fa100f94b6a366cf78f559 From git at git.haskell.org Wed Feb 7 06:40:29 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Feb 2018 06:40:29 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: bump (52e658a) Message-ID: <20180207064029.52C863A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/52e658af57869e6ee73c087811d9cf212b49381d/ghc >--------------------------------------------------------------- commit 52e658af57869e6ee73c087811d9cf212b49381d Author: Moritz Angermann Date: Mon Feb 5 14:15:35 2018 +0800 bump >--------------------------------------------------------------- 52e658af57869e6ee73c087811d9cf212b49381d libraries/Cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Cabal b/libraries/Cabal index 173d608..d039b9b 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit 173d608a33784dab64fa100f94b6a366cf78f559 +Subproject commit d039b9b5a318292c5a9cfab177650e26eba85cbd From git at git.haskell.org Wed Feb 7 06:40:23 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Feb 2018 06:40:23 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: Meh, Cabal. (3e37a87) Message-ID: <20180207064023.B93AA3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/3e37a87a1a38f3e6fc74a013bca2d853928b1e0c/ghc >--------------------------------------------------------------- commit 3e37a87a1a38f3e6fc74a013bca2d853928b1e0c Author: Moritz Angermann Date: Mon Feb 5 12:34:03 2018 +0800 Meh, Cabal. >--------------------------------------------------------------- 3e37a87a1a38f3e6fc74a013bca2d853928b1e0c rts/rts.cabal.in | 4 ++-- utils/hp2ps/hp2ps.cabal | 6 +++--- utils/touchy/touchy.cabal | 4 ++-- utils/unlit/unlit.cabal | 4 ++-- 4 files changed, 9 insertions(+), 9 deletions(-) diff --git a/rts/rts.cabal.in b/rts/rts.cabal.in index b33a5f4..e986484 100644 --- a/rts/rts.cabal.in +++ b/rts/rts.cabal.in @@ -1,7 +1,7 @@ -cabal-version: >= 2.1 +cabal-version: 2.1 name: rts version: 1.0 -license: BSD3 +license: BSD-3-Clause maintainer: glasgow-haskell-users at haskell.org build-type: Simple flag libm diff --git a/utils/hp2ps/hp2ps.cabal b/utils/hp2ps/hp2ps.cabal index ba5db04..b4062b2 100644 --- a/utils/hp2ps/hp2ps.cabal +++ b/utils/hp2ps/hp2ps.cabal @@ -1,8 +1,8 @@ -cabal-version: >=2.1 +cabal-version: 2.1 Name: hp2ps Version: 0.1 Copyright: XXX -License: BSD3 +license: BSD-3-Clause Author: XXX Maintainer: XXX Synopsis: Heap Profile to PostScript converter @@ -10,7 +10,7 @@ Description: XXX Category: Development build-type: Simple -Executable unlit +Executable hp2ps Default-Language: Haskell2010 Main-Is: Main.c extra-libraries: m diff --git a/utils/touchy/touchy.cabal b/utils/touchy/touchy.cabal index ab025e4..377051e 100644 --- a/utils/touchy/touchy.cabal +++ b/utils/touchy/touchy.cabal @@ -1,8 +1,8 @@ -cabal-version: >=2.1 +cabal-version: 2.1 Name: touchy Version: 0.1 Copyright: XXX -License: BSD3 +License: BSD-3-Clause Author: XXX Maintainer: XXX Synopsis: @touch@ for windows diff --git a/utils/unlit/unlit.cabal b/utils/unlit/unlit.cabal index e15a075..a621f04 100644 --- a/utils/unlit/unlit.cabal +++ b/utils/unlit/unlit.cabal @@ -1,8 +1,8 @@ -cabal-version: >=2.1 +cabal-version: 2.1 Name: unlit Version: 0.1 Copyright: XXX -License: BSD3 +License: BSD-3-Clause Author: XXX Maintainer: XXX Synopsis: Literate program filter From git at git.haskell.org Wed Feb 7 06:40:26 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Feb 2018 06:40:26 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: bump hadrian (again) (19d9834) Message-ID: <20180207064026.7E7C23A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/19d9834daf4ef6a31a01c54b38f751709b6d2687/ghc >--------------------------------------------------------------- commit 19d9834daf4ef6a31a01c54b38f751709b6d2687 Author: Moritz Angermann Date: Mon Feb 5 12:35:02 2018 +0800 bump hadrian (again) >--------------------------------------------------------------- 19d9834daf4ef6a31a01c54b38f751709b6d2687 hadrian | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/hadrian b/hadrian index 13989a1..b81a0fb 160000 --- a/hadrian +++ b/hadrian @@ -1 +1 @@ -Subproject commit 13989a1bc03eb86733f57e3199011ee319af97c9 +Subproject commit b81a0fb58aa53e23362d2684aacbe9daf6629aba From git at git.haskell.org Wed Feb 7 06:40:32 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Feb 2018 06:40:32 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: bump cabal (again) (da93e00) Message-ID: <20180207064032.1ADBF3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/da93e00307b058cb08b14fe4a9880cf1e01aee02/ghc >--------------------------------------------------------------- commit da93e00307b058cb08b14fe4a9880cf1e01aee02 Author: Moritz Angermann Date: Mon Feb 5 16:06:30 2018 +0800 bump cabal (again) >--------------------------------------------------------------- da93e00307b058cb08b14fe4a9880cf1e01aee02 libraries/Cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Cabal b/libraries/Cabal index d039b9b..e992f76 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit d039b9b5a318292c5a9cfab177650e26eba85cbd +Subproject commit e992f765dbca8367b089ecf394cd71211279c9df From git at git.haskell.org Wed Feb 7 06:40:34 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Feb 2018 06:40:34 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: bump hadrian (why not?) (01d2975) Message-ID: <20180207064034.CE6503A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/01d2975d086ee78abbdb2e8e9d84da10a254972e/ghc >--------------------------------------------------------------- commit 01d2975d086ee78abbdb2e8e9d84da10a254972e Author: Moritz Angermann Date: Mon Feb 5 17:58:58 2018 +0800 bump hadrian (why not?) >--------------------------------------------------------------- 01d2975d086ee78abbdb2e8e9d84da10a254972e hadrian | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/hadrian b/hadrian index b81a0fb..19980b7 160000 --- a/hadrian +++ b/hadrian @@ -1 +1 @@ -Subproject commit b81a0fb58aa53e23362d2684aacbe9daf6629aba +Subproject commit 19980b7955f186fd5f42ace71bfbcd6fd4ae38ff From git at git.haskell.org Wed Feb 7 06:40:37 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Feb 2018 06:40:37 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: bump (8f33eb8) Message-ID: <20180207064037.A08F33A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/8f33eb877a5ac915dbf9ed6022c91e150c7b9b99/ghc >--------------------------------------------------------------- commit 8f33eb877a5ac915dbf9ed6022c91e150c7b9b99 Author: Moritz Angermann Date: Wed Feb 7 14:00:32 2018 +0800 bump >--------------------------------------------------------------- 8f33eb877a5ac915dbf9ed6022c91e150c7b9b99 hadrian | 2 +- libraries/Cabal | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/hadrian b/hadrian index 19980b7..65872d2 160000 --- a/hadrian +++ b/hadrian @@ -1 +1 @@ -Subproject commit 19980b7955f186fd5f42ace71bfbcd6fd4ae38ff +Subproject commit 65872d27a88d54bc0b155cf028139cc577bf3cbb diff --git a/libraries/Cabal b/libraries/Cabal index e992f76..8aa423f 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit e992f765dbca8367b089ecf394cd71211279c9df +Subproject commit 8aa423f907364b52a98804d6d18e52c0db330ba0 From git at git.haskell.org Wed Feb 7 06:40:40 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Feb 2018 06:40:40 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng's head updated: bump (8f33eb8) Message-ID: <20180207064040.C6BE03A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/angerman/llvmng' now includes: 273131d Export typeNat{Div;Mod;Log}TyCon from TcTypeNats e32f582 Fix #14578 by checking isCompoundHsType in more places ebf8e07 Make typeToLHsType produce kind signatures for tycon applications d87bb65 KQueue: Fix write notification requests being ignored... dfe049f Refactor kcHsTyVarBndrs 40a31b3 Fix SigTvs at the kind level 87e517c Check for bogus quantified tyvars in partial type sigs b586f77 Refactor coercion holes 594879d Fix floating of equalities 5124b04 Drop dead Given bindings in setImplicationStatus 0d40693 Add regression test for #14040 3d2664e Fix two more bugs in partial signatures 8553593 Fix previous patch 7c69f11 Simplify HsPatSynDetails 20afdaa Fix join-point decision b92fb51 Parenthesize forall-type args in cvtTypeKind be8d667 configure: Various cleanups 3e3a096 Blackholes can be large objects (#14497) da83722 Improve treatment of sectioned holes 96b52e6 Inform hole substitutions of typeclass constraints (fixes #14273). f28645c Fix hash in haddock of ghc-prim. 4eccca7 Remove executable filename check on windows 33e3b3e Fix #14681 and #14682 with precision-aimed parentheses 61db0b8 Update Cabal submodule 906983c Bump terminfo submodule c105095 tentative improvement to callstack docs b75f8d2 Add new mbmi and mbmi2 compiler flags 1d05e0c Fix #14692 by correcting an off-by-one error in TcGenDeriv b779e1a Bump process submodule f60ae5a Bump filepath submodule 309d632 Add ptr-eq short-cut to `compareByteArrays#` primitive d4d6e44 Fix Windows stack allocations. c60c659 Fix #14719 by using the setting the right SrcSpan 0c4d9e9 Bump pretty submodule e6c1474 Move zonkWC to the right place in simplfyInfer 77cdf60 Prioritise equalities when solving, incl deriveds d3573e4 Look inside implications in simplifyRule 2d1f6af SysTools: Add detection support for LLD linker f026b1c rts: Ensure that forkOS releases Task on termination fe485f2 Mark xmm6 as caller saved in the register allocator for windows. 8f668bd Don't add targets that can't be found in GHCi d6f2f23 testsuite: Fix test output of T14715 233c5ce testsuite: Fix test output broken by efba054640d3 42a82cf Haddock needs to pass visible modules for instance filtering 0e073e5 Option for LINE pragmas to get lexed into tokens 445554b Upgrade containers submodule 7a3a7ee ghc-prim: Emulate C11 atomics when not available b7f9139 Don't apply dataToTag's caseRules for data families 89830a3 integer-gmp: Simplify gmp/configure invocation 5acecda Bump stm submodule to 2.4.5.0 f0cae1f cmm: Revert more aggressive CBE due to #14226 054abe3 testsuite: Add testcase for #14754 111737c Bump transformers submodule to 0.5.5.0 3c276b5 Adds `smp` flag to rts.cabal. 79b25d1 adds -latomic to. ghc-prim afedb46 Move `iserv` into `utils` and change package name from `iserv-bin` to `iserv` 4eac8fe Adds test 7aa6057 replace git subtree with submodule. 41d9d2e Adds distrib/Makefile from @alpmestan 5f7ea11 Adds x86_64 android layout bc80dbe Adds `-llvmng` d91524d Use packed structs. 3cf9fd9 no tbaa ddf45c0 Add network submodule. 9fe4375 bump submodules d260eb5 bump hadrian & Cabal 3e37a87 Meh, Cabal. 19d9834 bump hadrian (again) 52e658a bump da93e00 bump cabal (again) 01d2975 bump hadrian (why not?) 8f33eb8 bump From git at git.haskell.org Wed Feb 7 09:56:10 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Feb 2018 09:56:10 +0000 (UTC) Subject: [commit: ghc] master: Fix utterly bogus TagToEnum rule in caseRules (4aa98f4) Message-ID: <20180207095610.1B2C83A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4aa98f4a3cb0c965c4df19af2f1ccc2c5483c3a5/ghc >--------------------------------------------------------------- commit 4aa98f4a3cb0c965c4df19af2f1ccc2c5483c3a5 Author: Simon Peyton Jones Date: Wed Feb 7 09:55:14 2018 +0000 Fix utterly bogus TagToEnum rule in caseRules In prelRules we had: tx_con_tte :: DynFlags -> AltCon -> AltCon tx_con_tte _ DEFAULT = DEFAULT tx_con_tte dflags (DataAlt dc) | tag == 0 = DEFAULT -- See Note [caseRules for tagToEnum] | otherwise = LitAlt (mkMachInt dflags (toInteger tag)) The tag==0 case is totally wrong, and led directly to Trac #14768. See "Beware" in Note [caseRules for tagToEnum] (in the patch). Easily fixed, though! >--------------------------------------------------------------- 4aa98f4a3cb0c965c4df19af2f1ccc2c5483c3a5 compiler/coreSyn/CoreLint.hs | 2 +- compiler/prelude/PrelRules.hs | 39 ++++++++++++++++++++++++++------------- compiler/simplCore/SimplUtils.hs | 28 +++++++++++++++++++++++++--- 3 files changed, 52 insertions(+), 17 deletions(-) diff --git a/compiler/coreSyn/CoreLint.hs b/compiler/coreSyn/CoreLint.hs index e83f839..b0d2ac3 100644 --- a/compiler/coreSyn/CoreLint.hs +++ b/compiler/coreSyn/CoreLint.hs @@ -1123,7 +1123,7 @@ checkCaseAlts e ty alts = where (con_alts, maybe_deflt) = findDefault alts - -- Check that successive alternatives have increasing tags + -- Check that successive alternatives have strictly increasing tags increasing_tag (alt1 : rest@( alt2 : _)) = alt1 `ltAlt` alt2 && increasing_tag rest increasing_tag _ = True diff --git a/compiler/prelude/PrelRules.hs b/compiler/prelude/PrelRules.hs index 49cd9fa..c9a3bc7 100644 --- a/compiler/prelude/PrelRules.hs +++ b/compiler/prelude/PrelRules.hs @@ -1500,13 +1500,10 @@ adjustUnary op _ -> Nothing tx_con_tte :: DynFlags -> AltCon -> AltCon -tx_con_tte _ DEFAULT = DEFAULT -tx_con_tte dflags (DataAlt dc) - | tag == 0 = DEFAULT -- See Note [caseRules for tagToEnum] - | otherwise = LitAlt (mkMachInt dflags (toInteger tag)) - where - tag = dataConTagZ dc -tx_con_tte _ alt = pprPanic "caseRules" (ppr alt) +tx_con_tte _ DEFAULT = DEFAULT +tx_con_tte _ alt@(LitAlt {}) = pprPanic "caseRules" (ppr alt) +tx_con_tte dflags (DataAlt dc) -- See Note [caseRules for tagToEnum] + = LitAlt $ mkMachInt dflags $ toInteger $ dataConTagZ dc tx_con_dtt :: Type -> AltCon -> AltCon tx_con_dtt _ DEFAULT = DEFAULT @@ -1525,18 +1522,34 @@ We want to transform into case x of 0# -> e1 - 1# -> e1 + 1# -> e2 This rule eliminates a lot of boilerplate. For - if (x>y) then e1 else e2 + if (x>y) then e2 else e1 we generate case tagToEnum (x ># y) of - False -> e2 - True -> e1 + False -> e1 + True -> e2 and it is nice to then get rid of the tagToEnum. -NB: in SimplUtils, where we invoke caseRules, - we convert that 0# to DEFAULT +Beware (Trac #14768): avoid the temptation to map constructor 0 to +DEFAULT, in the hope of getting this + case (x ># y) of + DEFAULT -> e1 + 1# -> e2 +That fails utterly in the case of + data Colour = Red | Green | Blue + case tagToEnum x of + DEFAULT -> e1 + Red -> e2 + +We don't want to get this! + case x of + DEFAULT -> e1 + DEFAULT -> e2 + +Instead, we deal with turning one branch into DEAFULT in SimplUtils +(add_default in mkCase3). Note [caseRules for dataToTag] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ diff --git a/compiler/simplCore/SimplUtils.hs b/compiler/simplCore/SimplUtils.hs index d86adbb..cc72f7a 100644 --- a/compiler/simplCore/SimplUtils.hs +++ b/compiler/simplCore/SimplUtils.hs @@ -2165,12 +2165,34 @@ mkCase2 dflags scrut bndr alts_ty alts re_sort alts = sortBy cmpAlt alts -- preserve the #case_invariants# add_default :: [CoreAlt] -> [CoreAlt] - -- TagToEnum may change a boolean True/False set of alternatives - -- to LitAlt 0#/1# alternatives. But literal alternatives always - -- have a DEFAULT (I think). So add it. + -- See Note [Literal cases] add_default ((LitAlt {}, bs, rhs) : alts) = (DEFAULT, bs, rhs) : alts add_default alts = alts +{- Note [Literal cases] +~~~~~~~~~~~~~~~~~~~~~~~ +If we have + case tagToEnum (a ># b) of + False -> e1 + True -> e2 + +then caseRules for TagToEnum will turn it into + case tagToEnum (a ># b) of + 0# -> e1 + 1# -> e2 + +Since the case is exhaustive (all cases are) we can convert it to + case tagToEnum (a ># b) of + DEFAULT -> e1 + 1# -> e2 + +This may generate sligthtly better code (although it should not, since +all cases are exhaustive) and/or optimise better. I'm not certain that +it's necessary, but currenty we do make this change. We do it here, +NOT in the TagToEnum rules (see "Beware" in Note [caseRules for tagToEnum] +in PrelRules) +-} + -------------------------------------------------- -- Catch-all -------------------------------------------------- From git at git.haskell.org Wed Feb 7 12:16:33 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Feb 2018 12:16:33 +0000 (UTC) Subject: [commit: ghc] master: Comments only (41d29d5) Message-ID: <20180207121633.E4BD23A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/41d29d5ad100d4c8bf4d2175c11cc710b23843da/ghc >--------------------------------------------------------------- commit 41d29d5ad100d4c8bf4d2175c11cc710b23843da Author: Simon Peyton Jones Date: Wed Feb 7 11:56:58 2018 +0000 Comments only >--------------------------------------------------------------- 41d29d5ad100d4c8bf4d2175c11cc710b23843da compiler/typecheck/TcValidity.hs | 14 ++++++++++---- compiler/types/Type.hs | 4 ++++ 2 files changed, 14 insertions(+), 4 deletions(-) diff --git a/compiler/typecheck/TcValidity.hs b/compiler/typecheck/TcValidity.hs index 8c01460..3bf9f52 100644 --- a/compiler/typecheck/TcValidity.hs +++ b/compiler/typecheck/TcValidity.hs @@ -727,19 +727,25 @@ check_pred_help under_syn env dflags ctxt pred | Just pred' <- tcView pred -- Switch on under_syn when going under a -- synonym (Trac #9838, yuk) = check_pred_help True env dflags ctxt pred' - | otherwise + + | otherwise -- A bit like classifyPredType, but not the same + -- E.g. we treat (~) like (~#); and we look inside tuples = case splitTyConApp_maybe pred of Just (tc, tys) | isTupleTyCon tc -> check_tuple_pred under_syn env dflags ctxt pred tys - -- NB: this equality check must come first, because (~) is a class, - -- too. + | tc `hasKey` heqTyConKey || tc `hasKey` eqTyConKey || tc `hasKey` eqPrimTyConKey + -- NB: this equality check must come first, + -- because (~) is a class,too. -> check_eq_pred env dflags pred tc tys + | Just cls <- tyConClass_maybe tc - -> check_class_pred env dflags ctxt pred cls tys -- Includes Coercible + -- Includes Coercible + -> check_class_pred env dflags ctxt pred cls tys + _ -> check_irred_pred under_syn env dflags ctxt pred check_eq_pred :: TidyEnv -> DynFlags -> PredType -> TyCon -> [TcType] -> TcM () diff --git a/compiler/types/Type.hs b/compiler/types/Type.hs index 3f893db..3ee8a4a 100644 --- a/compiler/types/Type.hs +++ b/compiler/types/Type.hs @@ -1750,6 +1750,10 @@ eqRelRole ReprEq = Representational data PredTree = ClassPred Class [Type] | EqPred EqRel Type Type | IrredPred PredType + -- NB: There is no TuplePred case + -- Tuple predicates like (Eq a, Ord b) are just treated + -- as ClassPred, as if we had a tuple class with two superclasses + -- class (c1, c2) => (%,%) c1 c2 classifyPredType :: PredType -> PredTree classifyPredType ev_ty = case splitTyConApp_maybe ev_ty of From git at git.haskell.org Wed Feb 7 12:16:37 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Feb 2018 12:16:37 +0000 (UTC) Subject: [commit: ghc] master: Fix solveOneFromTheOther for RecursiveSuperclasses (6506980) Message-ID: <20180207121637.B0DBB3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/65069806ea3637882d584e785dcb9e650271e4b6/ghc >--------------------------------------------------------------- commit 65069806ea3637882d584e785dcb9e650271e4b6 Author: Simon Peyton Jones Date: Wed Feb 7 11:57:40 2018 +0000 Fix solveOneFromTheOther for RecursiveSuperclasses This patch fixes the redundant superclass expansion in Trac #14774. The main change is to fix TcInterac.solveOneFromTheOther, so that it does not prefer a work-item with a binding if that binding transitively depends on the inert item we are comparing it with. Explained in Note [Replacement vs keeping] in TcInert, esp item (c) of the "Constraints coming from the same level" part. To make this work I refactored out a new function TcEvidence.findNeededEvVars, which was previously buried inside TcSimplify.neededEvVars. I added quite a few more comments and signposts about superclass expansion. >--------------------------------------------------------------- 65069806ea3637882d584e785dcb9e650271e4b6 compiler/typecheck/TcCanonical.hs | 43 +++++++++++++++----- compiler/typecheck/TcEvidence.hs | 29 ++++++++++++- compiler/typecheck/TcInteract.hs | 47 ++++++++++++++-------- compiler/typecheck/TcSimplify.hs | 22 +++------- testsuite/tests/typecheck/should_compile/Makefile | 4 ++ testsuite/tests/typecheck/should_compile/T14774.hs | 13 ++++++ .../tests/typecheck/should_compile/T14774.stdout | 3 ++ testsuite/tests/typecheck/should_compile/all.T | 1 + 8 files changed, 119 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 65069806ea3637882d584e785dcb9e650271e4b6 From git at git.haskell.org Wed Feb 7 19:30:13 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Feb 2018 19:30:13 +0000 (UTC) Subject: [commit: ghc] master: Use SPDX syntax in rts/package.conf.in (be53d19) Message-ID: <20180207193013.5D9C43A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/be53d19e08c8b6db338c9027db5a0635f470f32f/ghc >--------------------------------------------------------------- commit be53d19e08c8b6db338c9027db5a0635f470f32f Author: Herbert Valerio Riedel Date: Wed Feb 7 18:36:13 2018 +0100 Use SPDX syntax in rts/package.conf.in This was an oversight from 2671cccde749ed64129097358f81bff43480cdb9 as it wasn't obvious to assume one would go the trouble to manually construct the pkg-db entries... :-) >--------------------------------------------------------------- be53d19e08c8b6db338c9027db5a0635f470f32f rts/package.conf.in | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/rts/package.conf.in b/rts/package.conf.in index 1746af5..15b8ac2 100644 --- a/rts/package.conf.in +++ b/rts/package.conf.in @@ -8,7 +8,7 @@ name: rts version: 1.0 id: rts key: rts -license: BSD3 +license: BSD-3-Clause maintainer: glasgow-haskell-users at haskell.org exposed: True From git at git.haskell.org Thu Feb 8 00:04:57 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Feb 2018 00:04:57 +0000 (UTC) Subject: [commit: ghc] master: rts: fix barf format attribute (059596d) Message-ID: <20180208000457.512203A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/059596df51619314a2e240af618fe7f4d2550ff2/ghc >--------------------------------------------------------------- commit 059596df51619314a2e240af618fe7f4d2550ff2 Author: Douglas Wilson Date: Thu Feb 8 00:03:28 2018 +0000 rts: fix barf format attribute Summary: See definition of PRINTF above the change Reviewers: bgamari, erikd, simonmar, Phyx Reviewed By: Phyx Subscribers: Phyx, rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4392 >--------------------------------------------------------------- 059596df51619314a2e240af618fe7f4d2550ff2 includes/rts/Messages.h | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/includes/rts/Messages.h b/includes/rts/Messages.h index 206d40f..c3199b2 100644 --- a/includes/rts/Messages.h +++ b/includes/rts/Messages.h @@ -41,7 +41,7 @@ */ void barf(const char *s, ...) GNUC3_ATTRIBUTE(__noreturn__) - GNUC3_ATTRIBUTE(format(printf, 1, 2)); + GNUC3_ATTRIBUTE(format(PRINTF, 1, 2)); void vbarf(const char *s, va_list ap) GNUC3_ATTRIBUTE(__noreturn__); From git at git.haskell.org Thu Feb 8 00:11:25 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Feb 2018 00:11:25 +0000 (UTC) Subject: [commit: nofib] master: Recognize shells reporting as MINGW under windows. (1364fe6) Message-ID: <20180208001126.006563A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/nofib On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1364fe623f9216108a285a8804a27bdd8dfea3c4/nofib >--------------------------------------------------------------- commit 1364fe623f9216108a285a8804a27bdd8dfea3c4 Author: klebinger.andreas at gmx.at Date: Thu Feb 8 00:09:55 2018 +0000 Recognize shells reporting as MINGW under windows. Summary: My msys instance at least reports MINGW instead of MSYS for uname. This commit adjusts the regex to match either one. Without this some errors occur because of missing .exe extensions in file names. This fixes #14654 Test Plan: make Reviewers: O26 nofib, Phyx, bgamari Reviewed By: Phyx, bgamari Subscribers: bgamari, Phyx GHC Trac Issues: #14654 Differential Revision: https://phabricator.haskell.org/D4297 >--------------------------------------------------------------- 1364fe623f9216108a285a8804a27bdd8dfea3c4 mk/boilerplate.mk | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/mk/boilerplate.mk b/mk/boilerplate.mk index c2a5cd6..fa8b635 100644 --- a/mk/boilerplate.mk +++ b/mk/boilerplate.mk @@ -23,7 +23,7 @@ CONTEXT_DIFF_RAW = diff -U 1 EXECUTABLE_FILE = chmod +x # Windows MSYS specific settings -ifeq ($(shell uname -s | grep -c MSYS), 1) +ifeq ($(shell uname -s | grep -c 'MSYS\|MINGW'), 1) exeext=.exe CONTEXT_DIFF=$(CONTEXT_DIFF_RAW) --strip-trailing-cr else From git at git.haskell.org Thu Feb 8 14:56:40 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Feb 2018 14:56:40 +0000 (UTC) Subject: [commit: ghc] wip/T14626: Revert "WIP: alias only local symbols for now" (1167e50) Message-ID: <20180208145640.DBF753A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14626 Link : http://ghc.haskell.org/trac/ghc/changeset/1167e50f452e156f335ad146a9040ea93eae438a/ghc >--------------------------------------------------------------- commit 1167e50f452e156f335ad146a9040ea93eae438a Author: Gabor Greif Date: Mon Feb 5 16:48:11 2018 +0100 Revert "WIP: alias only local symbols for now" This reverts commit 0e7f9e574889e4e6e42ed44f629794a3f0c679bf. >--------------------------------------------------------------- 1167e50f452e156f335ad146a9040ea93eae438a compiler/nativeGen/X86/Ppr.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/compiler/nativeGen/X86/Ppr.hs b/compiler/nativeGen/X86/Ppr.hs index 02e8773..95c4728 100644 --- a/compiler/nativeGen/X86/Ppr.hs +++ b/compiler/nativeGen/X86/Ppr.hs @@ -151,7 +151,6 @@ pprDatas (_, Statics alias [CmmStaticLit lit@(CmmLabel lbl), CmmStaticLit ind, _ labelInd (CmmLabel l) = Just l labelInd _ = Nothing , Just ind' <- labelInd ind - , not $ externallyVisibleCLabel ind' -- trips ld64 otherwise , let equate = pprGloblDecl alias $$ text ".equiv" <+> ppr alias <> comma <> ppr (CmmLabel ind') = pprTrace "IndStaticInfo: pprDatas" (ppr alias <+> ppr lit <+> ppr ind') equate From git at git.haskell.org Thu Feb 8 14:56:43 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Feb 2018 14:56:43 +0000 (UTC) Subject: [commit: ghc] wip/T14626: Typo in comments (56cf68a) Message-ID: <20180208145643.B0BD73A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14626 Link : http://ghc.haskell.org/trac/ghc/changeset/56cf68a535cdb6a2480711e5402fc78ae229831d/ghc >--------------------------------------------------------------- commit 56cf68a535cdb6a2480711e5402fc78ae229831d Author: Gabor Greif Date: Wed Feb 7 16:54:38 2018 +0100 Typo in comments >--------------------------------------------------------------- 56cf68a535cdb6a2480711e5402fc78ae229831d compiler/basicTypes/PatSyn.hs | 2 +- compiler/cmm/CLabel.hs | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/basicTypes/PatSyn.hs b/compiler/basicTypes/PatSyn.hs index 35ba8e9..2e838d6 100644 --- a/compiler/basicTypes/PatSyn.hs +++ b/compiler/basicTypes/PatSyn.hs @@ -162,7 +162,7 @@ type (T [a] Bool). For example, this is ill-typed f :: T p q -> String f (P x) = "urk" -This is differnet to the situation with GADTs: +This is different to the situation with GADTs: data S a where MkS :: Int -> S Bool diff --git a/compiler/cmm/CLabel.hs b/compiler/cmm/CLabel.hs index 9170ee0..3c6beb4 100644 --- a/compiler/cmm/CLabel.hs +++ b/compiler/cmm/CLabel.hs @@ -1182,7 +1182,7 @@ pprCLbl (LargeSRTLabel u) = pprUniqueAlways u <> pp_cSEP <> text "srtd" pprCLbl (LargeBitmapLabel u) = text "b" <> pprUniqueAlways u <> pp_cSEP <> text "btm" -- Some bitsmaps for tuple constructors have a numeric tag (e.g. '7') -- until that gets resolved we'll just force them to start --- with a letter so the label will be legal assmbly code. +-- with a letter so the label will be legal assembly code. pprCLbl (CmmLabel _ str CmmCode) = ftext str From git at git.haskell.org Thu Feb 8 14:56:49 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Feb 2018 14:56:49 +0000 (UTC) Subject: [commit: ghc] wip/T14626: Minimal refactoring (d54c6d7) Message-ID: <20180208145649.3BD063A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14626 Link : http://ghc.haskell.org/trac/ghc/changeset/d54c6d7d27a9b3ba71b03d814d6a846736228fc5/ghc >--------------------------------------------------------------- commit d54c6d7d27a9b3ba71b03d814d6a846736228fc5 Author: Gabor Greif Date: Thu Feb 8 15:54:20 2018 +0100 Minimal refactoring >--------------------------------------------------------------- d54c6d7d27a9b3ba71b03d814d6a846736228fc5 compiler/cmm/CLabel.hs | 28 ++++++++++++++-------------- 1 file changed, 14 insertions(+), 14 deletions(-) diff --git a/compiler/cmm/CLabel.hs b/compiler/cmm/CLabel.hs index 3c6beb4..e0e3641 100644 --- a/compiler/cmm/CLabel.hs +++ b/compiler/cmm/CLabel.hs @@ -1268,21 +1268,21 @@ pprCLbl (PicBaseLabel {}) = panic "pprCLbl PicBaseLabel" pprCLbl (DeadStripPreventer {}) = panic "pprCLbl DeadStripPreventer" ppIdFlavor :: IdLabelInfo -> SDoc -ppIdFlavor x = pp_cSEP <> +ppIdFlavor x = pp_cSEP <> text (case x of - Closure -> text "closure" - SRT -> text "srt" - InfoTable -> text "info" - LocalInfoTable -> text "info" - Entry -> text "entry" - LocalEntry -> text "entry" - Slow -> text "slow" - RednCounts -> text "ct" - ConEntry -> text "con_entry" - ConInfoTable -> text "con_info" - ClosureTable -> text "closure_tbl" - Bytes -> text "bytes" - BlockInfoTable -> text "info" + Closure -> "closure" + SRT -> "srt" + InfoTable -> "info" + LocalInfoTable -> "info" + Entry -> "entry" + LocalEntry -> "entry" + Slow -> "slow" + RednCounts -> "ct" + ConEntry -> "con_entry" + ConInfoTable -> "con_info" + ClosureTable -> "closure_tbl" + Bytes -> "bytes" + BlockInfoTable -> "info" ) From git at git.haskell.org Thu Feb 8 14:56:46 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Feb 2018 14:56:46 +0000 (UTC) Subject: [commit: ghc] wip/T14626: WIP: only alias exported symbols when defined in the same module (03e0cc8) Message-ID: <20180208145646.7691F3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14626 Link : http://ghc.haskell.org/trac/ghc/changeset/03e0cc8284b4d9287efa3888fe6b9c0023c3526c/ghc >--------------------------------------------------------------- commit 03e0cc8284b4d9287efa3888fe6b9c0023c3526c Author: Gabor Greif Date: Thu Feb 8 11:32:43 2018 +0100 WIP: only alias exported symbols when defined in the same module >--------------------------------------------------------------- 03e0cc8284b4d9287efa3888fe6b9c0023c3526c compiler/nativeGen/X86/Ppr.hs | 25 ++++++++++++++++++++++++- 1 file changed, 24 insertions(+), 1 deletion(-) diff --git a/compiler/nativeGen/X86/Ppr.hs b/compiler/nativeGen/X86/Ppr.hs index 95c4728..0089a9b 100644 --- a/compiler/nativeGen/X86/Ppr.hs +++ b/compiler/nativeGen/X86/Ppr.hs @@ -45,6 +45,7 @@ import Unique ( pprUniqueAlways ) import Platform import FastString import Outputable +import Name ( nameModule_maybe, isExternalName, isInternalName ) import Data.Word @@ -143,6 +144,25 @@ pprBasicBlock info_env (BasicBlock blockid instrs) (l at LOCATION{} : _) -> pprInstr l _other -> empty + +aliasToLocalOrIntoThisModule :: CLabel -> CLabel -> Bool +aliasToLocalOrIntoThisModule alias lab + | Just nam <- hasHaskellName lab + , isStaticClosureLabel lab + , isExternalName nam + , Just mod <- nameModule_maybe nam + , Just anam <- hasHaskellName alias + , Just thismod <- nameModule_maybe anam + = thismod == mod + +aliasToLocalOrIntoThisModule _ lab + | Just nam <- hasHaskellName lab + , isInternalName nam + = True + +aliasToLocalOrIntoThisModule _ _ = True + + pprDatas :: (Alignment, CmmStatics) -> SDoc pprDatas (_, Statics alias [CmmStaticLit lit@(CmmLabel lbl), CmmStaticLit ind, _, _]) @@ -151,7 +171,10 @@ pprDatas (_, Statics alias [CmmStaticLit lit@(CmmLabel lbl), CmmStaticLit ind, _ labelInd (CmmLabel l) = Just l labelInd _ = Nothing , Just ind' <- labelInd ind - , let equate = pprGloblDecl alias $$ text ".equiv" <+> ppr alias <> comma <> ppr (CmmLabel ind') + , aliasToLocalOrIntoThisModule alias ind' + , let equate = pprGloblDecl alias + $$ pprTypeAndSizeDecl alias -- NOT NEEDED! + $$ text ".equiv" <+> ppr alias <> comma <> ppr (CmmLabel ind') = pprTrace "IndStaticInfo: pprDatas" (ppr alias <+> ppr lit <+> ppr ind') equate pprDatas (align, (Statics lbl dats)) From git at git.haskell.org Thu Feb 8 14:56:52 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Feb 2018 14:56:52 +0000 (UTC) Subject: [commit: ghc] wip/T14626: WIP: barf differently when a banged field is not tagged (fbb63fc) Message-ID: <20180208145652.0E9FF3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14626 Link : http://ghc.haskell.org/trac/ghc/changeset/fbb63fcb8bf8424ae5c07bc0d9257609794b16ce/ghc >--------------------------------------------------------------- commit fbb63fcb8bf8424ae5c07bc0d9257609794b16ce Author: Gabor Greif Date: Thu Feb 8 15:55:38 2018 +0100 WIP: barf differently when a banged field is not tagged >--------------------------------------------------------------- fbb63fcb8bf8424ae5c07bc0d9257609794b16ce compiler/codeGen/StgCmmCon.hs | 2 +- rts/Apply.cmm | 8 ++++++++ 2 files changed, 9 insertions(+), 1 deletion(-) diff --git a/compiler/codeGen/StgCmmCon.hs b/compiler/codeGen/StgCmmCon.hs index 6415370..2368f14 100644 --- a/compiler/codeGen/StgCmmCon.hs +++ b/compiler/codeGen/StgCmmCon.hs @@ -270,7 +270,7 @@ buildDynCon' dflags _ binder actually_bound ccs con args lgood lcall Nothing pprTrace "checkTagOnPtr" (ppr con $$ ppr (dataConRepType con)) emitLabel lcall emitRtsCall rtsUnitId - (fsLit "checkTagged") [(p, AddrHint)] False + (fsLit "checkBangTagged") [(p, AddrHint)] False emitLabel lgood checkTagOnPtr _ _ = pure () diff --git a/rts/Apply.cmm b/rts/Apply.cmm index 7bbf610..1c7c7bd 100644 --- a/rts/Apply.cmm +++ b/rts/Apply.cmm @@ -20,6 +20,14 @@ checkTagged ( P_ obj ) return(); } +checkBangTagged ( P_ obj ) +{ + if (GETTAG(obj)==0) { + ccall barf("BANG NOT TAGGED! ") never returns; + } + return(); +} + /* ---------------------------------------------------------------------------- * Evaluate a closure and return it. From git at git.haskell.org Thu Feb 8 14:58:52 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Feb 2018 14:58:52 +0000 (UTC) Subject: [commit: ghc] master: Fix isDroppableCt (Trac #14763) (6edafe3) Message-ID: <20180208145852.C93233A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6edafe3be0133fe69581fb3851a812c69ab9dbf7/ghc >--------------------------------------------------------------- commit 6edafe3be0133fe69581fb3851a812c69ab9dbf7 Author: Simon Peyton Jones Date: Thu Feb 8 14:24:11 2018 +0000 Fix isDroppableCt (Trac #14763) When finishing up an implication constraint, it's a bit tricky to decide which Derived constraints to retain (for error reporting) and which to discard. I got this wrong in commit f20cf982f126aea968ed6a482551550ffb6650cf (Remove wc_insol from WantedConstraints) The particular problem in Trac #14763 was that we were reporting as an error a fundep-generated constraint (ex ~ T) where 'ex' is an existentially-bound variable in a pattern match. But this isn't really an error at all. This patch fixes the problem. Indeed, since I had to understand this rather tricky code, I took the opportunity to clean it up and document better. See isDroppableCt :: Ct -> Bool and Note [Dropping derived constraints] I also removed wl_deriv altogether from the WorkList data type. It was there in the hope of gaining efficiency by not even processing lots of derived constraints, but it has turned out that most derived constraints (notably equalities) must be processed anyway; see Note [Prioritise equalities] in TcSMonad. The two are coupled because to decide which constraints to put in wl_deriv I was using another variant of isDroppableCt. Now it's much simpler -- and perhaps even more efficient too. >--------------------------------------------------------------- 6edafe3be0133fe69581fb3851a812c69ab9dbf7 compiler/typecheck/TcCanonical.hs | 15 ++- compiler/typecheck/TcErrors.hs | 2 +- compiler/typecheck/TcInteract.hs | 5 +- compiler/typecheck/TcRnTypes.hs | 109 +++++++++++++-------- compiler/typecheck/TcSMonad.hs | 109 +++++++-------------- testsuite/tests/typecheck/should_compile/T14763.hs | 34 +++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 7 files changed, 148 insertions(+), 127 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 6edafe3be0133fe69581fb3851a812c69ab9dbf7 From git at git.haskell.org Fri Feb 9 00:18:20 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Feb 2018 00:18:20 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: Use SPDX syntax in rts/package.conf.in (acc2a83) Message-ID: <20180209001820.8E0D03A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/acc2a837d3b0ea363643f073c07f01c965b20d24/ghc >--------------------------------------------------------------- commit acc2a837d3b0ea363643f073c07f01c965b20d24 Author: Herbert Valerio Riedel Date: Wed Feb 7 18:36:13 2018 +0100 Use SPDX syntax in rts/package.conf.in This was an oversight from 2671cccde749ed64129097358f81bff43480cdb9 as it wasn't obvious to assume one would go the trouble to manually construct the pkg-db entries... :-) (cherry picked from commit be53d19e08c8b6db338c9027db5a0635f470f32f) >--------------------------------------------------------------- acc2a837d3b0ea363643f073c07f01c965b20d24 rts/package.conf.in | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/rts/package.conf.in b/rts/package.conf.in index 52d7ef8..05d98a5 100644 --- a/rts/package.conf.in +++ b/rts/package.conf.in @@ -8,7 +8,7 @@ name: rts version: 1.0 id: rts key: rts -license: BSD3 +license: BSD-3-Clause maintainer: glasgow-haskell-users at haskell.org exposed: True From git at git.haskell.org Fri Feb 9 00:18:23 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Feb 2018 00:18:23 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: Fix utterly bogus TagToEnum rule in caseRules (4e0b4b3) Message-ID: <20180209001823.5AB703A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/4e0b4b36aca29b4d67df5f36d1a06bdfdfeec612/ghc >--------------------------------------------------------------- commit 4e0b4b36aca29b4d67df5f36d1a06bdfdfeec612 Author: Simon Peyton Jones Date: Wed Feb 7 09:55:14 2018 +0000 Fix utterly bogus TagToEnum rule in caseRules In prelRules we had: tx_con_tte :: DynFlags -> AltCon -> AltCon tx_con_tte _ DEFAULT = DEFAULT tx_con_tte dflags (DataAlt dc) | tag == 0 = DEFAULT -- See Note [caseRules for tagToEnum] | otherwise = LitAlt (mkMachInt dflags (toInteger tag)) The tag==0 case is totally wrong, and led directly to Trac #14768. See "Beware" in Note [caseRules for tagToEnum] (in the patch). Easily fixed, though! (cherry picked from commit 4aa98f4a3cb0c965c4df19af2f1ccc2c5483c3a5) >--------------------------------------------------------------- 4e0b4b36aca29b4d67df5f36d1a06bdfdfeec612 compiler/coreSyn/CoreLint.hs | 2 +- compiler/prelude/PrelRules.hs | 39 ++++++++++++++++++++++++++------------- compiler/simplCore/SimplUtils.hs | 28 +++++++++++++++++++++++++--- 3 files changed, 52 insertions(+), 17 deletions(-) diff --git a/compiler/coreSyn/CoreLint.hs b/compiler/coreSyn/CoreLint.hs index 17fa980..2665c1e 100644 --- a/compiler/coreSyn/CoreLint.hs +++ b/compiler/coreSyn/CoreLint.hs @@ -1123,7 +1123,7 @@ checkCaseAlts e ty alts = where (con_alts, maybe_deflt) = findDefault alts - -- Check that successive alternatives have increasing tags + -- Check that successive alternatives have strictly increasing tags increasing_tag (alt1 : rest@( alt2 : _)) = alt1 `ltAlt` alt2 && increasing_tag rest increasing_tag _ = True diff --git a/compiler/prelude/PrelRules.hs b/compiler/prelude/PrelRules.hs index 80a1145..b475637 100644 --- a/compiler/prelude/PrelRules.hs +++ b/compiler/prelude/PrelRules.hs @@ -1500,13 +1500,10 @@ adjustUnary op _ -> Nothing tx_con_tte :: DynFlags -> AltCon -> AltCon -tx_con_tte _ DEFAULT = DEFAULT -tx_con_tte dflags (DataAlt dc) - | tag == 0 = DEFAULT -- See Note [caseRules for tagToEnum] - | otherwise = LitAlt (mkMachInt dflags (toInteger tag)) - where - tag = dataConTagZ dc -tx_con_tte _ alt = pprPanic "caseRules" (ppr alt) +tx_con_tte _ DEFAULT = DEFAULT +tx_con_tte _ alt@(LitAlt {}) = pprPanic "caseRules" (ppr alt) +tx_con_tte dflags (DataAlt dc) -- See Note [caseRules for tagToEnum] + = LitAlt $ mkMachInt dflags $ toInteger $ dataConTagZ dc tx_con_dtt :: Type -> AltCon -> AltCon tx_con_dtt _ DEFAULT = DEFAULT @@ -1525,18 +1522,34 @@ We want to transform into case x of 0# -> e1 - 1# -> e1 + 1# -> e2 This rule eliminates a lot of boilerplate. For - if (x>y) then e1 else e2 + if (x>y) then e2 else e1 we generate case tagToEnum (x ># y) of - False -> e2 - True -> e1 + False -> e1 + True -> e2 and it is nice to then get rid of the tagToEnum. -NB: in SimplUtils, where we invoke caseRules, - we convert that 0# to DEFAULT +Beware (Trac #14768): avoid the temptation to map constructor 0 to +DEFAULT, in the hope of getting this + case (x ># y) of + DEFAULT -> e1 + 1# -> e2 +That fails utterly in the case of + data Colour = Red | Green | Blue + case tagToEnum x of + DEFAULT -> e1 + Red -> e2 + +We don't want to get this! + case x of + DEFAULT -> e1 + DEFAULT -> e2 + +Instead, we deal with turning one branch into DEAFULT in SimplUtils +(add_default in mkCase3). Note [caseRules for dataToTag] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ diff --git a/compiler/simplCore/SimplUtils.hs b/compiler/simplCore/SimplUtils.hs index f2cf7a6..9f652db 100644 --- a/compiler/simplCore/SimplUtils.hs +++ b/compiler/simplCore/SimplUtils.hs @@ -2153,12 +2153,34 @@ mkCase2 dflags scrut bndr alts_ty alts re_sort alts = sortBy cmpAlt alts -- preserve the #case_invariants# add_default :: [CoreAlt] -> [CoreAlt] - -- TagToEnum may change a boolean True/False set of alternatives - -- to LitAlt 0#/1# alterantives. But literal alternatives always - -- have a DEFAULT (I think). So add it. + -- See Note [Literal cases] add_default ((LitAlt {}, bs, rhs) : alts) = (DEFAULT, bs, rhs) : alts add_default alts = alts +{- Note [Literal cases] +~~~~~~~~~~~~~~~~~~~~~~~ +If we have + case tagToEnum (a ># b) of + False -> e1 + True -> e2 + +then caseRules for TagToEnum will turn it into + case tagToEnum (a ># b) of + 0# -> e1 + 1# -> e2 + +Since the case is exhaustive (all cases are) we can convert it to + case tagToEnum (a ># b) of + DEFAULT -> e1 + 1# -> e2 + +This may generate sligthtly better code (although it should not, since +all cases are exhaustive) and/or optimise better. I'm not certain that +it's necessary, but currenty we do make this change. We do it here, +NOT in the TagToEnum rules (see "Beware" in Note [caseRules for tagToEnum] +in PrelRules) +-} + -------------------------------------------------- -- Catch-all -------------------------------------------------- From git at git.haskell.org Fri Feb 9 17:15:36 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Feb 2018 17:15:36 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: Fix isDroppableCt (Trac #14763) (f2bb550) Message-ID: <20180209171536.8B8523A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/f2bb550eb745d57afbc574e02900653281ae0212/ghc >--------------------------------------------------------------- commit f2bb550eb745d57afbc574e02900653281ae0212 Author: Simon Peyton Jones Date: Thu Feb 8 14:24:11 2018 +0000 Fix isDroppableCt (Trac #14763) When finishing up an implication constraint, it's a bit tricky to decide which Derived constraints to retain (for error reporting) and which to discard. I got this wrong in commit f20cf982f126aea968ed6a482551550ffb6650cf (Remove wc_insol from WantedConstraints) The particular problem in Trac #14763 was that we were reporting as an error a fundep-generated constraint (ex ~ T) where 'ex' is an existentially-bound variable in a pattern match. But this isn't really an error at all. This patch fixes the problem. Indeed, since I had to understand this rather tricky code, I took the opportunity to clean it up and document better. See isDroppableCt :: Ct -> Bool and Note [Dropping derived constraints] I also removed wl_deriv altogether from the WorkList data type. It was there in the hope of gaining efficiency by not even processing lots of derived constraints, but it has turned out that most derived constraints (notably equalities) must be processed anyway; see Note [Prioritise equalities] in TcSMonad. The two are coupled because to decide which constraints to put in wl_deriv I was using another variant of isDroppableCt. Now it's much simpler -- and perhaps even more efficient too. (cherry picked from commit 6edafe3be0133fe69581fb3851a812c69ab9dbf7) >--------------------------------------------------------------- f2bb550eb745d57afbc574e02900653281ae0212 compiler/typecheck/TcCanonical.hs | 15 ++- compiler/typecheck/TcErrors.hs | 2 +- compiler/typecheck/TcInteract.hs | 5 +- compiler/typecheck/TcRnTypes.hs | 109 +++++++++++++-------- compiler/typecheck/TcSMonad.hs | 109 +++++++-------------- testsuite/tests/typecheck/should_compile/T14763.hs | 34 +++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 7 files changed, 148 insertions(+), 127 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc f2bb550eb745d57afbc574e02900653281ae0212 From git at git.haskell.org Sat Feb 10 07:12:05 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 10 Feb 2018 07:12:05 +0000 (UTC) Subject: [commit: ghc] master: Simplify Foreign.Marshal.Alloc functions with ScopedTypeVariables (f489c12) Message-ID: <20180210071205.6A8213A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f489c12c9fe4e24dce55269e6998323fd1d9b2a4/ghc >--------------------------------------------------------------- commit f489c12c9fe4e24dce55269e6998323fd1d9b2a4 Author: Ömer Sinan Ağacan Date: Sat Feb 10 09:12:42 2018 +0300 Simplify Foreign.Marshal.Alloc functions with ScopedTypeVariables Reviewers: hvr, bgamari, RyanGlScott Reviewed By: RyanGlScott Subscribers: RyanGlScott, rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4401 >--------------------------------------------------------------- f489c12c9fe4e24dce55269e6998323fd1d9b2a4 libraries/base/Foreign/Marshal/Alloc.hs | 35 +++++++++++---------------------- 1 file changed, 12 insertions(+), 23 deletions(-) diff --git a/libraries/base/Foreign/Marshal/Alloc.hs b/libraries/base/Foreign/Marshal/Alloc.hs index 2a3c756..48ed7fb 100644 --- a/libraries/base/Foreign/Marshal/Alloc.hs +++ b/libraries/base/Foreign/Marshal/Alloc.hs @@ -1,5 +1,6 @@ {-# LANGUAGE Trustworthy #-} -{-# LANGUAGE NoImplicitPrelude, MagicHash, UnboxedTuples #-} +{-# LANGUAGE NoImplicitPrelude, MagicHash, UnboxedTuples, + ScopedTypeVariables #-} ----------------------------------------------------------------------------- -- | @@ -79,20 +80,14 @@ import GHC.Base -- no longer required. -- {-# INLINE malloc #-} -malloc :: Storable a => IO (Ptr a) -malloc = doMalloc undefined - where - doMalloc :: Storable b => b -> IO (Ptr b) - doMalloc dummy = mallocBytes (sizeOf dummy) +malloc :: forall a . Storable a => IO (Ptr a) +malloc = mallocBytes (sizeOf (undefined :: a)) -- |Like 'malloc' but memory is filled with bytes of value zero. -- {-# INLINE calloc #-} -calloc :: Storable a => IO (Ptr a) -calloc = doCalloc undefined - where - doCalloc :: Storable b => b -> IO (Ptr b) - doCalloc dummy = callocBytes (sizeOf dummy) +calloc :: forall a . Storable a => IO (Ptr a) +calloc = callocBytes (sizeOf (undefined :: a)) -- |Allocate a block of memory of the given number of bytes. -- The block of memory is sufficiently aligned for any of the basic @@ -117,11 +112,9 @@ callocBytes size = failWhenNULL "calloc" $ _calloc 1 (fromIntegral size) -- exception), so the pointer passed to @f@ must /not/ be used after this. -- {-# INLINE alloca #-} -alloca :: Storable a => (Ptr a -> IO b) -> IO b -alloca = doAlloca undefined - where - doAlloca :: Storable a' => a' -> (Ptr a' -> IO b') -> IO b' - doAlloca dummy = allocaBytesAligned (sizeOf dummy) (alignment dummy) +alloca :: forall a b . Storable a => (Ptr a -> IO b) -> IO b +alloca = + allocaBytesAligned (sizeOf (undefined :: a)) (alignment (undefined :: a)) -- |@'allocaBytes' n f@ executes the computation @f@, passing as argument -- a pointer to a temporarily allocated block of memory of @n@ bytes. @@ -163,14 +156,10 @@ allocaBytesAligned (I# size) (I# align) action = IO $ \ s0 -> -- If the argument to 'realloc' is 'nullPtr', 'realloc' behaves like -- 'malloc'. -- -realloc :: Storable b => Ptr a -> IO (Ptr b) -realloc = doRealloc undefined +realloc :: forall a b . Storable b => Ptr a -> IO (Ptr b) +realloc ptr = failWhenNULL "realloc" (_realloc ptr size) where - doRealloc :: Storable b' => b' -> Ptr a' -> IO (Ptr b') - doRealloc dummy ptr = let - size = fromIntegral (sizeOf dummy) - in - failWhenNULL "realloc" (_realloc ptr size) + size = fromIntegral (sizeOf (undefined :: b)) -- |Resize a memory area that was allocated with 'malloc' or 'mallocBytes' -- to the given size. The returned pointer may refer to an entirely From git at git.haskell.org Mon Feb 12 11:03:27 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 12 Feb 2018 11:03:27 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: bump (d7a1766) Message-ID: <20180212110327.1051C3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/d7a1766bc5f4d4eb6ed1837f911fd615aa0f64b0/ghc >--------------------------------------------------------------- commit d7a1766bc5f4d4eb6ed1837f911fd615aa0f64b0 Author: Moritz Angermann Date: Thu Feb 8 16:10:55 2018 +0800 bump >--------------------------------------------------------------- d7a1766bc5f4d4eb6ed1837f911fd615aa0f64b0 libraries/Cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/Cabal b/libraries/Cabal index 8aa423f..767efff 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit 8aa423f907364b52a98804d6d18e52c0db330ba0 +Subproject commit 767efffd7c1bd2abf7477fe998ecac1f67d76774 From git at git.haskell.org Mon Feb 12 11:03:24 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 12 Feb 2018 11:03:24 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: Move __ATOMICS into ghc-prim (f6c3a94) Message-ID: <20180212110324.488533A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/f6c3a947f45836c8df98f764536298ee23d89e43/ghc >--------------------------------------------------------------- commit f6c3a947f45836c8df98f764536298ee23d89e43 Author: Moritz Angermann Date: Thu Feb 8 16:07:07 2018 +0800 Move __ATOMICS into ghc-prim >--------------------------------------------------------------- f6c3a947f45836c8df98f764536298ee23d89e43 aclocal.m4 | 18 ------------------ configure.ac | 5 ----- libraries/ghc-prim/Setup.hs | 2 +- libraries/ghc-prim/aclocal.m4 | 17 +++++++++++++++++ libraries/ghc-prim/configure.ac | 18 ++++++++++++++++++ libraries/ghc-prim/ghc-prim.buildinfo.in | 2 ++ libraries/ghc-prim/ghc-prim.cabal | 3 --- 7 files changed, 38 insertions(+), 27 deletions(-) diff --git a/aclocal.m4 b/aclocal.m4 index 99ff1bf..fc9d618 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -1281,24 +1281,6 @@ AC_SUBST(GccIsClang) rm -f conftest.txt ]) -# FP_GCC_SUPPORTS__ATOMICS -# ------------------------ -# Does gcc support the __atomic_* family of builtins? -AC_DEFUN([FP_GCC_SUPPORTS__ATOMICS], -[ - AC_REQUIRE([AC_PROG_CC]) - AC_MSG_CHECKING([whether GCC supports __atomic_ builtins]) - echo 'int test(int *x) { int y; __atomic_load(&x, &y, __ATOMIC_SEQ_CST); return x; }' > conftest.c - if $CC -c conftest.c > /dev/null 2>&1; then - CONF_GCC_SUPPORTS__ATOMICS=YES - AC_MSG_RESULT([yes]) - else - CONF_GCC_SUPPORTS__ATOMICS=NO - AC_MSG_RESULT([no]) - fi - rm -f conftest.c conftest.o -]) - # FP_GCC_SUPPORTS_NO_PIE # ---------------------- # Does gcc support the -no-pie option? If so we should pass it to gcc when diff --git a/configure.ac b/configure.ac index ec96d2c..a2c0a3c 100644 --- a/configure.ac +++ b/configure.ac @@ -712,11 +712,6 @@ FP_GCC_VERSION dnl ** See whether gcc supports -no-pie FP_GCC_SUPPORTS_NO_PIE -dnl ** Used to determine how to compile ghc-prim's atomics.c, used by -dnl unregisterised, Sparc, and PPC backends. -FP_GCC_SUPPORTS__ATOMICS -AC_DEFINE([HAVE_C11_ATOMICS], [$CONF_GCC_SUPPORTS__ATOMICS], [Does GCC support __atomic primitives?]) - FP_GCC_EXTRA_FLAGS dnl ** look to see if we have a C compiler using an llvm back end. diff --git a/libraries/ghc-prim/Setup.hs b/libraries/ghc-prim/Setup.hs index 5bb17e2..cccc416 100644 --- a/libraries/ghc-prim/Setup.hs +++ b/libraries/ghc-prim/Setup.hs @@ -18,7 +18,7 @@ import System.Exit import System.Directory main :: IO () -main = do let hooks = simpleUserHooks { +main = do let hooks = autoconfUserHooks { regHook = addPrimModule $ regHook simpleUserHooks, buildHook = build_primitive_sources diff --git a/libraries/ghc-prim/aclocal.m4 b/libraries/ghc-prim/aclocal.m4 new file mode 100644 index 0000000..e569538 --- /dev/null +++ b/libraries/ghc-prim/aclocal.m4 @@ -0,0 +1,17 @@ +# FP_GCC_SUPPORTS__ATOMICS +# ------------------------ +# Does gcc support the __atomic_* family of builtins? +AC_DEFUN([FP_GCC_SUPPORTS__ATOMICS], +[ + AC_REQUIRE([AC_PROG_CC]) + AC_MSG_CHECKING([whether GCC supports __atomic_ builtins]) + echo 'int test(int *x) { int y; __atomic_load(&x, &y, __ATOMIC_SEQ_CST); return x; }' > conftest.c + if $CC -c conftest.c > /dev/null 2>&1; then + CONF_GCC_SUPPORTS__ATOMICS=YES + AC_MSG_RESULT([yes]) + else + CONF_GCC_SUPPORTS__ATOMICS=NO + AC_MSG_RESULT([no]) + fi + rm -f conftest.c conftest.o +]) diff --git a/libraries/ghc-prim/configure.ac b/libraries/ghc-prim/configure.ac new file mode 100644 index 0000000..bacc89c --- /dev/null +++ b/libraries/ghc-prim/configure.ac @@ -0,0 +1,18 @@ +AC_INIT([ghc-prim package], [2.1], [glasgow-haskell-bugs at haskell.org], [ghc-prim]) + +AC_CONFIG_SRCDIR([ghc-prim.cabal]) + +# ------------------------------------------------------------------------- +dnl ** Used to determine how to compile ghc-prim's atomics.c, used by +dnl unregisterised, Sparc, and PPC backends. +FP_GCC_SUPPORTS__ATOMICS +AC_DEFINE([HAVE_C11_ATOMICS], [$CONF_GCC_SUPPORTS__ATOMICS], [Does GCC support __atomic primitives?]) + +if test "x$CONF_GCC_SUPPORTS__ATOMICS" = YES +then PRIM_CFLAGS=-DHAVE_C11_ATOMICS + PRIM_EXTRA_LIBRARIES=atomic +fi +AC_SUBST([PRIM_CFLAGS]) +AC_SUBST([PRIM_EXTRA_LIBRARIES]) +AC_CONFIG_FILES([ghc-prim.buildinfo]) +AC_OUTPUT diff --git a/libraries/ghc-prim/ghc-prim.buildinfo.in b/libraries/ghc-prim/ghc-prim.buildinfo.in new file mode 100644 index 0000000..a093282 --- /dev/null +++ b/libraries/ghc-prim/ghc-prim.buildinfo.in @@ -0,0 +1,2 @@ +cc-options: @PRIM_CFLAGS@ +extra-libraries: @PRIM_EXTRA_LIBRARIES@ \ No newline at end of file diff --git a/libraries/ghc-prim/ghc-prim.cabal b/libraries/ghc-prim/ghc-prim.cabal index 2b860e6..f395c9f 100644 --- a/libraries/ghc-prim/ghc-prim.cabal +++ b/libraries/ghc-prim/ghc-prim.cabal @@ -66,9 +66,6 @@ Library -- on Windows. Required because of mingw32. extra-libraries: user32, mingw32, mingwex - if os(linux) - extra-libraries: atomic - c-sources: cbits/atomic.c cbits/bswap.c From git at git.haskell.org Mon Feb 12 11:03:29 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 12 Feb 2018 11:03:29 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: No relative inclusion of HsVersions.h (ab91b37) Message-ID: <20180212110329.D59763A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/ab91b37fd161fa01d94c541725200698bbaccd4f/ghc >--------------------------------------------------------------- commit ab91b37fd161fa01d94c541725200698bbaccd4f Author: Moritz Angermann Date: Mon Feb 12 14:12:37 2018 +0800 No relative inclusion of HsVersions.h >--------------------------------------------------------------- ab91b37fd161fa01d94c541725200698bbaccd4f compiler/cmm/SMRep.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/cmm/SMRep.hs b/compiler/cmm/SMRep.hs index 1469ae1..c200eaa 100644 --- a/compiler/cmm/SMRep.hs +++ b/compiler/cmm/SMRep.hs @@ -47,7 +47,7 @@ module SMRep ( pprWord8String, stringToWord8s ) where -#include "../HsVersions.h" +#include "HsVersions.h" #include "../includes/MachDeps.h" import GhcPrelude From git at git.haskell.org Mon Feb 12 11:03:32 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 12 Feb 2018 11:03:32 +0000 (UTC) Subject: [commit: ghc] wip/angerman/llvmng: bump hadrian. (b4ee0b9) Message-ID: <20180212110332.A2FF13A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/llvmng Link : http://ghc.haskell.org/trac/ghc/changeset/b4ee0b9a8a96f2daafccf7e0ef2fa0207838bdaa/ghc >--------------------------------------------------------------- commit b4ee0b9a8a96f2daafccf7e0ef2fa0207838bdaa Author: Moritz Angermann Date: Mon Feb 12 14:34:39 2018 +0800 bump hadrian. >--------------------------------------------------------------- b4ee0b9a8a96f2daafccf7e0ef2fa0207838bdaa hadrian | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/hadrian b/hadrian index 65872d2..0355054 160000 --- a/hadrian +++ b/hadrian @@ -1 +1 @@ -Subproject commit 65872d27a88d54bc0b155cf028139cc577bf3cbb +Subproject commit 03550544162f23c4f5bb960e586c696cfedcaca1 From git at git.haskell.org Mon Feb 12 11:34:21 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 12 Feb 2018 11:34:21 +0000 (UTC) Subject: [commit: ghc] master: Evac.c: remove unused CPP guard (583f561) Message-ID: <20180212113421.7D4B23A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/583f561c285d1742b7e73128fd3331a49b87ec75/ghc >--------------------------------------------------------------- commit 583f561c285d1742b7e73128fd3331a49b87ec75 Author: Ömer Sinan Ağacan Date: Mon Feb 12 14:33:25 2018 +0300 Evac.c: remove unused CPP guard `NO_PROMOTE_THUNKS` is never defined >--------------------------------------------------------------- 583f561c285d1742b7e73128fd3331a49b87ec75 rts/sm/Evac.c | 3 --- 1 file changed, 3 deletions(-) diff --git a/rts/sm/Evac.c b/rts/sm/Evac.c index 738e3e4..bb54c7e 100644 --- a/rts/sm/Evac.c +++ b/rts/sm/Evac.c @@ -704,9 +704,6 @@ loop: case THUNK_1_1: case THUNK_2_0: case THUNK_0_2: -#if defined(NO_PROMOTE_THUNKS) -#error bitrotted -#endif copy(p,info,q,sizeofW(StgThunk)+2,gen_no); return; From git at git.haskell.org Mon Feb 12 18:04:39 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 12 Feb 2018 18:04:39 +0000 (UTC) Subject: [commit: ghc] wip/tdammers/T11735: Tighten cached role in NthCo (1146825) Message-ID: <20180212180439.99E6B3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tdammers/T11735 Link : http://ghc.haskell.org/trac/ghc/changeset/1146825a3f59da1f88401d61380328806b5b2c07/ghc >--------------------------------------------------------------- commit 1146825a3f59da1f88401d61380328806b5b2c07 Author: Richard Eisenberg Date: Mon Feb 12 13:02:23 2018 -0500 Tighten cached role in NthCo >--------------------------------------------------------------- 1146825a3f59da1f88401d61380328806b5b2c07 compiler/backpack/RnModIface.hs | 2 +- compiler/coreSyn/CoreLint.hs | 9 +-- compiler/coreSyn/CoreUtils.hs | 2 +- compiler/iface/IfaceSyn.hs | 2 +- compiler/iface/IfaceType.hs | 14 ++-- compiler/iface/TcIface.hs | 3 +- compiler/iface/ToIface.hs | 2 +- compiler/typecheck/TcEvidence.hs | 2 +- compiler/types/Coercion.hs | 158 +++++++++++++++++++++++++-------------- compiler/types/Coercion.hs-boot | 2 +- compiler/types/OptCoercion.hs | 23 ++---- compiler/types/TyCoRep.hs | 5 +- docs/core-spec/CoreLint.ott | 5 +- 13 files changed, 131 insertions(+), 98 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1146825a3f59da1f88401d61380328806b5b2c07 From git at git.haskell.org Tue Feb 13 01:03:09 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Feb 2018 01:03:09 +0000 (UTC) Subject: [commit: ghc] master: Make ($!) representation-polymorphic (c9a88db) Message-ID: <20180213010309.761143A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c9a88db3ac4f1c3e97e3492ebe076f2df6463540/ghc >--------------------------------------------------------------- commit c9a88db3ac4f1c3e97e3492ebe076f2df6463540 Author: David Feuer Date: Mon Feb 12 20:01:56 2018 -0500 Make ($!) representation-polymorphic Now that `($)` is representation-polymorphic, `($!)` should surely follow suit. Reviewers: hvr, bgamari, simonpj Reviewed By: bgamari, simonpj Subscribers: simonpj, rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4382 >--------------------------------------------------------------- c9a88db3ac4f1c3e97e3492ebe076f2df6463540 docs/users_guide/8.6.1-notes.rst | 2 ++ libraries/base/GHC/Base.hs | 4 ++-- libraries/base/changelog.md | 4 ++++ 3 files changed, 8 insertions(+), 2 deletions(-) diff --git a/docs/users_guide/8.6.1-notes.rst b/docs/users_guide/8.6.1-notes.rst index c17664f..e844ab6 100644 --- a/docs/users_guide/8.6.1-notes.rst +++ b/docs/users_guide/8.6.1-notes.rst @@ -49,6 +49,8 @@ Template Haskell ``base`` library ~~~~~~~~~~~~~~~~ +``($!)`` is now representation-polymorphic like ``($)``. + Build system ~~~~~~~~~~~~ diff --git a/libraries/base/GHC/Base.hs b/libraries/base/GHC/Base.hs index 7875fef..17d4151 100644 --- a/libraries/base/GHC/Base.hs +++ b/libraries/base/GHC/Base.hs @@ -1327,8 +1327,8 @@ f $ x = f x -- argument, evaluates the argument to weak head normal form (WHNF), then calls -- the function with that value. -($!) :: (a -> b) -> a -> b -f $! x = let !vx = x in f vx -- see #2273 +($!) :: forall r a (b :: TYPE r). (a -> b) -> a -> b +f $! x = let !vx = x in f vx -- see #2273 -- | @'until' p f@ yields the result of applying @f@ until @p@ holds. until :: (a -> Bool) -> (a -> a) -> a -> a diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index ad8767f..fe7e377 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -1,5 +1,9 @@ # Changelog for [`base` package](http://hackage.haskell.org/package/base) +## 4.12.0.0 *TBA* + + * `($!)` is now representation-polymorphic like `($)`. + ## 4.11.1.0 *TBA* * `System.IO.openTempFile` is now thread-safe on Windows. From git at git.haskell.org Tue Feb 13 06:54:05 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Feb 2018 06:54:05 +0000 (UTC) Subject: [commit: ghc] branch 'wip/angerman/reloc' created Message-ID: <20180213065405.12C9A3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/angerman/reloc Referencing: ee0a06d668ea6f87a32a28533596aaaaaa7ec3df From git at git.haskell.org Tue Feb 13 06:54:07 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Feb 2018 06:54:07 +0000 (UTC) Subject: [commit: ghc] wip/angerman/reloc: adds hadrian and cabal submodules (414225d) Message-ID: <20180213065407.DD5A13A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/reloc Link : http://ghc.haskell.org/trac/ghc/changeset/414225d57a4f2331c45a1ca9edef1294e858f75d/ghc >--------------------------------------------------------------- commit 414225d57a4f2331c45a1ca9edef1294e858f75d Author: Moritz Angermann Date: Tue Feb 13 13:45:00 2018 +0800 adds hadrian and cabal submodules >--------------------------------------------------------------- 414225d57a4f2331c45a1ca9edef1294e858f75d hadrian | 2 +- libraries/Cabal | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/hadrian b/hadrian index 63a5563..0355054 160000 --- a/hadrian +++ b/hadrian @@ -1 +1 @@ -Subproject commit 63a556382f4b3154ed2ce3a6c8a36f79d9b8e3b1 +Subproject commit 03550544162f23c4f5bb960e586c696cfedcaca1 diff --git a/libraries/Cabal b/libraries/Cabal index 578d3a5..767efff 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit 578d3a50db818223017b8891df268d4200b8ffd3 +Subproject commit 767efffd7c1bd2abf7477fe998ecac1f67d76774 From git at git.haskell.org Tue Feb 13 06:54:13 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Feb 2018 06:54:13 +0000 (UTC) Subject: [commit: ghc] wip/angerman/reloc: Meh, Cabal. (0ac0739) Message-ID: <20180213065413.747933A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/reloc Link : http://ghc.haskell.org/trac/ghc/changeset/0ac073970d27664d994675e009499ca7e4e6cac1/ghc >--------------------------------------------------------------- commit 0ac073970d27664d994675e009499ca7e4e6cac1 Author: Moritz Angermann Date: Mon Feb 5 12:34:03 2018 +0800 Meh, Cabal. >--------------------------------------------------------------- 0ac073970d27664d994675e009499ca7e4e6cac1 rts/rts.cabal.in | 4 ++-- utils/hp2ps/hp2ps.cabal | 6 +++--- utils/touchy/touchy.cabal | 4 ++-- utils/unlit/unlit.cabal | 4 ++-- 4 files changed, 9 insertions(+), 9 deletions(-) diff --git a/rts/rts.cabal.in b/rts/rts.cabal.in index ce9d751..a895c9c 100644 --- a/rts/rts.cabal.in +++ b/rts/rts.cabal.in @@ -1,7 +1,7 @@ -cabal-version: >= 2.1 +cabal-version: 2.1 name: rts version: 1.0 -license: BSD3 +license: BSD-3-Clause maintainer: glasgow-haskell-users at haskell.org build-type: Simple flag libm diff --git a/utils/hp2ps/hp2ps.cabal b/utils/hp2ps/hp2ps.cabal index ba5db04..b4062b2 100644 --- a/utils/hp2ps/hp2ps.cabal +++ b/utils/hp2ps/hp2ps.cabal @@ -1,8 +1,8 @@ -cabal-version: >=2.1 +cabal-version: 2.1 Name: hp2ps Version: 0.1 Copyright: XXX -License: BSD3 +license: BSD-3-Clause Author: XXX Maintainer: XXX Synopsis: Heap Profile to PostScript converter @@ -10,7 +10,7 @@ Description: XXX Category: Development build-type: Simple -Executable unlit +Executable hp2ps Default-Language: Haskell2010 Main-Is: Main.c extra-libraries: m diff --git a/utils/touchy/touchy.cabal b/utils/touchy/touchy.cabal index ab025e4..377051e 100644 --- a/utils/touchy/touchy.cabal +++ b/utils/touchy/touchy.cabal @@ -1,8 +1,8 @@ -cabal-version: >=2.1 +cabal-version: 2.1 Name: touchy Version: 0.1 Copyright: XXX -License: BSD3 +License: BSD-3-Clause Author: XXX Maintainer: XXX Synopsis: @touch@ for windows diff --git a/utils/unlit/unlit.cabal b/utils/unlit/unlit.cabal index e15a075..a621f04 100644 --- a/utils/unlit/unlit.cabal +++ b/utils/unlit/unlit.cabal @@ -1,8 +1,8 @@ -cabal-version: >=2.1 +cabal-version: 2.1 Name: unlit Version: 0.1 Copyright: XXX -License: BSD3 +License: BSD-3-Clause Author: XXX Maintainer: XXX Synopsis: Literate program filter From git at git.haskell.org Tue Feb 13 06:54:10 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Feb 2018 06:54:10 +0000 (UTC) Subject: [commit: ghc] wip/angerman/reloc: Adds `smp` flag to rts.cabal. (6c5a586) Message-ID: <20180213065410.A82EF3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/reloc Link : http://ghc.haskell.org/trac/ghc/changeset/6c5a586f8c5d85c18f5e7dd0eebd357fcc453548/ghc >--------------------------------------------------------------- commit 6c5a586f8c5d85c18f5e7dd0eebd357fcc453548 Author: Moritz Angermann Date: Sat Nov 25 20:49:56 2017 +0800 Adds `smp` flag to rts.cabal. >--------------------------------------------------------------- 6c5a586f8c5d85c18f5e7dd0eebd357fcc453548 rts/rts.cabal.in | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/rts/rts.cabal.in b/rts/rts.cabal.in index 53b6271..ce9d751 100644 --- a/rts/rts.cabal.in +++ b/rts/rts.cabal.in @@ -24,6 +24,8 @@ flag 64bit default: @Cabal64bit@ flag leading-underscore default: @CabalLeadingUnderscore@ +flag smp + default: True library -- rts is a wired in package and @@ -72,6 +74,8 @@ library if flag(libdw) -- for backtraces extra-libraries: elf dw + if !flag(smp) + cpp-options: -DNOSMP include-dirs: build ../includes includes includes/dist-derivedconstants/header @FFIIncludeDir@ From git at git.haskell.org Tue Feb 13 06:54:17 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Feb 2018 06:54:17 +0000 (UTC) Subject: [commit: ghc] wip/angerman/reloc: Move `iserv` into `utils` and change package name from `iserv-bin` to `iserv` (116f3d1) Message-ID: <20180213065417.821883A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/reloc Link : http://ghc.haskell.org/trac/ghc/changeset/116f3d1e8659fd122871f70ada43d539de239fa1/ghc >--------------------------------------------------------------- commit 116f3d1e8659fd122871f70ada43d539de239fa1 Author: Moritz Angermann Date: Sat Nov 25 15:10:52 2017 +0800 Move `iserv` into `utils` and change package name from `iserv-bin` to `iserv` This is done for consistency. We usually call the package file the same name the folder has. The move into `utils` is done so that we can move the library into `libraries/iserv` and the proxy into `utils/iserv-proxy` and then break the `iserv.cabal` apart. This will make building the cross compiler with TH simpler, because we can build the library and proxy as separate packages. # Conflicts: # utils/iserv-proxy/iserv-proxy.cabal >--------------------------------------------------------------- 116f3d1e8659fd122871f70ada43d539de239fa1 ghc.mk | 13 +-- {iserv => libraries/libiserv}/Makefile | 0 {iserv => libraries/libiserv}/cbits/iservmain.c | 0 libraries/libiserv/ghc.mk | 5 + libraries/libiserv/libiserv.cabal | 39 +++++++ {iserv => libraries/libiserv}/proxy-src/Remote.hs | 0 {iserv => libraries/libiserv}/src/GHCi/Utils.hsc | 0 {iserv => libraries/libiserv}/src/Lib.hs | 0 {iserv => libraries/libiserv}/src/Main.hs | 0 .../libiserv}/src/Remote/Message.hs | 0 {iserv => libraries/libiserv}/src/Remote/Slave.hs | 0 {iserv => utils/iserv-proxy}/Makefile | 0 utils/iserv-proxy/ghc.mk | 113 +++++++++++++++++++++ .../iserv-proxy/iserv-proxy.cabal | 72 +------------ .../Remote.hs => utils/iserv-proxy/src/Main.hs | 0 {iserv => utils/iserv}/Makefile | 0 {iserv => utils/iserv}/cbits/iservmain.c | 0 {iserv => utils/iserv}/ghc.mk | 66 ++++++------ utils/iserv/iserv.cabal | 44 ++++++++ {iserv => utils/iserv}/src/Main.hs | 0 20 files changed, 246 insertions(+), 106 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 116f3d1e8659fd122871f70ada43d539de239fa1 From git at git.haskell.org Tue Feb 13 06:54:20 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Feb 2018 06:54:20 +0000 (UTC) Subject: [commit: ghc] wip/angerman/reloc: bump hadrian (-fllvmng) (ee0a06d) Message-ID: <20180213065420.4DD0F3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/reloc Link : http://ghc.haskell.org/trac/ghc/changeset/ee0a06d668ea6f87a32a28533596aaaaaa7ec3df/ghc >--------------------------------------------------------------- commit ee0a06d668ea6f87a32a28533596aaaaaa7ec3df Author: Moritz Angermann Date: Tue Feb 13 14:49:54 2018 +0800 bump hadrian (-fllvmng) >--------------------------------------------------------------- ee0a06d668ea6f87a32a28533596aaaaaa7ec3df hadrian | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/hadrian b/hadrian index 0355054..e3d27af 160000 --- a/hadrian +++ b/hadrian @@ -1 +1 @@ -Subproject commit 03550544162f23c4f5bb960e586c696cfedcaca1 +Subproject commit e3d27af408bfd9cfa0557028b55457c224d03407 From git at git.haskell.org Tue Feb 13 07:03:19 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Feb 2018 07:03:19 +0000 (UTC) Subject: [commit: ghc] master: Collect CCs in CorePrep, including CCs in unfoldings (5957405) Message-ID: <20180213070319.294E53A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5957405808fe89e9b108dc0bc3cf4b56aec37775/ghc >--------------------------------------------------------------- commit 5957405808fe89e9b108dc0bc3cf4b56aec37775 Author: Ömer Sinan Ağacan Date: Tue Feb 13 09:03:57 2018 +0300 Collect CCs in CorePrep, including CCs in unfoldings This patch includes two changes: 1. Move cost centre collection from `SCCfinal` to `CorePrep`, to be able to collect cost centres in unfoldings. `CorePrep` drops unfoldings, so that's the latest stage in the compilation pipeline for this. After this change `SCCfinal` no longer collects all cost centres, but it still generates & collects CAF cost centres + updates cost centre stacks of `StgRhsClosure` and `StgRhsCon`s. This fixes #5889. 2. Initialize cost centre stack fields of `StgRhs` in `coreToStg`. With this we no longer need to update cost centre stack fields in `SCCfinal`, so that module is removed. Cost centre initialization explained in Note [Cost-centre initialization plan]. Because with -fcaf-all we need to attach a new cost-centre to each CAF, `coreTopBindToStg` now returns `CollectedCCs`. Test Plan: validate Reviewers: simonpj, bgamari, simonmar Reviewed By: simonpj, bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #5889 Differential Revision: https://phabricator.haskell.org/D4325 >--------------------------------------------------------------- 5957405808fe89e9b108dc0bc3cf4b56aec37775 compiler/coreSyn/CorePrep.hs | 58 ++++- compiler/deSugar/Coverage.hs | 9 +- compiler/ghc.cabal.in | 1 - compiler/main/HscMain.hs | 20 +- compiler/profiling/CostCentre.hs | 23 +- compiler/profiling/SCCfinal.hs | 284 --------------------- compiler/simplStg/SimplStg.hs | 47 +--- compiler/stgSyn/CoreToStg.hs | 227 +++++++++++----- testsuite/tests/profiling/should_compile/all.T | 2 +- .../simplCore/should_compile/noinline01.stderr | 16 +- 10 files changed, 258 insertions(+), 429 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 5957405808fe89e9b108dc0bc3cf4b56aec37775 From git at git.haskell.org Tue Feb 13 15:34:03 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Feb 2018 15:34:03 +0000 (UTC) Subject: [commit: ghc] wip/T14068: Merge branch 'master' of git://git.haskell.org/ghc into wip/T14068 (1f3da3b) Message-ID: <20180213153403.BBDD93A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14068 Link : http://ghc.haskell.org/trac/ghc/changeset/1f3da3b5bea004e75f9389796a2a537007291463/ghc >--------------------------------------------------------------- commit 1f3da3b5bea004e75f9389796a2a537007291463 Merge: f04fdcb 5957405 Author: Joachim Breitner Date: Tue Feb 13 10:19:52 2018 -0500 Merge branch 'master' of git://git.haskell.org/ghc into wip/T14068 >--------------------------------------------------------------- Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1f3da3b5bea004e75f9389796a2a537007291463 From git at git.haskell.org Tue Feb 13 15:34:07 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Feb 2018 15:34:07 +0000 (UTC) Subject: [commit: ghc] wip/T14068's head updated: Merge branch 'master' of git://git.haskell.org/ghc into wip/T14068 (1f3da3b) Message-ID: <20180213153407.A71263A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T14068' now includes: 29ae833 Tidy up IfaceEqualityTyCon 1317ba6 Implement the EmptyDataDeriving proposal 1130c67 PPC NCG: Impl branch prediction, atomic ops. b0b80e9 Implement the basics of hex floating point literals e0df569 Use proper Unique for Name b938576 Add custom exception for fixIO 36f0cb7 TcRnDriver: Bracket family instance consistency output in -ddump-rn-trace cbd6a4d Introduce -dsuppress-stg-free-vars flag bd765f4 Fix atomicread/write operations d9b6015 Revert "Move check-ppr and check-api-annotations to testsuite/utils" 51321cf rts/PrimOps.cmm: add declaration for heapOverflow closure 4353756 CmmSink: Use a IntSet instead of a list 15f788f llvmGen: Pass vector arguments in vector registers by default eb37132 Bump haddock submodule 3c8e55c Name TypeRep constructor fields 19ca2ca Deserialize all function TypeReps 5d48f7c Fix documentation and comment issues df479f7 change example from msum to mfilter 436b3ef Clean up comments about match algorithm a bit. f6521e6 testsuite: Bump metrics of haddock.Cabal 4dfb790 rts/win32: Emit exception handler output to stderr 6f990c5 cmm/CBE: Fix comparison between blocks of different lengths a27056f cmm/CBE: Fix a few more zip uses 2ded536 Typo in glasgow_exts.rst 35642f4 Update ErrorCall documentation for the location argument 8613e61 DynFlags: Introduce -show-mods-loaded flag 59de290 Update autoconf test for gcc to require 4.7 and up 66b5b3e Specialise lcm :: Word -> Word -> Word (trac#14424) 275ac8e base: Add examples to Bifunctor documentation 7b0b9f6 Squashed 'hadrian/' content from commit 438dc57 5cee480 Merge commit '7b0b9f603bb1215e2b7af23c2404d637b95a4988' as 'hadrian' 0ff152c WIP on combining Step 1 and 3 of Trees That Grow 7d6fa32 Set up Linux, OSX and FreeBSD on CircleCI. b0cabc9 Set up AppVeyor, Windows CI. 6f665cc Sdist -> bindist -> tests 07e0d0d Revert "Sdist -> bindist -> tests" ed18f47 Factor out builds into steps. Address ghc/ghc#83 comments. ae7c33f testsuite: Bump haddock.compiler allocations 7d34f69 relnotes: Clarify a few things c1bc923 relnotes: Note enabling of -fllvm-pass-vectorse-in-regs 93b4820 Revert "WIP on combining Step 1 and 3 of Trees That Grow" 9f8dde0 Update link to Haskeline user preferences bf9ba7b base: Escape \ in CallStack example 14d885e Merge remote-tracking branch 'github/pr/83' 21970de Imrpove comments about equality types 30058b0 Fix another dark corner in the shortcut solver 2c2f3ce Minimise provided dictionaries in pattern synonyms fe6848f Fix in-scope set in simplifier 438dd1c WIP on Doing a combined Step 1 and 3 for Trees That Grow 803ed03 Invoke lintUnfolding only on top-level unfoldings (#14430) 6bd352a Remove left-overs from compareByteArray# inline conversion 10ff3e3 testsuite: Fix output of T14394 bdd2d28 Update Win32 version for GHC 8.4. 9773053 Merge initial Hadrian snapshot ce9a677 base: Add test for #14425 c59d6da base: Normalize style of approxRational 5834da4 base: Fix #14425 0656cb4 Update comment in GHC.Real (trac#14432) 6b52b4c Remove unreliable Core Lint empty case checks e6b13c9 testsuite: Add test for #5889 75291ab Change `OPTIONS_GHC -O` to `OPTIONS_GHC -O2` f8e7fec Fix PPC NCG after blockID patch 5229c43 Squashed 'hadrian/' changes from 438dc576e7..5ebb69ae1e 506ba62 Merge commit '5229c43ccf77bcbffeced01dccb27398d017fa34' f11f252 Windows: Bump to GCC 7.2 for GHC 8.4 ba2ae2c Adds cmm-sources to base 426af53 Use LICENSE instead of ../LICENSE in the compiler.cabal file 5f158bc circleci: Bump down thread count 86c50a1 Declare proper spec version in `base.cabal` e3ec2e7 WIP on combined Step 1 and 3 for Trees That Grow, HsExpr 0a85190 Fix a TyVar bug in the flattener f570000 A bit more tc-tracing 47ad657 TTG3 Combined Step 1 and 3 for Trees That Grow f5dc8cc Add new mbmi and mbmi2 compiler flags 6dfe982 StaticPointers: Clarify documentation 5dea62f Adds rts/rts.cabal.in file 8b1020e RTS: Disable warnings in ffi.h ea26162 CLabel: Clean up unused label types 1aba27a CLabels: Remove CaseLabel 383016b Add dump flag for timing output d9f0c24 rts: Fix gc timing d0a641a Allow the rts lib to be called rts-1.0 3bed4aa Cabalify all the things e14945c Adjust AltCon Ord instance to match Core linter requirements. ec080ea users_guide: Fix "CancelSynchronousIo" casing c1fcd9b Squashed 'hadrian/' changes from 5ebb69a..fa3771f 07ac921 Pull recent Hadrian changes from upstream 2f46387 Detect overly long GC sync 2da7813 Document -ddump-timings c729734 configure: Fix incorrect quoting 12a7444 Adds -ghc-version flag to ghc. 835d8dd GHC.Prim use virtual-modules bb11a2d Relocatable GHC 74070bb Fix rts.cabal.in 912a72d Fix T4437 b8e324a base: Make documentation of atomically more accurate 7d16d8a Fix #elfi -> #elif; unbreak -Werror. ca3700a Rename ghc-version -> ghcversion-file 606bbc3 Stop generating make files when using hadrian. e66913d Bump hsc2hs submodule 25f36bd Bump haddock submodule ddded7e ghc-pkg: Add missing newlines to usage message 1b1ba9d rel-notes: Fix up formatting in release notes d213ee8 CircleCI: Disable artifact collection on OS X 66d1799 configure: Fix ar probed flags 0b20d9c base: Document GHC.Stack.CCS internals 314bc31 Revert "trees that grow" work 90a819b CircleCI: Add webhook for Harbormaster builds 2ca2259 Update ANNOUNCE 763ecac rts: Move libdwPrintBacktrace to public interface f376eba rts: Fix inconsistencies in how retainer and heap censuses are timed. 63e4ac3 Add warn-missing-export-lists 8a8a79a Update leftover reference to refer to [FunBind vs PatBind] dad9864 Remove hadrian sub-dir from .gitignore 0db4627 Test Trac #14488 bb2a08e testsuite: Add test for #14257 23116df cmm: Optimise remainders by powers of two eb5a40c base: Remove redundant subtraction in (^) and stimes 7a73a1c Bump stm submodule 2d1c671 ErrUtils: Refactor dump file logic c11f145 ErrUtils: Ensure timing dumps are always output on one line 360d740 Squashed 'hadrian/' changes from fa3771fe6b..4499b294e4 abdb555 Update Hadrian 341013e Revert "Add new mbmi and mbmi2 compiler flags" 5fdb858 Fix README 33cbc9f CircleCI: Perform nightly validation of unregisterised build 866f669 CircleCI: Try validating LLVM as well e2cc106 circleci: Build with Hadrian ad57e28 CircleCI: Install lbzip2 and patch 5e35627 rts/Printer: add closure name entries for small arrays (Fixes #14513) 30aa643 SysTools: Expand occurrences of $topdir anywhere in a Settings path 69cd1e9 SysTools: Split up TopDir logic into new module 599243e DynFlags: Expand $topdir in --info output 99089fc users-guide: Fix :default: placement f209e66 base: fdReady(): Fix timeouts > ~49 days overflowing. Fixes #14262. a1950e6 CircleCI: Reenable artifact collection on Darwin 471d677 Don't complain about UNPACK in -fno-code. 6282366 Follow symlinks in the Win32 code for System.Environment.getExecutablePath b241d6d Add obvious Outputable Integer instance. f713be7 RtsFlags: allow +RTS -K0 00b96b2 boot: Eliminate superfluous output 4efe5fe Check quantification for partial type signatues df1a0c0 typecheck: Consistently use pretty quotes in error messages eb86e86 Don't call alex for Cabal lib during GHC build e4dc2cd relnotes: Rework treatment of included package list 54fda25 base: Rip out old RTS statistics interface 17e71c1 CLabel.labelType: Make catch-all case explicit 048a913 cmm: Use LocalBlockLabel instead of AsmTempLabel to represent blocks 16dd532 CLabel: Refactor pprDynamicLinkerAsmLabel 55e621c nativeGen: Use plusUFMList instead of foldr 7dc82d6 nativeGen: Use foldl' instead of foldl 66c1c8e CLabel: More specific debug output from CLabel d3b80c7 Cmm: Add missing cases for BlockInfoTable 030d9d4 CLabel: A bit of documentation 4c65867 CircleCI: Disallow hscolour 1.24.3 3c0ffd1 CircleCI: Freeze all packages at fixed index state 5b3f33b Minor tweaks to codegens.rst b6428af Comments only: Trac #14511 b6a2691 Bump unix submodule f246d35 Darwin: Set deployment target d672b7f Darwin: Use gmp from homebrew 6998772 Make use of boot TyThings during typechecking. e1fb283 Handle CPP properly in Backpack 12efb23 Add trace injection bc761ad Cache TypeRep kinds aggressively 1acb922 Make the Con and Con' patterns produce evidence cfea745 template-haskell: Rip out FamFlavour 595f60f Fix ghc_packages d6fccfb Bump version to 8.5 30d6373 rts: fix filename case for mingw32 target 1ecbe9c utils/hsc2hs: update submodule 5f332e1 Forward-port changes from GHC 8.2 branch fa29df0 Refactor ConDecl: Trac #14529 e4a1f03 Revert accidental hsc2hs submodule downgrade de20440 Refactor kcHsTyVarBndrs 800009d Improve LiberateCase 5695f46 Occurrrence analysis improvements for NOINLINE functions 7733e44 Rip out hadrian subtree 4335c07 Add hadrian as a submodule 716acbb Improved panic message for zonkTcTyVarToTyVar 8b36ed1 Build only well-kinded types in type checker 8361b2c Fix SigTvs at the kind level abd5db6 Only look for locales of the form LL.VV 21be5bd Fixed misprint 'aqcuired' 6847c6b Improve Control.Monad.guard and Control.Monad.MonadPlus docs 00d7132 Add information about irrefutable pattern Syntax to XStrict. 21cdfe5 Add NOINLINE pragma to hPutStr' 4bfff7a rts: Don't default to single capability when profiled cafe983 Always use the safe open() call 708ed9c Allow users to ignore optimization changes 430d1f6 fdReady: Use C99 bools / CBool in signature 9d29925 base: fdReady(): Return only after sycall returns after `msecs` have passed be1ca0e Add regression test for #14040 a106a20 Minor refactor of TcExpr.tcApp e40db7b Detect levity-polymorphic uses of unsafeCoerce# 321b420 Tidy up of wired-in names aef4dee Add missing stderr for Trac #14561 63e968a Re-centre perf for T5321Fun 0a12d92 Further improvements to well-kinded types 6eb3257 Typofix in comment 6f6d105 Add test for Trac #14580 b1ea047 Fix an outright bug in the unflattener fa1afcd Better tc-trace messages eeb36eb typos in local var 16c7d9d Fix #14135 by validity checking matches d4c8d89 users-guide: Consistently document LLVM version requirement 4a331e6 users-guide: Fix various bits of markup 6814945 Fix tcDataKindSig 3910d3e Add some commentary re: fix to #11203 23b5b80 Add missing case to HsExpr.isMonadFailStmtContext 1e64fc8 Tiny refactor: use mkTyVarNamePairs f1fe5b4 Fix scoping of pattern-synonym existentials fb1f0a4 Blackholes can be large objects (#14497) 0302439 testsuite: Exit with non-zero exit code when tests fail 8c9906c testsuite: Semigroup/Monoid compat for T3001-2 244d144 Typos in comments a100763 Get rid of some stuttering in comments and docs 10ed319 Stop runRW# being magic ff1544d Rmove a call to mkStatePrimTy 71f96bb Sync up ghc-prim changelog from GHC 8.2 branch 1bd91a7 Fix #14578 by checking isCompoundHsType in more places 9caf40e Fix #14588 by checking for more bang patterns 9cb289a Remove hack put in place for #12512 b6304f8 Document ScopedTypeVariables' interaction with nested foralls 4d41e92 Improve treatment of sectioned holes 584cbd4 Simplify HsPatSynDetails 72938f5 Check for bogus quantified tyvars in partial type sigs a492af0 Refactor coercion holes f5cf9d1 Fix floating of equalities bcb519c Typos in comments 05551d0 Comments only [skip ci] fc257e4 Sync `ghc-prim` changelog from GHC 8.2 c88564d MkIface: Ensure syntactic compatibility with ghc 8.0.1 6549706 relnotes: Fix typo in pattern synonym example e237e1f Bump Cabal submodule d7d0aa3 Add GHC 8.6.1 release notes 02aaeab aclocal.m4: add minimal support for nios2 architecture e19b646 Compute InScopeSet in substInteractiveContext 722a658 Fix #14618 by applying a subst in deeplyInstantiate f2db228 Typos in comments [ci skip] 862c59e Rewrite Note [The polymorphism rule of join points] a2e9549 users-guide: Fix markup b31c721 Fix sign error in kelvinToC. 12f5c00 Prevent "C--" translating to "C–" in the User's Guide. 69f1e49 Reformat Control.Monad.mfilter docs a67c264 Add example to Control.Monad.join docs 4887c30 Improve Control.Monad docs 27b7b4d Windows: fix all failing tests. 46287af Make System.IO.openTempFile thread-safe on Windows ecff651 Fix #14608 by restoring an unboxed tuple check 3382ade Rename HEq_sc and Coercible_sc to heq_sel and coercible_sel 2c7b183 Comments only 83b96a4 More informative pretty-printing for phantom coercions f3a0fe2 Comments about join point types 1e12783 Tiny refactor around fillInferResult 3bf910d Small refactoring in Coercion 112266c White space only 9e5535c Fix OptCoercion bd438b2 Get evaluated-ness right in the back end 298ec78 No deferred type errors under a forall 7a25659 Typos in comments 649e777 Make typeToLHsType produce kind signatures for tycon applications 6c34824 Cache the number of data cons in DataTyCon and SumTyCon 954cbc7 Drop dead Given bindings in setImplicationStatus e2998d7 Stop double-stacktrace in ASSERT failures 86ea3b1 comments only 307d1df Fix deep, dark corner of pattern synonyms c732711 Improve pretty-printing for pattern synonyms 40cbab9 Fix another obscure pattern-synonym crash 303106d Make the Div and Mod type families `infixl 7` a1a689d Improve accuracy of get/setAllocationCounter fb78b0d Export typeNat{Div;Mod;Log}TyCon from TcTypeNats 30b1fe2 Remove a bogus warning 66ff794 Fix join-point decision 1c1e46c preInlineUnconditionally is ok for INLINEABLE 448685c Small local refactoring 1577908 Fix two more bugs in partial signatures dbdf77d Lift constructor tag allocation out of a loop f3f90a0 Fix previous patch 6c3eafb KQueue: Fix write notification requests being ignored... b2f10d8 Fix mistaken merge e20046a Support constructor Haddocks in more places a770226 Fix regression on i386 due to get/setAllocationCounter change d1ac1c3 Rename -frule-check to -drule-check and document 492e604 Kill off irrefutable pattern errors 3d17f1f Tweak link order slightly to prefer user shared libs before system ones. 87917a5 Support LIBRARY_PATH and LD_LIBRARY_PATH in rts 9f7edb9 Fix hashbang of gen-data-layout 78306b5 CoreLint: typo in a comment 2feed11 Fix hash in haddock of ghc-prim. 41afbb3 Add flag -fno-it f380115 Parenthesize forall-type args in cvtTypeKind 1bf70b2 Remove executable filename check on windows bc383f2 Simplify guard in createSwitchPlan. 8de8930 configure: Various cleanups cf2c029 Fix quadratic behavior of prepareAlts c65104e Typos in comments 6b1ff00 Fix references to cminusminus.org 1e14fd3 Inform hole substitutions of typeclass constraints (fixes #14273). 8bb150d Revert "Fix regression on i386 due to get/setAllocationCounter change" e1d4140 Revert "Improve accuracy of get/setAllocationCounter" 3335811 cmm: Include braces on default branch as required by the parser 2a78cf7 Remove unused extern cost centre collection 575c009 Fix #14681 and #14682 with precision-aimed parentheses 5e8ea6a testsuite: Add test for #14335 f855769 Add new mbmi and mbmi2 compiler flags 765ba65 testsuite: Add testcase for #14670 0074a08 Fix #14692 by correcting an off-by-one error in TcGenDeriv 5edb18a tentative improvement to callstack docs 180ca65 [rts] Adjust whitehole_spin 4a13c5b Implement underscores in numeric literals (NumericUnderscores extension) 8829743 Use IntSet in Dataflow 6c0db98 SysTools: Add detection support for LLD linker 2671ccc Update Cabal submodule 24e56eb Bump transformers submodule to 0.5.5.0 a3cde5f Improve comments about TcLevel invariants 452dee3 Pass -dsuppress-uniques when running T14507 f00ddea Allocate less in plus_mod_dep d36ae5d Comments about CoercionHoles 076bdb3 Remove dead code: mkNthCoRole 2a2e6a8 Comments only 0636689 Fix the lone-variable case in callSiteInline d6e0338 Bump terminfo submodule 40c753f testsuite: Bump haddock.Cabal allocations due to submodule bump 0e022e5 Turn EvTerm (almost) into CoreExpr (#14691) 983e491 testsuite: Add testcase for #12158 66961dc Haddock needs to pass visible modules for instance filtering 302aee5 base: Refactor Show ErrorCall instance into proper ShowS style 52dfb25 Handle the likely:True case in CmmContFlowOpt e7dcc70 Add ability to parse likely flags for ifs in Cmm. 31c260f Add ptr-eq short-cut to `compareByteArrays#` primitive cbdea95 Sort valid substitutions for typed holes by "relevance" cacba07 Linker: ignore empty paths in addEnvPaths bd58e29 Remove Hoopl.Unique 9a57cfe Option for LINE pragmas to get lexed into tokens a55d581 Fix Windows stack allocations. 59fa7b3 Fix #14719 by using the setting the right SrcSpan 7ff6023 cmm: Use two equality checks for two alt switch with default 1cb12ea Bump hadrian submodule 96d2eb2 Invert likeliness when improving conditionals 1205629 Add likely annotation to cmm files in a few obvious places. 5e8d314 Update outputs of T12962, scc003 47031db A bit more tc-tracing e7c3878 Move zonkWC to the right place in simplfyInfer 0f43d0d More tc-tracing efba054 Prioritise equalities when solving, incl deriveds e9ae0ca Look inside implications in simplifyRule 55aea8f testsuite: Mark scc001 and T5363 as broken due to #14705 370b167 circleci: Add Dockerfile for x86_64-linux b37dc23 appveyor: Don't install gcc fe6fdf6 testsuite: Fix test output of T14715 7d9812e testsuite: Fix test output broken by efba054640d3 5f922fb appveyor: Refactor 0171e09 Make RTS keep less memory (fixes #14702) 0bff9e6 Don't add targets that can't be found in GHCi be84823 Implement BlockArguments (#10843) 1a911f2 Sequester deriving-related validity check into cond_stdOK 382c12d rts: Ensure that forkOS releases Task on termination add4e1f Mark xmm6 as caller saved in the register allocator for windows. e4ab65b Optimize coercionKind (Trac #11735) ced9fbd UnboxedTuples can't be used as constraints 618a805 Experiment with eliminating the younger tyvar db5a4b8 Re-center improved perf for T3064 efce943 Add -ddump-ds-preopt e31b41b Flag `-fdefer-typed-holes` also implies `-fdefer-out-of-scope-variables`. 2974b2b Hoopl.Collections: change right folds to strict left folds c3ccd83 testsuite: Fix scc001 profile output 7fb3287 Add HasDebugCallStack to nameModule 4f52bc1 DriverPhases: Fix flipped input extensions for cmm and cmmcpp 3441b14 integer-gmp: Simplify gmp/configure invocation fdf518c Upgrade containers submodule 217e417 ghc-prim: Emulate C11 atomics when not available d8a0e6d Don't apply dataToTag's caseRules for data families e5d0101 base: Deprecate STM invariant checking primitives 50adbd7 cmm: Revert more aggressive CBE due to #14226 606edbf testsuite: Add testcase for #14754 d987f71 Improve unboxed sum documentation 326df5d Bump Cabal submodule d2511e3 Compute the union of imp_finsts on the side 7ad72eb cmm: Remove unnecessary HsVersion.h includes 1512b63 rts: Fix format of failed memory commit message 4d1c3b7 rts: Add format attribute to barf 4c36440 Restore 'It is a member of hidden package' message. 2987b04 Improve X86CodeGen's pprASCII. 3cd1305 rts: Use BITS_IN macro in bitmap calculations 00f1a4a rts: fix some barf format specifiers. da46813 testsuite: Add test for #14768 4aa98f4 Fix utterly bogus TagToEnum rule in caseRules 41d29d5 Comments only 6506980 Fix solveOneFromTheOther for RecursiveSuperclasses be53d19 Use SPDX syntax in rts/package.conf.in 059596d rts: fix barf format attribute 6edafe3 Fix isDroppableCt (Trac #14763) f489c12 Simplify Foreign.Marshal.Alloc functions with ScopedTypeVariables 583f561 Evac.c: remove unused CPP guard c9a88db Make ($!) representation-polymorphic 5957405 Collect CCs in CorePrep, including CCs in unfoldings 1f3da3b Merge branch 'master' of git://git.haskell.org/ghc into wip/T14068 From git at git.haskell.org Tue Feb 13 22:50:01 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Feb 2018 22:50:01 +0000 (UTC) Subject: [commit: ghc] master: Fix tests broken by c9a88db3ac4f1c3e97e3492ebe076f2df6463540 (0c9777b) Message-ID: <20180213225001.E9E5C3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0c9777b787d072f9f57e0cdfe44e2e2d48217077/ghc >--------------------------------------------------------------- commit 0c9777b787d072f9f57e0cdfe44e2e2d48217077 Author: Ben Gamari Date: Tue Feb 13 17:49:02 2018 -0500 Fix tests broken by c9a88db3ac4f1c3e97e3492ebe076f2df6463540 >--------------------------------------------------------------- 0c9777b787d072f9f57e0cdfe44e2e2d48217077 testsuite/tests/ghci/scripts/T5545.stdout | 5 ++++- testsuite/tests/typecheck/should_compile/holes.stderr | 6 +++--- testsuite/tests/typecheck/should_compile/holes3.stderr | 6 +++--- 3 files changed, 10 insertions(+), 7 deletions(-) diff --git a/testsuite/tests/ghci/scripts/T5545.stdout b/testsuite/tests/ghci/scripts/T5545.stdout index 2262c35..9780ffc 100644 --- a/testsuite/tests/ghci/scripts/T5545.stdout +++ b/testsuite/tests/ghci/scripts/T5545.stdout @@ -1,2 +1,5 @@ -($!) :: (a -> b) -> a -> b -- Defined in ‘GHC.Base’ +($!) :: + forall (r :: GHC.Types.RuntimeRep) a (b :: TYPE r). + (a -> b) -> a -> b + -- Defined in ‘GHC.Base’ infixr 0 $! diff --git a/testsuite/tests/typecheck/should_compile/holes.stderr b/testsuite/tests/typecheck/should_compile/holes.stderr index 8421e9a..a4b32cd 100644 --- a/testsuite/tests/typecheck/should_compile/holes.stderr +++ b/testsuite/tests/typecheck/should_compile/holes.stderr @@ -371,9 +371,6 @@ holes.hs:11:15: warning: [-Wtyped-holes (in -Wdefault)] (.) :: forall b c a. (b -> c) -> (a -> b) -> a -> c (imported from ‘Prelude’ at holes.hs:1:8-12 (and originally defined in ‘GHC.Base’)) - ($!) :: forall a b. (a -> b) -> a -> b - (imported from ‘Prelude’ at holes.hs:1:8-12 - (and originally defined in ‘GHC.Base’)) uncurry :: forall a b c. (a -> b -> c) -> (a, b) -> c (imported from ‘Prelude’ at holes.hs:1:8-12 (and originally defined in ‘Data.Tuple’)) @@ -463,6 +460,9 @@ holes.hs:11:15: warning: [-Wtyped-holes (in -Wdefault)] ($) :: forall a (b :: TYPE r). (a -> b) -> a -> b (imported from ‘Prelude’ at holes.hs:1:8-12 (and originally defined in ‘GHC.Base’)) + ($!) :: forall a (b :: TYPE r). (a -> b) -> a -> b + (imported from ‘Prelude’ at holes.hs:1:8-12 + (and originally defined in ‘GHC.Base’)) id :: forall a. a -> a (imported from ‘Prelude’ at holes.hs:1:8-12 (and originally defined in ‘GHC.Base’)) diff --git a/testsuite/tests/typecheck/should_compile/holes3.stderr b/testsuite/tests/typecheck/should_compile/holes3.stderr index ce1c947..add03e2 100644 --- a/testsuite/tests/typecheck/should_compile/holes3.stderr +++ b/testsuite/tests/typecheck/should_compile/holes3.stderr @@ -374,9 +374,6 @@ holes3.hs:11:15: error: (.) :: forall b c a. (b -> c) -> (a -> b) -> a -> c (imported from ‘Prelude’ at holes3.hs:1:8-13 (and originally defined in ‘GHC.Base’)) - ($!) :: forall a b. (a -> b) -> a -> b - (imported from ‘Prelude’ at holes3.hs:1:8-13 - (and originally defined in ‘GHC.Base’)) uncurry :: forall a b c. (a -> b -> c) -> (a, b) -> c (imported from ‘Prelude’ at holes3.hs:1:8-13 (and originally defined in ‘Data.Tuple’)) @@ -466,6 +463,9 @@ holes3.hs:11:15: error: ($) :: forall a (b :: TYPE r). (a -> b) -> a -> b (imported from ‘Prelude’ at holes3.hs:1:8-13 (and originally defined in ‘GHC.Base’)) + ($!) :: forall a (b :: TYPE r). (a -> b) -> a -> b + (imported from ‘Prelude’ at holes3.hs:1:8-13 + (and originally defined in ‘GHC.Base’)) id :: forall a. a -> a (imported from ‘Prelude’ at holes3.hs:1:8-13 (and originally defined in ‘GHC.Base’)) From git at git.haskell.org Tue Feb 13 22:49:59 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Feb 2018 22:49:59 +0000 (UTC) Subject: [commit: ghc] master: Raise parse error for `data T where`. (8936ab6) Message-ID: <20180213224959.0ADBD3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8936ab69d18669bab3ca4edf40458f88ae5903f0/ghc >--------------------------------------------------------------- commit 8936ab69d18669bab3ca4edf40458f88ae5903f0 Author: HE, Tao Date: Mon Feb 12 19:55:41 2018 -0500 Raise parse error for `data T where`. Empty GADTs data declarations can't be identified in type checker. This patch adds additional checks in parser and raise a parse error when encounter empty GADTs declarations but extension `GADTs` is not enabled. Only empty declarations are checked in parser to avoid affecting existing error messages related to missing GADTs extension. This patch should fix issue 8258. Signed-off-by: HE, Tao Test Plan: make test TEST="T8258 T8258NoGADTs" Reviewers: bgamari, mpickering, alanz, RyanGlScott Reviewed By: bgamari, RyanGlScott Subscribers: adamse, RyanGlScott, rwbarton, thomie, mpickering, carter GHC Trac Issues: #8258 Differential Revision: https://phabricator.haskell.org/D4350 >--------------------------------------------------------------- 8936ab69d18669bab3ca4edf40458f88ae5903f0 compiler/parser/Parser.y | 19 +++++++++++-------- compiler/parser/RdrHsSyn.hs | 16 ++++++++++++++++ docs/users_guide/8.6.1-notes.rst | 8 ++++++++ testsuite/tests/parser/should_compile/T8258.hs | 5 +++++ testsuite/tests/parser/should_compile/all.T | 1 + testsuite/tests/parser/should_fail/T8258NoGADTs.hs | 3 +++ .../tests/parser/should_fail/T8258NoGADTs.stderr | 5 +++++ testsuite/tests/parser/should_fail/all.T | 1 + testsuite/tests/polykinds/T11640.hs | 2 +- testsuite/tests/typecheck/should_compile/tc247.hs | 2 +- 10 files changed, 52 insertions(+), 10 deletions(-) diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y index 7f1a725..898ed3c 100644 --- a/compiler/parser/Parser.y +++ b/compiler/parser/Parser.y @@ -2087,14 +2087,17 @@ both become a HsTyVar ("Zero", DataName) after the renamer. gadt_constrlist :: { Located ([AddAnn] ,[LConDecl GhcPs]) } -- Returned in order - : 'where' '{' gadt_constrs '}' { L (comb2 $1 $3) - ([mj AnnWhere $1 - ,moc $2 - ,mcc $4] - , unLoc $3) } - | 'where' vocurly gadt_constrs close { L (comb2 $1 $3) - ([mj AnnWhere $1] - , unLoc $3) } + + : 'where' '{' gadt_constrs '}' {% checkEmptyGADTs $ + L (comb2 $1 $3) + ([mj AnnWhere $1 + ,moc $2 + ,mcc $4] + , unLoc $3) } + | 'where' vocurly gadt_constrs close {% checkEmptyGADTs $ + L (comb2 $1 $3) + ([mj AnnWhere $1] + , unLoc $3) } | {- empty -} { noLoc ([],[]) } gadt_constrs :: { Located [LConDecl GhcPs] } diff --git a/compiler/parser/RdrHsSyn.hs b/compiler/parser/RdrHsSyn.hs index 357d224..6ac6cbc 100644 --- a/compiler/parser/RdrHsSyn.hs +++ b/compiler/parser/RdrHsSyn.hs @@ -55,6 +55,7 @@ module RdrHsSyn ( checkValSigLhs, checkDoAndIfThenElse, checkRecordSyntax, + checkEmptyGADTs, parseErrorSDoc, hintBangPat, splitTilde, splitTildeApps, @@ -783,6 +784,21 @@ checkRecordSyntax lr@(L loc r) (text "Illegal record syntax (use TraditionalRecordSyntax):" <+> ppr r) +-- | Check if the gadt_constrlist is empty. Only raise parse error for +-- `data T where` to avoid affecting existing error message, see #8258. +checkEmptyGADTs :: Located ([AddAnn], [LConDecl GhcPs]) + -> P (Located ([AddAnn], [LConDecl GhcPs])) +checkEmptyGADTs gadts@(L span (_, [])) -- Empty GADT declaration. + = do opts <- fmap options getPState + if LangExt.GADTSyntax `extopt` opts -- GADTs implies GADTSyntax + then return gadts + else parseErrorSDoc span $ vcat + [ text "Illegal keyword 'where' in data declaration" + , text "Perhaps you intended to use GADTs or a similar language" + , text "extension to enable syntax: data T where" + ] +checkEmptyGADTs gadts = return gadts -- Ordinary GADT declaration. + checkTyClHdr :: Bool -- True <=> class header -- False <=> type header -> LHsType GhcPs diff --git a/docs/users_guide/8.6.1-notes.rst b/docs/users_guide/8.6.1-notes.rst index e844ab6..8f7e961 100644 --- a/docs/users_guide/8.6.1-notes.rst +++ b/docs/users_guide/8.6.1-notes.rst @@ -22,6 +22,14 @@ Full details Language ~~~~~~~~ +- Data declarations with empty ``where`` clauses are no longer valid without the + extension :extension:`GADTSyntax` enabled. For instance, consider the + following, :: + + data T where + + The grammar is invalid in Haskell2010. Previously it could be compiled successfully + without ``GADTs``. As of GHC 8.6.1, this is a parse error. Compiler ~~~~~~~~ diff --git a/testsuite/tests/parser/should_compile/T8258.hs b/testsuite/tests/parser/should_compile/T8258.hs new file mode 100644 index 0000000..18d6483 --- /dev/null +++ b/testsuite/tests/parser/should_compile/T8258.hs @@ -0,0 +1,5 @@ +{-# LANGUAGE GADTs #-} + +module T8258 where + +data T where diff --git a/testsuite/tests/parser/should_compile/all.T b/testsuite/tests/parser/should_compile/all.T index cc97710..1ca6d7e 100644 --- a/testsuite/tests/parser/should_compile/all.T +++ b/testsuite/tests/parser/should_compile/all.T @@ -100,6 +100,7 @@ test('T7118', normal, compile, ['']) test('T7776', normal, compile, ['']) test('RdrNoStaticPointers01', [], compile, ['']) test('T5682', normal, compile, ['']) +test('T8258', normal, compile, ['']) test('T9723a', normal, compile, ['']) test('T9723b', normal, compile, ['']) test('T10188', normal, compile, ['']) diff --git a/testsuite/tests/parser/should_fail/T8258NoGADTs.hs b/testsuite/tests/parser/should_fail/T8258NoGADTs.hs new file mode 100644 index 0000000..1080233 --- /dev/null +++ b/testsuite/tests/parser/should_fail/T8258NoGADTs.hs @@ -0,0 +1,3 @@ +module T8258NoGADTs where + +data T where diff --git a/testsuite/tests/parser/should_fail/T8258NoGADTs.stderr b/testsuite/tests/parser/should_fail/T8258NoGADTs.stderr new file mode 100644 index 0000000..35f5306 --- /dev/null +++ b/testsuite/tests/parser/should_fail/T8258NoGADTs.stderr @@ -0,0 +1,5 @@ + +T8258NoGADTs.hs:3:8: error: + Illegal keyword 'where' in data declaration + Perhaps you intended to use GADTs or a similar language + extension to enable syntax: data T where diff --git a/testsuite/tests/parser/should_fail/all.T b/testsuite/tests/parser/should_fail/all.T index ef47ed3..2cb9c49 100644 --- a/testsuite/tests/parser/should_fail/all.T +++ b/testsuite/tests/parser/should_fail/all.T @@ -87,6 +87,7 @@ test('T5425', normal, compile_fail, ['']) test('T984', normal, compile_fail, ['']) test('T7848', normal, compile_fail, ['-dppr-user-length=100']) test('ExportCommaComma', normal, compile_fail, ['']) +test('T8258NoGADTs', normal, compile_fail, ['']) test('T8430', literate, compile_fail, ['']) test('T8431', compile_timeout_multiplier(0.05), compile_fail, ['-XAlternativeLayoutRule']) diff --git a/testsuite/tests/polykinds/T11640.hs b/testsuite/tests/polykinds/T11640.hs index 16d9f7c..bbb4a53 100644 --- a/testsuite/tests/polykinds/T11640.hs +++ b/testsuite/tests/polykinds/T11640.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE RankNTypes, TypeInType #-} +{-# LANGUAGE GADTs, RankNTypes, TypeInType #-} module T11640 where diff --git a/testsuite/tests/typecheck/should_compile/tc247.hs b/testsuite/tests/typecheck/should_compile/tc247.hs index 0f017a0..abfc9ac 100644 --- a/testsuite/tests/typecheck/should_compile/tc247.hs +++ b/testsuite/tests/typecheck/should_compile/tc247.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE EmptyDataDecls, KindSignatures #-} +{-# LANGUAGE GADTs, EmptyDataDecls, KindSignatures #-} module ShouldCompile where From git at git.haskell.org Wed Feb 14 11:28:43 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 14 Feb 2018 11:28:43 +0000 (UTC) Subject: [commit: ghc] wip/angerman/reloc: Adds profiling flag (f12c377) Message-ID: <20180214112843.D41CD3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/reloc Link : http://ghc.haskell.org/trac/ghc/changeset/f12c3773ffa3435fa0cd89073f98a4cb7f625ad1/ghc >--------------------------------------------------------------- commit f12c3773ffa3435fa0cd89073f98a4cb7f625ad1 Author: Moritz Angermann Date: Wed Feb 14 09:33:43 2018 +0800 Adds profiling flag origianlly authored by @alp >--------------------------------------------------------------- f12c3773ffa3435fa0cd89073f98a4cb7f625ad1 rts/rts.cabal.in | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/rts/rts.cabal.in b/rts/rts.cabal.in index a895c9c..5f88f7e 100644 --- a/rts/rts.cabal.in +++ b/rts/rts.cabal.in @@ -26,6 +26,8 @@ flag leading-underscore default: @CabalLeadingUnderscore@ flag smp default: True +flag profiling + default: False library -- rts is a wired in package and @@ -43,7 +45,9 @@ library -- libCffi_debug libCffi_ libCffi_l libCffi_p -- libCffi_thr libCffi_thr_debug libCffi_thr_l libCffi_thr_p extra-library-flavours: _debug _l _thr _thr_debug _thr_l - -- TODO: _p and _thr_p only if profiling. + if flag(profiling) + extra-library-flavours: _p _thr_p + exposed: True exposed-modules: if flag(libm) From git at git.haskell.org Wed Feb 14 11:28:46 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 14 Feb 2018 11:28:46 +0000 (UTC) Subject: [commit: ghc] wip/angerman/reloc: bump (836badf) Message-ID: <20180214112846.A7F3B3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/reloc Link : http://ghc.haskell.org/trac/ghc/changeset/836badf6e57f779f97e9e051fc635add03fbaaad/ghc >--------------------------------------------------------------- commit 836badf6e57f779f97e9e051fc635add03fbaaad Author: Moritz Angermann Date: Wed Feb 14 09:39:55 2018 +0800 bump >--------------------------------------------------------------- 836badf6e57f779f97e9e051fc635add03fbaaad hadrian | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/hadrian b/hadrian index e3d27af..9505159 160000 --- a/hadrian +++ b/hadrian @@ -1 +1 @@ -Subproject commit e3d27af408bfd9cfa0557028b55457c224d03407 +Subproject commit 950515995a8e0f5b34fbed3f895752e5ae09f8f8 From git at git.haskell.org Wed Feb 14 11:28:49 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 14 Feb 2018 11:28:49 +0000 (UTC) Subject: [commit: ghc] wip/angerman/reloc: bump (0743b38) Message-ID: <20180214112849.834693A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/reloc Link : http://ghc.haskell.org/trac/ghc/changeset/0743b38073741a8133ceb4f5d61425fe7893f15f/ghc >--------------------------------------------------------------- commit 0743b38073741a8133ceb4f5d61425fe7893f15f Author: Moritz Angermann Date: Wed Feb 14 19:28:18 2018 +0800 bump >--------------------------------------------------------------- 0743b38073741a8133ceb4f5d61425fe7893f15f hadrian | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/hadrian b/hadrian index 9505159..f0a39fd 160000 --- a/hadrian +++ b/hadrian @@ -1 +1 @@ -Subproject commit 950515995a8e0f5b34fbed3f895752e5ae09f8f8 +Subproject commit f0a39fda5b49b9e4b160ca4fba531c8807c9fb5f From git at git.haskell.org Wed Feb 14 22:07:14 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 14 Feb 2018 22:07:14 +0000 (UTC) Subject: [commit: ghc] master: Various documentation improvements (df449e1) Message-ID: <20180214220714.5B8E73A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/df449e1744d59eef7f41e09196629bc01815e984/ghc >--------------------------------------------------------------- commit df449e1744d59eef7f41e09196629bc01815e984 Author: Sergey Vinokurov Date: Wed Feb 7 21:10:17 2018 +0000 Various documentation improvements * Fix missing code example in changelog for 8.4.1 * List 'setEnv' as opposite of 'getEnv' It seems best to direct users to use 'System.Environment.setEnv' rather than 'System.Posix.Env.putEnv'. This is due to 'setEnv' being located in the same module as 'getEnv' and my virtue of working on Windows platform, whereas 'putEnv' does not have that quality because it's part of the 'unix' package. * Reflect in docs the fact that 'readMVar' is not a composition of 'takeMVVar' and 'putMVar' any more >--------------------------------------------------------------- df449e1744d59eef7f41e09196629bc01815e984 docs/users_guide/8.4.1-notes.rst | 2 +- libraries/base/Control/Concurrent/MVar.hs | 4 ++-- libraries/base/GHC/MVar.hs | 2 +- libraries/base/System/Environment.hs | 4 ++-- 4 files changed, 6 insertions(+), 6 deletions(-) diff --git a/docs/users_guide/8.4.1-notes.rst b/docs/users_guide/8.4.1-notes.rst index 963e8d9..305f962 100644 --- a/docs/users_guide/8.4.1-notes.rst +++ b/docs/users_guide/8.4.1-notes.rst @@ -182,7 +182,7 @@ Compiler ``error``: :: instance Show (Empty a) where - showsPrec = "Void showsPrec" + showsPrec = error "Void showsPrec" Now, they emit code that inspects the argument. That is, if the argument diverges, then showing it will also diverge: :: diff --git a/libraries/base/Control/Concurrent/MVar.hs b/libraries/base/Control/Concurrent/MVar.hs index 393fca8..fa99361 100644 --- a/libraries/base/Control/Concurrent/MVar.hs +++ b/libraries/base/Control/Concurrent/MVar.hs @@ -41,8 +41,8 @@ -- atomic operations such as reading from multiple variables: use 'STM' -- instead. -- --- In particular, the "bigger" functions in this module ('readMVar', --- 'swapMVar', 'withMVar', 'modifyMVar_' and 'modifyMVar') are simply +-- In particular, the "bigger" functions in this module ('swapMVar', +-- 'withMVar', 'modifyMVar_' and 'modifyMVar') are simply -- the composition of a 'takeMVar' followed by a 'putMVar' with -- exception safety. -- These only have atomicity guarantees if all other threads diff --git a/libraries/base/GHC/MVar.hs b/libraries/base/GHC/MVar.hs index f334ddb..aa59002 100644 --- a/libraries/base/GHC/MVar.hs +++ b/libraries/base/GHC/MVar.hs @@ -90,7 +90,7 @@ takeMVar :: MVar a -> IO a takeMVar (MVar mvar#) = IO $ \ s# -> takeMVar# mvar# s# -- |Atomically read the contents of an 'MVar'. If the 'MVar' is --- currently empty, 'readMVar' will wait until its full. +-- currently empty, 'readMVar' will wait until it is full. -- 'readMVar' is guaranteed to receive the next 'putMVar'. -- -- 'readMVar' is multiple-wakeup, so when multiple readers are diff --git a/libraries/base/System/Environment.hs b/libraries/base/System/Environment.hs index 343b772..5604ca2 100644 --- a/libraries/base/System/Environment.hs +++ b/libraries/base/System/Environment.hs @@ -123,8 +123,8 @@ basename f = go f f -- | Computation 'getEnv' @var@ returns the value --- of the environment variable @var at . For the inverse, POSIX users --- can use 'System.Posix.Env.putEnv'. +-- of the environment variable @var at . For the inverse, the +-- `System.Environment.setEnv` function can be used. -- -- This computation may fail with: -- From git at git.haskell.org Thu Feb 15 01:44:12 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Feb 2018 01:44:12 +0000 (UTC) Subject: [commit: ghc] master: adds -latomic to. ghc-prim (ec9aacf) Message-ID: <20180215014412.80A173A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ec9aacf3eb2975fd302609163aaef429962ecd87/ghc >--------------------------------------------------------------- commit ec9aacf3eb2975fd302609163aaef429962ecd87 Author: Moritz Angermann Date: Thu Feb 8 16:07:07 2018 +0800 adds -latomic to. ghc-prim Reviewers: bgamari, hvr Reviewed By: bgamari Subscribers: erikd, hvr, rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4378 >--------------------------------------------------------------- ec9aacf3eb2975fd302609163aaef429962ecd87 aclocal.m4 | 18 ------------------ configure.ac | 5 ----- libraries/ghc-prim/Setup.hs | 2 +- libraries/ghc-prim/aclocal.m4 | 17 +++++++++++++++++ libraries/ghc-prim/configure.ac | 18 ++++++++++++++++++ libraries/ghc-prim/ghc-prim.buildinfo.in | 2 ++ 6 files changed, 38 insertions(+), 24 deletions(-) diff --git a/aclocal.m4 b/aclocal.m4 index 2ed2c08..6f37972 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -1281,24 +1281,6 @@ AC_SUBST(GccIsClang) rm -f conftest.txt ]) -# FP_GCC_SUPPORTS__ATOMICS -# ------------------------ -# Does gcc support the __atomic_* family of builtins? -AC_DEFUN([FP_GCC_SUPPORTS__ATOMICS], -[ - AC_REQUIRE([AC_PROG_CC]) - AC_MSG_CHECKING([whether GCC supports __atomic_ builtins]) - echo 'int test(int *x) { int y; __atomic_load(&x, &y, __ATOMIC_SEQ_CST); return x; }' > conftest.c - if $CC -c conftest.c > /dev/null 2>&1; then - CONF_GCC_SUPPORTS__ATOMICS=YES - AC_MSG_RESULT([yes]) - else - CONF_GCC_SUPPORTS__ATOMICS=NO - AC_MSG_RESULT([no]) - fi - rm -f conftest.c conftest.o -]) - # FP_GCC_SUPPORTS_NO_PIE # ---------------------- # Does gcc support the -no-pie option? If so we should pass it to gcc when diff --git a/configure.ac b/configure.ac index 5bf096b..216a97f 100644 --- a/configure.ac +++ b/configure.ac @@ -712,11 +712,6 @@ FP_GCC_VERSION dnl ** See whether gcc supports -no-pie FP_GCC_SUPPORTS_NO_PIE -dnl ** Used to determine how to compile ghc-prim's atomics.c, used by -dnl unregisterised, Sparc, and PPC backends. -FP_GCC_SUPPORTS__ATOMICS -AC_DEFINE([HAVE_C11_ATOMICS], [$CONF_GCC_SUPPORTS__ATOMICS], [Does GCC support __atomic primitives?]) - FP_GCC_EXTRA_FLAGS dnl ** look to see if we have a C compiler using an llvm back end. diff --git a/libraries/ghc-prim/Setup.hs b/libraries/ghc-prim/Setup.hs index 5bb17e2..cccc416 100644 --- a/libraries/ghc-prim/Setup.hs +++ b/libraries/ghc-prim/Setup.hs @@ -18,7 +18,7 @@ import System.Exit import System.Directory main :: IO () -main = do let hooks = simpleUserHooks { +main = do let hooks = autoconfUserHooks { regHook = addPrimModule $ regHook simpleUserHooks, buildHook = build_primitive_sources diff --git a/libraries/ghc-prim/aclocal.m4 b/libraries/ghc-prim/aclocal.m4 new file mode 100644 index 0000000..e569538 --- /dev/null +++ b/libraries/ghc-prim/aclocal.m4 @@ -0,0 +1,17 @@ +# FP_GCC_SUPPORTS__ATOMICS +# ------------------------ +# Does gcc support the __atomic_* family of builtins? +AC_DEFUN([FP_GCC_SUPPORTS__ATOMICS], +[ + AC_REQUIRE([AC_PROG_CC]) + AC_MSG_CHECKING([whether GCC supports __atomic_ builtins]) + echo 'int test(int *x) { int y; __atomic_load(&x, &y, __ATOMIC_SEQ_CST); return x; }' > conftest.c + if $CC -c conftest.c > /dev/null 2>&1; then + CONF_GCC_SUPPORTS__ATOMICS=YES + AC_MSG_RESULT([yes]) + else + CONF_GCC_SUPPORTS__ATOMICS=NO + AC_MSG_RESULT([no]) + fi + rm -f conftest.c conftest.o +]) diff --git a/libraries/ghc-prim/configure.ac b/libraries/ghc-prim/configure.ac new file mode 100644 index 0000000..bacc89c --- /dev/null +++ b/libraries/ghc-prim/configure.ac @@ -0,0 +1,18 @@ +AC_INIT([ghc-prim package], [2.1], [glasgow-haskell-bugs at haskell.org], [ghc-prim]) + +AC_CONFIG_SRCDIR([ghc-prim.cabal]) + +# ------------------------------------------------------------------------- +dnl ** Used to determine how to compile ghc-prim's atomics.c, used by +dnl unregisterised, Sparc, and PPC backends. +FP_GCC_SUPPORTS__ATOMICS +AC_DEFINE([HAVE_C11_ATOMICS], [$CONF_GCC_SUPPORTS__ATOMICS], [Does GCC support __atomic primitives?]) + +if test "x$CONF_GCC_SUPPORTS__ATOMICS" = YES +then PRIM_CFLAGS=-DHAVE_C11_ATOMICS + PRIM_EXTRA_LIBRARIES=atomic +fi +AC_SUBST([PRIM_CFLAGS]) +AC_SUBST([PRIM_EXTRA_LIBRARIES]) +AC_CONFIG_FILES([ghc-prim.buildinfo]) +AC_OUTPUT diff --git a/libraries/ghc-prim/ghc-prim.buildinfo.in b/libraries/ghc-prim/ghc-prim.buildinfo.in new file mode 100644 index 0000000..a093282 --- /dev/null +++ b/libraries/ghc-prim/ghc-prim.buildinfo.in @@ -0,0 +1,2 @@ +cc-options: @PRIM_CFLAGS@ +extra-libraries: @PRIM_EXTRA_LIBRARIES@ \ No newline at end of file From git at git.haskell.org Thu Feb 15 01:51:25 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Feb 2018 01:51:25 +0000 (UTC) Subject: [commit: ghc] master: Adds `smp` flag to rts.cabal. (d5ff33d) Message-ID: <20180215015125.DF52B3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d5ff33d34b0d8eb26b496a809a2f73e83ea59573/ghc >--------------------------------------------------------------- commit d5ff33d34b0d8eb26b496a809a2f73e83ea59573 Author: Moritz Angermann Date: Sat Nov 25 20:49:56 2017 +0800 Adds `smp` flag to rts.cabal. Reviewers: bgamari, erikd, simonmar Reviewed By: simonmar Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4393 >--------------------------------------------------------------- d5ff33d34b0d8eb26b496a809a2f73e83ea59573 rts/rts.cabal.in | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/rts/rts.cabal.in b/rts/rts.cabal.in index 53b6271..ce9d751 100644 --- a/rts/rts.cabal.in +++ b/rts/rts.cabal.in @@ -24,6 +24,8 @@ flag 64bit default: @Cabal64bit@ flag leading-underscore default: @CabalLeadingUnderscore@ +flag smp + default: True library -- rts is a wired in package and @@ -72,6 +74,8 @@ library if flag(libdw) -- for backtraces extra-libraries: elf dw + if !flag(smp) + cpp-options: -DNOSMP include-dirs: build ../includes includes includes/dist-derivedconstants/header @FFIIncludeDir@ From git at git.haskell.org Thu Feb 15 01:58:46 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Feb 2018 01:58:46 +0000 (UTC) Subject: [commit: ghc] master: Update .cabal files for Cabal 2.1 (e03ca71) Message-ID: <20180215015846.D23683A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e03ca71f14dca2fe0bf3e884f34c44838937424a/ghc >--------------------------------------------------------------- commit e03ca71f14dca2fe0bf3e884f34c44838937424a Author: Moritz Angermann Date: Mon Feb 5 12:34:03 2018 +0800 Update .cabal files for Cabal 2.1 cabal introduces SPDX identifier, and as such we need to change the BSD3 license name. Also the >= qualifier is no longer prefered. Test Plan: ./validate Reviewers: bgamari, erikd, simonmar Reviewed By: bgamari Subscribers: alpmestan, rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4406 >--------------------------------------------------------------- e03ca71f14dca2fe0bf3e884f34c44838937424a rts/rts.cabal.in | 4 ++-- utils/hp2ps/hp2ps.cabal | 6 +++--- utils/touchy/touchy.cabal | 4 ++-- utils/unlit/unlit.cabal | 4 ++-- 4 files changed, 9 insertions(+), 9 deletions(-) diff --git a/rts/rts.cabal.in b/rts/rts.cabal.in index ce9d751..a895c9c 100644 --- a/rts/rts.cabal.in +++ b/rts/rts.cabal.in @@ -1,7 +1,7 @@ -cabal-version: >= 2.1 +cabal-version: 2.1 name: rts version: 1.0 -license: BSD3 +license: BSD-3-Clause maintainer: glasgow-haskell-users at haskell.org build-type: Simple flag libm diff --git a/utils/hp2ps/hp2ps.cabal b/utils/hp2ps/hp2ps.cabal index ba5db04..b4062b2 100644 --- a/utils/hp2ps/hp2ps.cabal +++ b/utils/hp2ps/hp2ps.cabal @@ -1,8 +1,8 @@ -cabal-version: >=2.1 +cabal-version: 2.1 Name: hp2ps Version: 0.1 Copyright: XXX -License: BSD3 +license: BSD-3-Clause Author: XXX Maintainer: XXX Synopsis: Heap Profile to PostScript converter @@ -10,7 +10,7 @@ Description: XXX Category: Development build-type: Simple -Executable unlit +Executable hp2ps Default-Language: Haskell2010 Main-Is: Main.c extra-libraries: m diff --git a/utils/touchy/touchy.cabal b/utils/touchy/touchy.cabal index ab025e4..377051e 100644 --- a/utils/touchy/touchy.cabal +++ b/utils/touchy/touchy.cabal @@ -1,8 +1,8 @@ -cabal-version: >=2.1 +cabal-version: 2.1 Name: touchy Version: 0.1 Copyright: XXX -License: BSD3 +License: BSD-3-Clause Author: XXX Maintainer: XXX Synopsis: @touch@ for windows diff --git a/utils/unlit/unlit.cabal b/utils/unlit/unlit.cabal index e15a075..a621f04 100644 --- a/utils/unlit/unlit.cabal +++ b/utils/unlit/unlit.cabal @@ -1,8 +1,8 @@ -cabal-version: >=2.1 +cabal-version: 2.1 Name: unlit Version: 0.1 Copyright: XXX -License: BSD3 +License: BSD-3-Clause Author: XXX Maintainer: XXX Synopsis: Literate program filter From git at git.haskell.org Thu Feb 15 07:27:32 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Feb 2018 07:27:32 +0000 (UTC) Subject: [commit: ghc] master: rts.cabal.in: advertise profiling flavours of libraries, behind a flag (0c2350c) Message-ID: <20180215072732.828C23A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0c2350c293b82e4cb24a66e00b904933bdb1c8f3/ghc >--------------------------------------------------------------- commit 0c2350c293b82e4cb24a66e00b904933bdb1c8f3 Author: Alp Mestanogullari Date: Thu Feb 15 15:23:01 2018 +0800 rts.cabal.in: advertise profiling flavours of libraries, behind a flag The make build system appears to be doing a bit of magic in order to supply the profiled flavours of libHSrts and libCffi, as they're not advertised in the 'extra-library-flavours' field of rts.cabal.in. This patch explicitly advertises _p and _thr_p flavours of the RTS library and libCffi, but only when the RTS is configured with the (newly introduced) 'profiling' flag. This is necessary for Hadrian, as a branch (soon to be merged) does away with ghc-cabal and relies just on Cabal to get package information. Without this patch, Cabal can never inform us that _p and _thr_p flavours should be built (and registered in the package db) as well, which obviously prevents us from building a profiled GHC. Reviewers: bgamari, erikd, simonmar Reviewed By: bgamari Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4409 >--------------------------------------------------------------- 0c2350c293b82e4cb24a66e00b904933bdb1c8f3 rts/rts.cabal.in | 13 ++++++++++++- 1 file changed, 12 insertions(+), 1 deletion(-) diff --git a/rts/rts.cabal.in b/rts/rts.cabal.in index a895c9c..67fb9c5 100644 --- a/rts/rts.cabal.in +++ b/rts/rts.cabal.in @@ -26,6 +26,8 @@ flag leading-underscore default: @CabalLeadingUnderscore@ flag smp default: True +flag profiling + default: False library -- rts is a wired in package and @@ -43,7 +45,16 @@ library -- libCffi_debug libCffi_ libCffi_l libCffi_p -- libCffi_thr libCffi_thr_debug libCffi_thr_l libCffi_thr_p extra-library-flavours: _debug _l _thr _thr_debug _thr_l - -- TODO: _p and _thr_p only if profiling. + + -- The make build system seems to be doing something "magic"/special + -- for generating profiled builds of those libraries, but we need to + -- be transparent for hadrian which gets information about the rts + -- "package" through Cabal and this cabal file. We therefore declare + -- two profiling-enabled flavours to be available when passing the + -- 'profiling' flag when configuring the RTS from hadrian, using Cabal. + if flag(profiling) + extra-library-flavours: _p _thr_p + exposed: True exposed-modules: if flag(libm) From git at git.haskell.org Thu Feb 15 07:35:01 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Feb 2018 07:35:01 +0000 (UTC) Subject: [commit: ghc] wip/angerman/reloc: Move `iserv` into `utils` and change package name from `iserv-bin` to `iserv` (ddf191e) Message-ID: <20180215073501.DAFFD3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/reloc Link : http://ghc.haskell.org/trac/ghc/changeset/ddf191ec6041193542a5b907806fb10f5e6350d0/ghc >--------------------------------------------------------------- commit ddf191ec6041193542a5b907806fb10f5e6350d0 Author: Moritz Angermann Date: Sat Nov 25 15:10:52 2017 +0800 Move `iserv` into `utils` and change package name from `iserv-bin` to `iserv` This is done for consistency. We usually call the package file the same name the folder has. The move into `utils` is done so that we can move the library into `libraries/iserv` and the proxy into `utils/iserv-proxy` and then break the `iserv.cabal` apart. This will make building the cross compiler with TH simpler, because we can build the library and proxy as separate packages. # Conflicts: # utils/iserv-proxy/iserv-proxy.cabal >--------------------------------------------------------------- ddf191ec6041193542a5b907806fb10f5e6350d0 ghc.mk | 13 +-- {iserv => libraries/libiserv}/Makefile | 0 {iserv => libraries/libiserv}/cbits/iservmain.c | 0 libraries/libiserv/ghc.mk | 5 + libraries/libiserv/libiserv.cabal | 39 +++++++ {iserv => libraries/libiserv}/proxy-src/Remote.hs | 0 {iserv => libraries/libiserv}/src/GHCi/Utils.hsc | 0 {iserv => libraries/libiserv}/src/Lib.hs | 0 {iserv => libraries/libiserv}/src/Main.hs | 0 .../libiserv}/src/Remote/Message.hs | 0 {iserv => libraries/libiserv}/src/Remote/Slave.hs | 0 {iserv => utils/iserv-proxy}/Makefile | 0 utils/iserv-proxy/ghc.mk | 113 +++++++++++++++++++++ .../iserv-proxy/iserv-proxy.cabal | 72 +------------ .../Remote.hs => utils/iserv-proxy/src/Main.hs | 0 {iserv => utils/iserv}/Makefile | 0 {iserv => utils/iserv}/cbits/iservmain.c | 0 {iserv => utils/iserv}/ghc.mk | 66 ++++++------ utils/iserv/iserv.cabal | 44 ++++++++ {iserv => utils/iserv}/src/Main.hs | 0 20 files changed, 246 insertions(+), 106 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ddf191ec6041193542a5b907806fb10f5e6350d0 From git at git.haskell.org Thu Feb 15 07:35:04 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Feb 2018 07:35:04 +0000 (UTC) Subject: [commit: ghc] wip/angerman/reloc: temp fix Makefile (61ba492) Message-ID: <20180215073504.A539E3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/reloc Link : http://ghc.haskell.org/trac/ghc/changeset/61ba492873c825feff8977e7bee75d0dce6d6a55/ghc >--------------------------------------------------------------- commit 61ba492873c825feff8977e7bee75d0dce6d6a55 Author: Moritz Angermann Date: Thu Feb 15 12:29:14 2018 +0800 temp fix Makefile >--------------------------------------------------------------- 61ba492873c825feff8977e7bee75d0dce6d6a55 utils/iserv/Makefile | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/utils/iserv/Makefile b/utils/iserv/Makefile index f160978..3619858 100644 --- a/utils/iserv/Makefile +++ b/utils/iserv/Makefile @@ -10,6 +10,6 @@ # # ----------------------------------------------------------------------------- -dir = iserv -TOP = .. +dir = utils/iserv +TOP = ../.. include $(TOP)/mk/sub-makefile.mk From git at git.haskell.org Thu Feb 15 07:35:12 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Feb 2018 07:35:12 +0000 (UTC) Subject: [commit: ghc] wip/angerman/reloc's head updated: bump libs (8a437b0) Message-ID: <20180215073512.91DBD3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/angerman/reloc' now includes: 5957405 Collect CCs in CorePrep, including CCs in unfoldings 0c9777b Fix tests broken by c9a88db3ac4f1c3e97e3492ebe076f2df6463540 8936ab6 Raise parse error for `data T where`. df449e1 Various documentation improvements ec9aacf adds -latomic to. ghc-prim d5ff33d Adds `smp` flag to rts.cabal. e03ca71 Update .cabal files for Cabal 2.1 ddf191e Move `iserv` into `utils` and change package name from `iserv-bin` to `iserv` 61ba492 temp fix Makefile 1d956bd adds .gitignore 8a437b0 bump libs From git at git.haskell.org Thu Feb 15 07:35:10 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Feb 2018 07:35:10 +0000 (UTC) Subject: [commit: ghc] wip/angerman/reloc: bump libs (8a437b0) Message-ID: <20180215073510.470C83A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/reloc Link : http://ghc.haskell.org/trac/ghc/changeset/8a437b0b65b16f450ef7db9c914aa068167a915f/ghc >--------------------------------------------------------------- commit 8a437b0b65b16f450ef7db9c914aa068167a915f Author: Moritz Angermann Date: Thu Feb 15 15:34:34 2018 +0800 bump libs >--------------------------------------------------------------- 8a437b0b65b16f450ef7db9c914aa068167a915f hadrian | 2 +- libraries/Cabal | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/hadrian b/hadrian index 63a5563..f0a39fd 160000 --- a/hadrian +++ b/hadrian @@ -1 +1 @@ -Subproject commit 63a556382f4b3154ed2ce3a6c8a36f79d9b8e3b1 +Subproject commit f0a39fda5b49b9e4b160ca4fba531c8807c9fb5f diff --git a/libraries/Cabal b/libraries/Cabal index 578d3a5..ccb3350 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit 578d3a50db818223017b8891df268d4200b8ffd3 +Subproject commit ccb3350ddf2c225ed47618df05dc58afe4482a1b From git at git.haskell.org Thu Feb 15 07:35:07 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Feb 2018 07:35:07 +0000 (UTC) Subject: [commit: ghc] wip/angerman/reloc: adds .gitignore (1d956bd) Message-ID: <20180215073507.770E73A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/reloc Link : http://ghc.haskell.org/trac/ghc/changeset/1d956bd17abf19ca5b1fd656a00bcd69e16cc297/ghc >--------------------------------------------------------------- commit 1d956bd17abf19ca5b1fd656a00bcd69e16cc297 Author: Moritz Angermann Date: Thu Feb 15 13:54:55 2018 +0800 adds .gitignore >--------------------------------------------------------------- 1d956bd17abf19ca5b1fd656a00bcd69e16cc297 .gitignore | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/.gitignore b/.gitignore index 67eea8a..0d3a3a2 100644 --- a/.gitignore +++ b/.gitignore @@ -81,8 +81,7 @@ _darcs/ /ghc/stage1/ /ghc/stage2/ /ghc/stage3/ -/iserv/stage2*/ -/iserv/dist/ +/utils/iserv/stage2*/ # ----------------------------------------------------------------------------- # specific generated files From git at git.haskell.org Thu Feb 15 08:50:23 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Feb 2018 08:50:23 +0000 (UTC) Subject: [commit: ghc] master: Get eqTypeRep to inline (8529fbb) Message-ID: <20180215085023.9BDF03A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8529fbba309cd692bbbb0386321515d05a6ed256/ghc >--------------------------------------------------------------- commit 8529fbba309cd692bbbb0386321515d05a6ed256 Author: David Feuer Date: Thu Feb 15 03:48:51 2018 -0500 Get eqTypeRep to inline GHC didn't inline `eqTypeRep`, presumably because it ended up being too big. This was unfortunate because it produces a `Maybe`, which will almost always be scrutinized immediately. Split `eqTypeRep` into a worker and a tiny wrapper, and mark the wrapper `INLINABLE`. This change actually seems to reduce Core size, at least in a small test. Reviewers: hvr, bgamari, mpickering Reviewed By: mpickering Subscribers: mpickering, rwbarton, thomie, carter GHC Trac Issues: #14790 Differential Revision: https://phabricator.haskell.org/D4405 >--------------------------------------------------------------- 8529fbba309cd692bbbb0386321515d05a6ed256 libraries/base/Data/Typeable/Internal.hs | 14 +++++++++++--- 1 file changed, 11 insertions(+), 3 deletions(-) diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs index a01a9ff..6c52cc5 100644 --- a/libraries/base/Data/Typeable/Internal.hs +++ b/libraries/base/Data/Typeable/Internal.hs @@ -564,9 +564,17 @@ typeRepTyCon (TrFun {}) = typeRepTyCon $ typeRep @(->) eqTypeRep :: forall k1 k2 (a :: k1) (b :: k2). TypeRep a -> TypeRep b -> Maybe (a :~~: b) eqTypeRep a b - | typeRepFingerprint a == typeRepFingerprint b = Just (unsafeCoerce HRefl) - | otherwise = Nothing - + | sameTypeRep a b = Just (unsafeCoerce# HRefl) + | otherwise = Nothing +-- We want GHC to inline eqTypeRep to get rid of the Maybe +-- in the usual case that it is scrutinized immediately. We +-- split eqTypeRep into a worker and wrapper because otherwise +-- it's much larger than anything we'd want to inline. +{-# INLINABLE eqTypeRep #-} + +sameTypeRep :: forall k1 k2 (a :: k1) (b :: k2). + TypeRep a -> TypeRep b -> Bool +sameTypeRep a b = typeRepFingerprint a == typeRepFingerprint b ------------------------------------------------------------- -- From git at git.haskell.org Thu Feb 15 15:43:00 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Feb 2018 15:43:00 +0000 (UTC) Subject: [commit: ghc] master: Move `iserv` into `utils` and change package name from `iserv-bin` to `iserv` (7c173b9) Message-ID: <20180215154300.A266E3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7c173b9043f7a9a5da46c5b0cc5fc3b38d1a7019/ghc >--------------------------------------------------------------- commit 7c173b9043f7a9a5da46c5b0cc5fc3b38d1a7019 Author: Moritz Angermann Date: Thu Feb 15 13:54:55 2018 +0800 Move `iserv` into `utils` and change package name from `iserv-bin` to `iserv` This is done for consistency. We usually call the package file the same name the folder has. The move into `utils` is done so that we can move the library into `libraries/iserv` and the proxy into `utils/iserv-proxy` and then break the `iserv.cabal` apart. This will make building the cross compiler with TH simpler, because we can build the library and proxy as separate packages. Reviewers: bgamari, simonmar, goldfire, erikd Reviewed By: simonmar Subscribers: tdammers, rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4377 >--------------------------------------------------------------- 7c173b9043f7a9a5da46c5b0cc5fc3b38d1a7019 .gitignore | 3 +- ghc.mk | 13 +-- {iserv => libraries/libiserv}/Makefile | 0 {iserv => libraries/libiserv}/cbits/iservmain.c | 0 libraries/libiserv/ghc.mk | 5 + libraries/libiserv/libiserv.cabal | 39 +++++++ {iserv => libraries/libiserv}/proxy-src/Remote.hs | 0 {iserv => libraries/libiserv}/src/GHCi/Utils.hsc | 0 {iserv => libraries/libiserv}/src/Lib.hs | 0 {iserv => libraries/libiserv}/src/Main.hs | 0 .../libiserv}/src/Remote/Message.hs | 0 {iserv => libraries/libiserv}/src/Remote/Slave.hs | 0 {iserv => utils/iserv-proxy}/Makefile | 0 utils/iserv-proxy/ghc.mk | 113 +++++++++++++++++++++ .../iserv-proxy/iserv-proxy.cabal | 72 +------------ .../Remote.hs => utils/iserv-proxy/src/Main.hs | 0 utils/{hp2ps => iserv}/Makefile | 2 +- {iserv => utils/iserv}/cbits/iservmain.c | 0 {iserv => utils/iserv}/ghc.mk | 66 ++++++------ utils/iserv/iserv.cabal | 44 ++++++++ {iserv => utils/iserv}/src/Main.hs | 0 21 files changed, 248 insertions(+), 109 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 7c173b9043f7a9a5da46c5b0cc5fc3b38d1a7019 From git at git.haskell.org Thu Feb 15 15:45:30 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Feb 2018 15:45:30 +0000 (UTC) Subject: [commit: ghc] wip/angerman/reloc: bump libs (4c732fb) Message-ID: <20180215154530.6C8BF3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/reloc Link : http://ghc.haskell.org/trac/ghc/changeset/4c732fb5f9f75ef399b20e7338f57c68678deafa/ghc >--------------------------------------------------------------- commit 4c732fb5f9f75ef399b20e7338f57c68678deafa Author: Moritz Angermann Date: Thu Feb 15 15:34:34 2018 +0800 bump libs >--------------------------------------------------------------- 4c732fb5f9f75ef399b20e7338f57c68678deafa hadrian | 2 +- libraries/Cabal | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/hadrian b/hadrian index 63a5563..f0a39fd 160000 --- a/hadrian +++ b/hadrian @@ -1 +1 @@ -Subproject commit 63a556382f4b3154ed2ce3a6c8a36f79d9b8e3b1 +Subproject commit f0a39fda5b49b9e4b160ca4fba531c8807c9fb5f diff --git a/libraries/Cabal b/libraries/Cabal index 578d3a5..ccb3350 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit 578d3a50db818223017b8891df268d4200b8ffd3 +Subproject commit ccb3350ddf2c225ed47618df05dc58afe4482a1b From git at git.haskell.org Thu Feb 15 15:45:33 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Feb 2018 15:45:33 +0000 (UTC) Subject: [commit: ghc] wip/angerman/reloc: bump hadrian (e5e55a7) Message-ID: <20180215154533.364743A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/reloc Link : http://ghc.haskell.org/trac/ghc/changeset/e5e55a7cec279d4ea2fc6d63615b3bf26034f456/ghc >--------------------------------------------------------------- commit e5e55a7cec279d4ea2fc6d63615b3bf26034f456 Author: Moritz Angermann Date: Thu Feb 15 18:26:59 2018 +0800 bump hadrian >--------------------------------------------------------------- e5e55a7cec279d4ea2fc6d63615b3bf26034f456 hadrian | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/hadrian b/hadrian index f0a39fd..40709cc 160000 --- a/hadrian +++ b/hadrian @@ -1 +1 @@ -Subproject commit f0a39fda5b49b9e4b160ca4fba531c8807c9fb5f +Subproject commit 40709ccde49de7aaf5581ce2465235bd25fbd398 From git at git.haskell.org Thu Feb 15 15:45:35 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Feb 2018 15:45:35 +0000 (UTC) Subject: [commit: ghc] wip/angerman/reloc's head updated: bump hadrian (e5e55a7) Message-ID: <20180215154535.7712D3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/angerman/reloc' now includes: 0c2350c rts.cabal.in: advertise profiling flavours of libraries, behind a flag 8529fbb Get eqTypeRep to inline 7c173b9 Move `iserv` into `utils` and change package name from `iserv-bin` to `iserv` 4c732fb bump libs e5e55a7 bump hadrian From git at git.haskell.org Fri Feb 16 18:52:15 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Feb 2018 18:52:15 +0000 (UTC) Subject: [commit: ghc] master: Fix #14811 by wiring in $tcUnit# (d5ac582) Message-ID: <20180216185215.9E53C3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d5ac5820111bc957e72c8ce11e59d7cbbdd63526/ghc >--------------------------------------------------------------- commit d5ac5820111bc957e72c8ce11e59d7cbbdd63526 Author: Ryan Scott Date: Fri Feb 16 13:51:27 2018 -0500 Fix #14811 by wiring in $tcUnit# Previously, we were skipping over `$tcUnit#` entirely when wiring in `Typeable` tycons, resulting in #14811. Easily fixed. Test Plan: make test TEST=T14811 Reviewers: bgamari, dfeuer Reviewed By: dfeuer Subscribers: dfeuer, rwbarton, thomie, carter GHC Trac Issues: #14811 Differential Revision: https://phabricator.haskell.org/D4414 >--------------------------------------------------------------- d5ac5820111bc957e72c8ce11e59d7cbbdd63526 compiler/typecheck/TcTypeable.hs | 5 ++--- testsuite/tests/typecheck/should_compile/T14811.hs | 5 +++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 3 files changed, 8 insertions(+), 3 deletions(-) diff --git a/compiler/typecheck/TcTypeable.hs b/compiler/typecheck/TcTypeable.hs index 6fa875b..4c2a69a 100644 --- a/compiler/typecheck/TcTypeable.hs +++ b/compiler/typecheck/TcTypeable.hs @@ -345,9 +345,8 @@ mkPrimTypeableTodos -- Note [Built-in syntax and the OrigNameCache] in IfaceEnv for more. ghcPrimTypeableTyCons :: [TyCon] ghcPrimTypeableTyCons = concat - [ [ runtimeRepTyCon, vecCountTyCon, vecElemTyCon - , funTyCon, tupleTyCon Unboxed 0 ] - , map (tupleTyCon Unboxed) [2..mAX_TUPLE_SIZE] + [ [ runtimeRepTyCon, vecCountTyCon, vecElemTyCon, funTyCon ] + , map (tupleTyCon Unboxed) [0..mAX_TUPLE_SIZE] , map sumTyCon [2..mAX_SUM_SIZE] , primTyCons ] diff --git a/testsuite/tests/typecheck/should_compile/T14811.hs b/testsuite/tests/typecheck/should_compile/T14811.hs new file mode 100644 index 0000000..20c6ab9 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T14811.hs @@ -0,0 +1,5 @@ +{-# language UnboxedTuples #-} +module T14811 where + +data Foo a = Foo (# a #) +data Bar = Bar (# #) diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index c5c106a..9db9393 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -594,3 +594,4 @@ test('T14273', normal, compile, ['-fdefer-type-errors -fno-max-valid-substitutio test('T14732', normal, compile, ['']) test('T14774', [], run_command, ['$MAKE -s --no-print-directory T14774']) test('T14763', normal, compile, ['']) +test('T14811', normal, compile, ['']) From git at git.haskell.org Sun Feb 18 16:59:59 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Feb 2018 16:59:59 +0000 (UTC) Subject: [commit: ghc] master: circleci: Add nightly build using devel2 flavour (a644dff) Message-ID: <20180218165959.97EFF3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a644dffe8830a9f5a65f066fa84df9df494a5fe8/ghc >--------------------------------------------------------------- commit a644dffe8830a9f5a65f066fa84df9df494a5fe8 Author: Ben Gamari Date: Wed Feb 14 17:37:08 2018 -0500 circleci: Add nightly build using devel2 flavour >--------------------------------------------------------------- a644dffe8830a9f5a65f066fa84df9df494a5fe8 .circleci/config.yml | 19 +++++++++++++++++++ 1 file changed, 19 insertions(+) diff --git a/.circleci/config.yml b/.circleci/config.yml index 80bccd7..b93c651 100644 --- a/.circleci/config.yml +++ b/.circleci/config.yml @@ -215,6 +215,24 @@ jobs: - *make - *slowtest + # Nightly build with -DDEBUG using devel2 flavour + "validate-x86_64-linux-debug": + resource_class: xlarge + docker: + - image: haskell:8.2 + environment: + BUILD_FLAVOUR: devel2 + <<: *buildenv + steps: + - *precheckout + - checkout + - *prepare + - *submodules + - *boot + - *configure_unreg + - *make + - *test + workflows: version: 2 validate: @@ -237,6 +255,7 @@ workflows: jobs: - validate-x86_64-linux-unreg - validate-x86_64-linux-llvm + - validate-x86_64-linux-debug notify: webhooks: From git at git.haskell.org Sun Feb 18 17:00:05 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Feb 2018 17:00:05 +0000 (UTC) Subject: [commit: ghc] master: base: Fix changelog entry for openTempFile (9080466) Message-ID: <20180218170005.DFFF43A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/908046608bff517f1cc34d743681e177b0f46a05/ghc >--------------------------------------------------------------- commit 908046608bff517f1cc34d743681e177b0f46a05 Author: Ben Gamari Date: Thu Feb 15 13:01:09 2018 -0500 base: Fix changelog entry for openTempFile This change is present in 4.11.0.0. >--------------------------------------------------------------- 908046608bff517f1cc34d743681e177b0f46a05 libraries/base/changelog.md | 5 ++--- 1 file changed, 2 insertions(+), 3 deletions(-) diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index fe7e377..53a515d 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -4,12 +4,11 @@ * `($!)` is now representation-polymorphic like `($)`. -## 4.11.1.0 *TBA* - * `System.IO.openTempFile` is now thread-safe on Windows. - ## 4.11.0.0 *TBA* * Bundled with GHC 8.4.1 + * `System.IO.openTempFile` is now thread-safe on Windows. + * Deprecated `GHC.Stats.GCStats` interface has been removed. * Add `showHFloat` to `Numeric` From git at git.haskell.org Sun Feb 18 17:00:03 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Feb 2018 17:00:03 +0000 (UTC) Subject: [commit: ghc] master: Implement stopgap solution for #14728 (1ede46d) Message-ID: <20180218170003.1D53E3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1ede46d415757f53af33bc6672bd9d3fba7f205d/ghc >--------------------------------------------------------------- commit 1ede46d415757f53af33bc6672bd9d3fba7f205d Author: Ryan Scott Date: Sun Feb 18 11:00:40 2018 -0500 Implement stopgap solution for #14728 It turns out that one can produce ill-formed Core by combining `GeneralizedNewtypeDeriving`, `TypeInType`, and `TypeFamilies`, as demonstrated in #14728. The root of the problem is allowing the last parameter of a class to appear in a //kind// of an associated type family, as our current approach to deriving associated type family instances simply doesn't work well for that situation. Although it might be possible to properly implement this feature today (see https://ghc.haskell.org/trac/ghc/ticket/14728#comment:3 for a sketch of how this might work), there does not currently exist a performant implementation of the algorithm needed to accomplish this. Until such an implementation surfaces, we will make this corner case of `GeneralizedNewtypeDeriving` an error. Test Plan: make test TEST="T14728a T14728b" Reviewers: bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14728 Differential Revision: https://phabricator.haskell.org/D4402 >--------------------------------------------------------------- 1ede46d415757f53af33bc6672bd9d3fba7f205d compiler/typecheck/TcDeriv.hs | 43 ++++++++++++++++++++-- testsuite/tests/deriving/should_fail/T14728a.hs | 20 ++++++++++ .../tests/deriving/should_fail/T14728a.stderr | 7 ++++ testsuite/tests/deriving/should_fail/T14728b.hs | 16 ++++++++ .../tests/deriving/should_fail/T14728b.stderr | 7 ++++ testsuite/tests/deriving/should_fail/all.T | 2 + 6 files changed, 92 insertions(+), 3 deletions(-) diff --git a/compiler/typecheck/TcDeriv.hs b/compiler/typecheck/TcDeriv.hs index 2290bce..b78cba7 100644 --- a/compiler/typecheck/TcDeriv.hs +++ b/compiler/typecheck/TcDeriv.hs @@ -1308,6 +1308,8 @@ mkNewTypeEqn && ats_ok -- Check (b) from Note [GND and associated type families] && isNothing at_without_last_cls_tv + -- Check (d) from Note [GND and associated type families] + && isNothing at_last_cls_tv_in_kinds -- Check that eta reduction is OK eta_ok = rep_tc_args `lengthAtLeast` nt_eta_arity @@ -1324,6 +1326,12 @@ mkNewTypeEqn at_without_last_cls_tv = find (\tc -> last_cls_tv `notElem` tyConTyVars tc) atf_tcs + at_last_cls_tv_in_kinds + = find (\tc -> any (at_last_cls_tv_in_kind . tyVarKind) + (tyConTyVars tc) + || at_last_cls_tv_in_kind (tyConResKind tc)) atf_tcs + at_last_cls_tv_in_kind kind + = last_cls_tv `elemVarSet` exactTyCoVarsOfType kind at_tcs = classATs cls last_cls_tv = ASSERT( notNull cls_tyvars ) last cls_tyvars @@ -1331,14 +1339,22 @@ mkNewTypeEqn cant_derive_err = vcat [ ppUnless eta_ok eta_msg , ppUnless ats_ok ats_msg - , maybe empty at_tv_msg - at_without_last_cls_tv] + , maybe empty at_without_last_cls_tv_msg + at_without_last_cls_tv + , maybe empty at_last_cls_tv_in_kinds_msg + at_last_cls_tv_in_kinds + ] eta_msg = text "cannot eta-reduce the representation type enough" ats_msg = text "the class has associated data types" - at_tv_msg at_tc = hang + at_without_last_cls_tv_msg at_tc = hang (text "the associated type" <+> quotes (ppr at_tc) <+> text "is not parameterized over the last type variable") 2 (text "of the class" <+> quotes (ppr cls)) + at_last_cls_tv_in_kinds_msg at_tc = hang + (text "the associated type" <+> quotes (ppr at_tc) + <+> text "contains the last type variable") + 2 (text "of the class" <+> quotes (ppr cls) + <+> text "in a kind, which is not (yet) allowed") MASSERT( cls_tys `lengthIs` (classArity cls - 1) ) case mb_strat of @@ -1525,6 +1541,27 @@ However, we must watch out for three things: GHC's termination checker isn't sophisticated enough to conclude that the definition of T MyInt terminates, so UndecidableInstances is required. +(d) For the time being, we do not allow the last type variable of the class to + appear in a /kind/ of an associated type family definition. For instance: + + class C a where + type T1 a -- OK + type T2 (x :: a) -- Illegal: a appears in the kind of x + type T3 y :: a -- Illegal: a appears in the kind of (T3 y) + + The reason we disallow this is because our current approach to deriving + associated type family instances—i.e., by unwrapping the newtype's type + constructor as shown above—is ill-equipped to handle the scenario when + the last type variable appears as an implicit argument. In the worst case, + allowing the last variable to appear in a kind can result in improper Core + being generated (see #14728). + + There is hope for this feature being added some day, as one could + conceivably take a newtype axiom (which witnesses a coercion between a + newtype and its representation type) at lift that through each associated + type at the Core level. See #14728, comment:3 for a sketch of how this + might work. Until then, we disallow this featurette wholesale. + ************************************************************************ * * \subsection[TcDeriv-normal-binds]{Bindings for the various classes} diff --git a/testsuite/tests/deriving/should_fail/T14728a.hs b/testsuite/tests/deriving/should_fail/T14728a.hs new file mode 100644 index 0000000..28cf8e0 --- /dev/null +++ b/testsuite/tests/deriving/should_fail/T14728a.hs @@ -0,0 +1,20 @@ +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE StandaloneDeriving #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE TypeInType #-} +module T14728a where + +import Data.Functor.Identity +import Data.Kind + +class C (a :: Type) where + type T a (x :: a) :: Type + type U z :: a + +instance C () where + type T () '() = Bool + +deriving instance C (Identity a) + +f :: T (Identity ()) ('Identity '()) +f = True diff --git a/testsuite/tests/deriving/should_fail/T14728a.stderr b/testsuite/tests/deriving/should_fail/T14728a.stderr new file mode 100644 index 0000000..b76d073 --- /dev/null +++ b/testsuite/tests/deriving/should_fail/T14728a.stderr @@ -0,0 +1,7 @@ + +T14728a.hs:17:1: error: + • Can't make a derived instance of ‘C (Identity a)’ + (even with cunning GeneralizedNewtypeDeriving): + the associated type ‘T’ contains the last type variable + of the class ‘C’ in a kind, which is not (yet) allowed + • In the stand-alone deriving instance for ‘C (Identity a)’ diff --git a/testsuite/tests/deriving/should_fail/T14728b.hs b/testsuite/tests/deriving/should_fail/T14728b.hs new file mode 100644 index 0000000..7fdfcb3 --- /dev/null +++ b/testsuite/tests/deriving/should_fail/T14728b.hs @@ -0,0 +1,16 @@ +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE StandaloneDeriving #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE TypeInType #-} +module T14728b where + +import Data.Functor.Identity +import Data.Kind + +class C (a :: Type) where + type U z :: a + +instance C () where + type U z = '() + +deriving instance C (Identity a) diff --git a/testsuite/tests/deriving/should_fail/T14728b.stderr b/testsuite/tests/deriving/should_fail/T14728b.stderr new file mode 100644 index 0000000..ee74f8b4 --- /dev/null +++ b/testsuite/tests/deriving/should_fail/T14728b.stderr @@ -0,0 +1,7 @@ + +T14728b.hs:16:1: error: + • Can't make a derived instance of ‘C (Identity a)’ + (even with cunning GeneralizedNewtypeDeriving): + the associated type ‘U’ contains the last type variable + of the class ‘C’ in a kind, which is not (yet) allowed + • In the stand-alone deriving instance for ‘C (Identity a)’ diff --git a/testsuite/tests/deriving/should_fail/all.T b/testsuite/tests/deriving/should_fail/all.T index c9b8469..acd3486 100644 --- a/testsuite/tests/deriving/should_fail/all.T +++ b/testsuite/tests/deriving/should_fail/all.T @@ -69,3 +69,5 @@ test('T12512', omit_ways(['ghci']), compile_fail, ['']) test('T12801', normal, compile_fail, ['']) test('T14365', [extra_files(['T14365B.hs','T14365B.hs-boot'])], multimod_compile_fail, ['T14365A','']) +test('T14728a', normal, compile_fail, ['']) +test('T14728b', normal, compile_fail, ['']) From git at git.haskell.org Sun Feb 18 17:00:10 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Feb 2018 17:00:10 +0000 (UTC) Subject: [commit: ghc] master: Add valid refinement substitution suggestions for typed holes (918c0b3) Message-ID: <20180218170010.0D2F03A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/918c0b393663e88f89becdb8520de477ce6a5463/ghc >--------------------------------------------------------------- commit 918c0b393663e88f89becdb8520de477ce6a5463 Author: Matthías Páll Gissurarson Date: Sun Feb 18 11:01:06 2018 -0500 Add valid refinement substitution suggestions for typed holes This adds valid refinement substitution suggestions for typed holes and documentation thereof. Inspired by Agda's refinement facilities, this extends the typed holes feature to be able to search for valid refinement substitutions, which are substitutions that have one or more holes in them. When the flag `-frefinement-level-substitutions=n` where `n > 0` is passed, we also look for valid refinement substitutions, i.e. substitutions that are valid, but adds more holes. Consider the following: f :: [Integer] -> Integer f = _ Here the valid substitutions suggested will be (with the new `-funclutter-valid-substitutions` flag for less verbosity set): ``` Valid substitutions include f :: [Integer] -> Integer product :: forall (t :: * -> *). Foldable t => forall a. Num a => t a -> a sum :: forall (t :: * -> *). Foldable t => forall a. Num a => t a -> a maximum :: forall (t :: * -> *). Foldable t => forall a. Ord a => t a -> a minimum :: forall (t :: * -> *). Foldable t => forall a. Ord a => t a -> a head :: forall a. [a] -> a (Some substitutions suppressed; use -fmax-valid-substitutions=N or -fno-max-valid-substitutions) ``` When the `-frefinement-level-substitutions=1` flag is given, we additionally compute and report valid refinement substitutions: ``` Valid refinement substitutions include foldl1 _ :: forall (t :: * -> *). Foldable t => forall a. (a -> a -> a) -> t a -> a foldr1 _ :: forall (t :: * -> *). Foldable t => forall a. (a -> a -> a) -> t a -> a head _ :: forall a. [a] -> a last _ :: forall a. [a] -> a error _ :: forall (a :: TYPE r). GHC.Stack.Types.HasCallStack => [Char] -> a errorWithoutStackTrace _ :: forall (a :: TYPE r). [Char] -> a (Some refinement substitutions suppressed; use -fmax-refinement-substitutions=N or -fno-max-refinement-substitutions) ``` Which are substitutions with holes in them. This allows e.g. beginners to discover the fold functions and similar. We find these refinement suggestions by considering substitutions that don't fit the type of the hole, but ones that would fit if given an additional argument. We do this by creating a new type variable with newOpenFlexiTyVarTy (e.g. `t_a1/m[tau:1]`), and then considering substitutions of the type `t_a1/m[tau:1] -> v` where `v` is the type of the hole. Since the simplifier is free to unify this new type variable with any type (and it is cloned before each check to avoid side-effects), we can now discover any identifiers that would fit if given another identifier of a suitable type. This is then generalized so that we can consider any number of additional arguments by setting the `-frefinement-level-substitutions` flag to any number, and then considering substitutions like e.g. `foldl _ _` with two additional arguments. This can e.g. help beginners discover the `fold` functions. This could also help more advanced users figure out which morphisms they can use when arrow chasing. Then you could write `m = _ . m2 . m3` where `m2` and `m3` are some morphisms, and not only get exact fits, but also help in finding morphisms that might get you a little bit closer to where you want to go in the diagram. Reviewers: bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4357 >--------------------------------------------------------------- 918c0b393663e88f89becdb8520de477ce6a5463 compiler/main/DynFlags.hs | 20 ++ compiler/typecheck/TcErrors.hs | 290 ++++++++++++++++----- compiler/typecheck/TcRnTypes.hs | 16 +- docs/users_guide/glasgow_exts.rst | 116 ++++++++- .../abstract_refinement_substitutions.hs | 7 + .../abstract_refinement_substitutions.stderr | 290 +++++++++++++++++++++ testsuite/tests/typecheck/should_compile/all.T | 2 + .../should_compile/refinement_substitutions.hs | 7 + .../should_compile/refinement_substitutions.stderr | 188 +++++++++++++ 9 files changed, 857 insertions(+), 79 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 918c0b393663e88f89becdb8520de477ce6a5463 From git at git.haskell.org Sun Feb 18 17:00:12 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Feb 2018 17:00:12 +0000 (UTC) Subject: [commit: ghc] master: Build Haddocks with --quickjump (9ff4cce) Message-ID: <20180218170012.C67113A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9ff4cce373765cec064e2a41d4c6ddd84b873f04/ghc >--------------------------------------------------------------- commit 9ff4cce373765cec064e2a41d4c6ddd84b873f04 Author: Ben Gamari Date: Sun Feb 18 11:01:59 2018 -0500 Build Haddocks with --quickjump By request of @alexbiehl. CCing @snowleopard and @alpmestan as the same should be done in Hadrian. Bumps haddock submodule. Reviewers: alexbiehl Reviewed By: alexbiehl Subscribers: rwbarton, thomie, carter, snowleopard, alpmestan, alexbiehl Differential Revision: https://phabricator.haskell.org/D4365 >--------------------------------------------------------------- 9ff4cce373765cec064e2a41d4c6ddd84b873f04 rules/haddock.mk | 1 + utils/haddock | 2 +- 2 files changed, 2 insertions(+), 1 deletion(-) diff --git a/rules/haddock.mk b/rules/haddock.mk index 35748c3..37182bc 100644 --- a/rules/haddock.mk +++ b/rules/haddock.mk @@ -65,6 +65,7 @@ endif --dump-interface=$$($$($1_PACKAGE)-$$($1_$2_VERSION)_HADDOCK_FILE) \ --html \ --hoogle \ + --quickjump \ --title="$$($1_PACKAGE)-$$($1_$2_VERSION)$$(if $$(strip $$($1_$2_SYNOPSIS)),: $$(strip $$($1_$2_SYNOPSIS)),)" \ --prologue="$1/$2/haddock-prologue.txt" \ --optghc="-D__HADDOCK_VERSION__=$$(HADDOCK_VERSION_STRING)" \ diff --git a/utils/haddock b/utils/haddock index dd80ae1..0ef6a26 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit dd80ae1773ea6aae48c3c5a899d510699783d6ee +Subproject commit 0ef6a26d49fc2b3a5785a55d95b64f77c40e58ad From git at git.haskell.org Sun Feb 18 17:00:15 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Feb 2018 17:00:15 +0000 (UTC) Subject: [commit: ghc] master: myThreadId# is trivial; make it an inline primop (c05529c) Message-ID: <20180218170015.98A013A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c05529c2219d12ee950eb8972e1aca135cd8e032/ghc >--------------------------------------------------------------- commit c05529c2219d12ee950eb8972e1aca135cd8e032 Author: Simon Marlow Date: Sun Feb 18 11:09:19 2018 -0500 myThreadId# is trivial; make it an inline primop The pattern `threadCapability =<< myThreadId` is used a lot in code that uses `hs_try_putmvar`, I want to make it cheaper. Test Plan: validate Reviewers: bgamari, erikd Reviewed By: bgamari Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4381 >--------------------------------------------------------------- c05529c2219d12ee950eb8972e1aca135cd8e032 compiler/codeGen/StgCmmPrim.hs | 3 +++ compiler/prelude/primops.txt.pp | 1 - rts/PrimOps.cmm | 5 ----- rts/RtsSymbols.c | 1 - 4 files changed, 3 insertions(+), 7 deletions(-) diff --git a/compiler/codeGen/StgCmmPrim.hs b/compiler/codeGen/StgCmmPrim.hs index 7661e9f..b5cd267 100644 --- a/compiler/codeGen/StgCmmPrim.hs +++ b/compiler/codeGen/StgCmmPrim.hs @@ -306,6 +306,9 @@ emitPrimOp dflags [res] GetCCSOfOp [arg] emitPrimOp _ [res] GetCurrentCCSOp [_dummy_arg] = emitAssign (CmmLocal res) cccsExpr +emitPrimOp _ [res] MyThreadIdOp [] + = emitAssign (CmmLocal res) currentTSOExpr + emitPrimOp dflags [res] ReadMutVarOp [mutv] = emitAssign (CmmLocal res) (cmmLoadIndexW dflags mutv (fixedHdrSizeW dflags) (gcWord dflags)) diff --git a/compiler/prelude/primops.txt.pp b/compiler/prelude/primops.txt.pp index 43e8f53..038d350 100644 --- a/compiler/prelude/primops.txt.pp +++ b/compiler/prelude/primops.txt.pp @@ -2403,7 +2403,6 @@ primop YieldOp "yield#" GenPrimOp primop MyThreadIdOp "myThreadId#" GenPrimOp State# RealWorld -> (# State# RealWorld, ThreadId# #) with - out_of_line = True has_side_effects = True primop LabelThreadOp "labelThread#" GenPrimOp diff --git a/rts/PrimOps.cmm b/rts/PrimOps.cmm index fb9db0a..6d57fd8 100644 --- a/rts/PrimOps.cmm +++ b/rts/PrimOps.cmm @@ -943,11 +943,6 @@ stg_yieldzh () jump stg_yield_noregs(); } -stg_myThreadIdzh () -{ - return (CurrentTSO); -} - stg_labelThreadzh ( gcptr threadid, W_ addr ) { #if defined(DEBUG) || defined(TRACING) || defined(DTRACE) diff --git a/rts/RtsSymbols.c b/rts/RtsSymbols.c index 2ea6713..e53a056 100644 --- a/rts/RtsSymbols.c +++ b/rts/RtsSymbols.c @@ -641,7 +641,6 @@ SymI_HasProto(lookupSymbol) \ SymI_HasProto(stg_makeStablePtrzh) \ SymI_HasProto(stg_mkApUpd0zh) \ - SymI_HasProto(stg_myThreadIdzh) \ SymI_HasProto(stg_labelThreadzh) \ SymI_HasProto(stg_newArrayzh) \ SymI_HasProto(stg_copyArrayzh) \ From git at git.haskell.org Sun Feb 18 17:00:18 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Feb 2018 17:00:18 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Add newline to test output (d924c17) Message-ID: <20180218170018.5C9AF3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d924c17dfc8d277a7460fa57217a9ab82f78ee4e/ghc >--------------------------------------------------------------- commit d924c17dfc8d277a7460fa57217a9ab82f78ee4e Author: Douglas Wilson Date: Sun Feb 18 11:10:21 2018 -0500 testsuite: Add newline to test output Reviewers: bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4389 >--------------------------------------------------------------- d924c17dfc8d277a7460fa57217a9ab82f78ee4e testsuite/tests/concurrent/should_run/setnumcapabilities001.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/concurrent/should_run/setnumcapabilities001.hs b/testsuite/tests/concurrent/should_run/setnumcapabilities001.hs index 27685f0..a18d75a 100644 --- a/testsuite/tests/concurrent/should_run/setnumcapabilities001.hs +++ b/testsuite/tests/concurrent/should_run/setnumcapabilities001.hs @@ -15,7 +15,7 @@ main = do forM_ (cycle ([n,n-1..1] ++ [2..n-1])) $ \m -> do setNumCapabilities m threadDelay t - printf "%d" (nqueens q) + printf "%d\n" (nqueens q) killThread t -- If we don't kill the child thread, it might be about to -- call setNumCapabilities() in C when the main thread exits, From git at git.haskell.org Sun Feb 18 17:00:21 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Feb 2018 17:00:21 +0000 (UTC) Subject: [commit: ghc] master: Tidy up and consolidate canned CmmReg and CmmGlobals (ccda486) Message-ID: <20180218170021.3C45D3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ccda4862102104e080a200e4d9c2ca8f42eb5b70/ghc >--------------------------------------------------------------- commit ccda4862102104e080a200e4d9c2ca8f42eb5b70 Author: Simon Marlow Date: Sun Feb 18 11:08:52 2018 -0500 Tidy up and consolidate canned CmmReg and CmmGlobals Test Plan: validate Reviewers: bgamari, erikd Reviewed By: bgamari Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4380 >--------------------------------------------------------------- ccda4862102104e080a200e4d9c2ca8f42eb5b70 compiler/cmm/CmmExpr.hs | 13 +++++++++-- compiler/cmm/CmmLayoutStack.hs | 16 ++++++------- compiler/cmm/CmmSink.hs | 2 +- compiler/cmm/CmmUtils.hs | 18 +++++++++++++++ compiler/codeGen/CgUtils.hs | 2 +- compiler/codeGen/StgCmmBind.hs | 11 +++++---- compiler/codeGen/StgCmmCon.hs | 4 ++-- compiler/codeGen/StgCmmForeign.hs | 47 +++++++++++++-------------------------- compiler/codeGen/StgCmmHeap.hs | 9 ++++---- compiler/codeGen/StgCmmLayout.hs | 3 +-- compiler/codeGen/StgCmmPrim.hs | 18 +++++++-------- compiler/codeGen/StgCmmProf.hs | 15 +++++-------- compiler/codeGen/StgCmmUtils.hs | 2 +- 13 files changed, 83 insertions(+), 77 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ccda4862102104e080a200e4d9c2ca8f42eb5b70 From git at git.haskell.org Sun Feb 18 17:00:24 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Feb 2018 17:00:24 +0000 (UTC) Subject: [commit: ghc] master: CBE: re-introduce bgamari's fixes (4e513bf) Message-ID: <20180218170024.083753A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4e513bf758c32804fc71b98215f96e8481697a36/ghc >--------------------------------------------------------------- commit 4e513bf758c32804fc71b98215f96e8481697a36 Author: Michal Terepeta Date: Sun Feb 18 11:09:40 2018 -0500 CBE: re-introduce bgamari's fixes During some recent work on CBE we discovered that `zipWith` is used to check for equality, but that doesn't quite work if lists are of different lengths! This was fixed by bgamari, but unfortunately the fix had to be rolled back due to other changes in CBE in 50adbd7c5fe5894d3e6e2a58b353ed07e5f8949d. Since I wanted to have another look at CBE anyway, we agreed that the first thing to do would be to re-introduce the fix. Sadly I don't have any actual test case that would exercise this. Signed-off-by: Michal Terepeta Test Plan: ./validate Reviewers: bgamari, simonmar Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14226 Differential Revision: https://phabricator.haskell.org/D4387 >--------------------------------------------------------------- 4e513bf758c32804fc71b98215f96e8481697a36 compiler/cmm/CmmCommonBlockElim.hs | 11 ++++++++--- 1 file changed, 8 insertions(+), 3 deletions(-) diff --git a/compiler/cmm/CmmCommonBlockElim.hs b/compiler/cmm/CmmCommonBlockElim.hs index 2c889b3..ba3b1c8 100644 --- a/compiler/cmm/CmmCommonBlockElim.hs +++ b/compiler/cmm/CmmCommonBlockElim.hs @@ -209,7 +209,7 @@ eqMiddleWith eqBid (CmmStore l1 r1) (CmmStore l2 r2) = eqExprWith eqBid l1 l2 && eqExprWith eqBid r1 r2 eqMiddleWith eqBid (CmmUnsafeForeignCall t1 r1 a1) (CmmUnsafeForeignCall t2 r2 a2) - = t1 == t2 && r1 == r2 && and (zipWith (eqExprWith eqBid) a1 a2) + = t1 == t2 && r1 == r2 && eqListWith (eqExprWith eqBid) a1 a2 eqMiddleWith _ _ _ = False eqExprWith :: (BlockId -> BlockId -> Bool) @@ -224,7 +224,7 @@ eqExprWith eqBid = eq CmmStackSlot a1 i1 `eq` CmmStackSlot a2 i2 = eqArea a1 a2 && i1==i2 _e1 `eq` _e2 = False - xs `eqs` ys = and (zipWith eq xs ys) + xs `eqs` ys = eqListWith eq xs ys eqLit (CmmBlock id1) (CmmBlock id2) = eqBid id1 id2 eqLit l1 l2 = l1 == l2 @@ -247,7 +247,7 @@ eqBlockBodyWith eqBid block block' (_,m',l') = blockSplit block' nodes' = filter (not . dont_care) (blockToList m') - equal = and (zipWith (eqMiddleWith eqBid) nodes nodes') && + equal = eqListWith (eqMiddleWith eqBid) nodes nodes' && eqLastWith eqBid l l' @@ -266,6 +266,11 @@ eqMaybeWith eltEq (Just e) (Just e') = eltEq e e' eqMaybeWith _ Nothing Nothing = True eqMaybeWith _ _ _ = False +eqListWith :: (a -> b -> Bool) -> [a] -> [b] -> Bool +eqListWith f (a : as) (b : bs) = f a b && eqListWith f as bs +eqListWith _ [] [] = True +eqListWith _ _ _ = False + -- | Given a block map, ensure that all "target" blocks are covered by -- the same ticks as the respective "source" blocks. This not only -- means copying ticks, but also adjusting tick scopes where From git at git.haskell.org Sun Feb 18 17:00:26 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Feb 2018 17:00:26 +0000 (UTC) Subject: [commit: ghc] master: Remove doubled words (bfb90bc) Message-ID: <20180218170026.C541D3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bfb90bcab844ded9051370b822f0a9582c35e83e/ghc >--------------------------------------------------------------- commit bfb90bcab844ded9051370b822f0a9582c35e83e Author: Adam Sandberg Eriksson Date: Sun Feb 18 11:08:31 2018 -0500 Remove doubled words Reviewers: bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4368 >--------------------------------------------------------------- bfb90bcab844ded9051370b822f0a9582c35e83e docs/users_guide/8.2.1-notes.rst | 2 +- docs/users_guide/phases.rst | 5 ++--- 2 files changed, 3 insertions(+), 4 deletions(-) diff --git a/docs/users_guide/8.2.1-notes.rst b/docs/users_guide/8.2.1-notes.rst index ca045ee..d46f08d 100644 --- a/docs/users_guide/8.2.1-notes.rst +++ b/docs/users_guide/8.2.1-notes.rst @@ -154,7 +154,7 @@ Compiler directive on undefined identifiers. - GHC will no longer automatically infer the kind of higher-rank type synonyms; - you must explicitly explicitly annotate the synonym with a kind signature. + you must explicitly annotate the synonym with a kind signature. For example, given:: data T :: (forall k. k -> Type) -> Type diff --git a/docs/users_guide/phases.rst b/docs/users_guide/phases.rst index da8a84b..ad9daf1 100644 --- a/docs/users_guide/phases.rst +++ b/docs/users_guide/phases.rst @@ -900,9 +900,8 @@ for example). The threaded runtime system provides the following benefits: - It enables the :rts-flag:`-N ⟨x⟩` RTS option to be used, - which allows threads to run in parallelparallelism on a - multiprocessormultiprocessorSMP or multicoremulticore machine. - See :ref:`using-smp`. + which allows threads to run in parallel on a multiprocessor + or multicore machine. See :ref:`using-smp`. - If a thread makes a foreign call (and the call is not marked ``unsafe``), then other Haskell threads in the program will From git at git.haskell.org Sun Feb 18 17:00:30 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Feb 2018 17:00:30 +0000 (UTC) Subject: [commit: ghc] master: Rename the types in a GADT constructor in toposorted order (043466b) Message-ID: <20180218170030.2D7483A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/043466b9aac403553e2aaf8054c064016f963f80/ghc >--------------------------------------------------------------- commit 043466b9aac403553e2aaf8054c064016f963f80 Author: Ryan Scott Date: Sun Feb 18 11:14:26 2018 -0500 Rename the types in a GADT constructor in toposorted order Previously, we were extracting the free variables from a GADT constructor in an incorrect order, which caused the type variables for the constructor's type signature to end up in non-toposorted order. Thankfully, rearranging the order of types during renaming makes swift work of this bug. This fixes a regression introduced in commit fa29df02a1b0b926afb2525a258172dcbf0ea460. For whatever reason, that commit also commented out a significant portion of the `T13123` test. This code appears to work, so I've opted to uncomment it. Test Plan: make test TEST=T14808 Reviewers: simonpj, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14808 Differential Revision: https://phabricator.haskell.org/D4413 >--------------------------------------------------------------- 043466b9aac403553e2aaf8054c064016f963f80 compiler/rename/RnSource.hs | 5 ++++- testsuite/tests/gadt/T14808.hs | 12 ++++++++++++ testsuite/tests/gadt/all.T | 1 + testsuite/tests/th/T13123.hs | 2 -- 4 files changed, 17 insertions(+), 3 deletions(-) diff --git a/compiler/rename/RnSource.hs b/compiler/rename/RnSource.hs index e51d9ef..5c7f538 100644 --- a/compiler/rename/RnSource.hs +++ b/compiler/rename/RnSource.hs @@ -1917,7 +1917,10 @@ rnConDecl decl@(ConDeclGADT { con_names = names ; let explicit_tkvs = hsQTvExplicit qtvs theta = hsConDeclTheta mcxt arg_tys = hsConDeclArgTys args - ; free_tkvs <- extractHsTysRdrTyVarsDups (res_ty : theta ++ arg_tys) + -- We must ensure that we extract the free tkvs in the + -- order of theta, then arg_tys, then res_ty. Failing to + -- do so resulted in #14808. + ; free_tkvs <- extractHsTysRdrTyVarsDups (theta ++ arg_tys ++ [res_ty]) ; free_tkvs <- extractHsTvBndrs explicit_tkvs free_tkvs ; let ctxt = ConDeclCtx new_names diff --git a/testsuite/tests/gadt/T14808.hs b/testsuite/tests/gadt/T14808.hs new file mode 100644 index 0000000..726f502 --- /dev/null +++ b/testsuite/tests/gadt/T14808.hs @@ -0,0 +1,12 @@ +{-# LANGUAGE ConstraintKinds #-} +{-# LANGUAGE GADTs #-} +{-# LANGUAGE TypeApplications #-} +module T14808 where + +import Data.Kind + +data ECC ctx f a where + ECC :: ctx => f a -> ECC ctx f a + +f :: [()] -> ECC () [] () +f = ECC @() @[] @() diff --git a/testsuite/tests/gadt/all.T b/testsuite/tests/gadt/all.T index 59ec307..4c8eb80 100644 --- a/testsuite/tests/gadt/all.T +++ b/testsuite/tests/gadt/all.T @@ -116,3 +116,4 @@ test('T12087', normal, compile_fail, ['']) test('T12468', normal, compile_fail, ['']) test('T14320', normal, compile, ['']) test('T14719', normal, compile_fail, ['-fdiagnostics-show-caret']) +test('T14808', normal, compile, ['']) diff --git a/testsuite/tests/th/T13123.hs b/testsuite/tests/th/T13123.hs index dbc071c..d7e1006 100644 --- a/testsuite/tests/th/T13123.hs +++ b/testsuite/tests/th/T13123.hs @@ -8,7 +8,6 @@ module T13123 where import GHC.Exts (Constraint) -{- $([d| idProxy :: forall proxy (a :: k). proxy a -> proxy a idProxy x = x |]) @@ -32,7 +31,6 @@ $([d| class Foo b where $([d| data GADT where MkGADT :: forall proxy (a :: k). proxy a -> GADT |]) --} $([d| data Dec13 :: (* -> Constraint) -> * where MkDec13 :: c a => a -> Dec13 c From git at git.haskell.org Sun Feb 18 17:00:33 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Feb 2018 17:00:33 +0000 (UTC) Subject: [commit: ghc] master: StgLint overhaul (7f389a5) Message-ID: <20180218170033.0F81D3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7f389a580f42a105623853adad15ab3323b41ed5/ghc >--------------------------------------------------------------- commit 7f389a580f42a105623853adad15ab3323b41ed5 Author: Ömer Sinan Ağacan Date: Sun Feb 18 11:12:53 2018 -0500 StgLint overhaul - Remove all type checks - Check two STG invariants (no unboxed let bindings, variables defined before used) and post-unarisation invariants. See the module header and #14787. This version validates with `-dstg-lint` added to `GhcStage2HcOpts` and `GhcLibHcOpts` and `EXTRA_HC_OPTS`. Unarise changes: - `unariseConArgBinder` and `unariseFunArgBinder` functions were almost the same; only difference was when unarising fun args we keep void args while in con args we drop them. A new function `unariseArgBinder` added with a `Bool` argument for whether we're unarising a con arg. `unariseConArgBinder` and `unariseFunArgBinder` are now defined as unariseConArgBinder = unarsieArgBinder True -- data con unariseFunArgBinder = unariseArgBinder False -- not data con - A bug in `unariseConArgBinder` and `unariseFunArgBinder` (which are just calls to `unariseArgBinder` now) that invalidated the post-unarise invariants when the argument has single type rep (i.e. `length (typePrimRep x) == 1`) fixed. This isn't a correctness issue (it's fine not to unarise if a variable is already represented as single value), but it triggers StgLint. Test Plan: - Pass testsuite with `-dstg-lint` [done] - Boot stage2 (including libraries) with `-dstg-lint` [done] Reviewers: simonpj, bgamari Reviewed By: bgamari Subscribers: duog, rwbarton, thomie, carter GHC Trac Issues: #14787 Differential Revision: https://phabricator.haskell.org/D4404 >--------------------------------------------------------------- 7f389a580f42a105623853adad15ab3323b41ed5 compiler/simplStg/SimplStg.hs | 12 +- compiler/simplStg/UnariseStg.hs | 60 ++++-- compiler/stgSyn/StgLint.hs | 459 +++++++++++++--------------------------- compiler/stgSyn/StgSyn.hs | 1 + docs/users_guide/debugging.rst | 2 +- 5 files changed, 196 insertions(+), 338 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 7f389a580f42a105623853adad15ab3323b41ed5 From git at git.haskell.org Sun Feb 18 17:00:36 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Feb 2018 17:00:36 +0000 (UTC) Subject: [commit: ghc] master: Improve error message for UNPACK/strictness annotations. (fc33f8b) Message-ID: <20180218170036.A32CE3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fc33f8b31b9c23cc12f02a028bbaeab06ba8fe96/ghc >--------------------------------------------------------------- commit fc33f8b31b9c23cc12f02a028bbaeab06ba8fe96 Author: HE, Tao Date: Sun Feb 18 11:10:37 2018 -0500 Improve error message for UNPACK/strictness annotations. Print different error message for improper UNPACK and strictness annotations. Fix Trac #14761. Signed-off-by: HE, Tao Test Plan: make test TEST="T7210 T14761a T14761b" Reviewers: goldfire, bgamari, RyanGlScott, simonpj Reviewed By: RyanGlScott, simonpj Subscribers: simonpj, goldfire, rwbarton, thomie, carter GHC Trac Issues: #14761 Differential Revision: https://phabricator.haskell.org/D4397 >--------------------------------------------------------------- fc33f8b31b9c23cc12f02a028bbaeab06ba8fe96 compiler/typecheck/TcHsType.hs | 13 ++++++++++--- testsuite/tests/typecheck/should_fail/T14761a.hs | 3 +++ testsuite/tests/typecheck/should_fail/T14761a.stderr | 7 +++++++ testsuite/tests/typecheck/should_fail/T14761b.hs | 5 +++++ testsuite/tests/typecheck/should_fail/T14761b.stderr | 7 +++++++ testsuite/tests/typecheck/should_fail/T7210.stderr | 1 + testsuite/tests/typecheck/should_fail/all.T | 2 ++ 7 files changed, 35 insertions(+), 3 deletions(-) diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs index 08dc56d..a8b9fe8 100644 --- a/compiler/typecheck/TcHsType.hs +++ b/compiler/typecheck/TcHsType.hs @@ -559,11 +559,18 @@ tc_hs_type :: TcTyMode -> HsType GhcRn -> TcKind -> TcM TcType tc_hs_type mode (HsParTy ty) exp_kind = tc_lhs_type mode ty exp_kind tc_hs_type mode (HsDocTy ty _) exp_kind = tc_lhs_type mode ty exp_kind -tc_hs_type _ ty@(HsBangTy {}) _ +tc_hs_type _ ty@(HsBangTy bang _) _ -- While top-level bangs at this point are eliminated (eg !(Maybe Int)), -- other kinds of bangs are not (eg ((!Maybe) Int)). These kinds of - -- bangs are invalid, so fail. (#7210) - = failWithTc (text "Unexpected strictness annotation:" <+> ppr ty) + -- bangs are invalid, so fail. (#7210, #14761) + = do { let bangError err = failWith $ + text "Unexpected" <+> text err <+> text "annotation:" <+> ppr ty $$ + text err <+> text "annotation cannot appear nested inside a type" + ; case bang of + HsSrcBang _ SrcUnpack _ -> bangError "UNPACK" + HsSrcBang _ SrcNoUnpack _ -> bangError "NOUNPACK" + HsSrcBang _ NoSrcUnpack SrcLazy -> bangError "laziness" + HsSrcBang _ _ _ -> bangError "strictness" } tc_hs_type _ ty@(HsRecTy _) _ -- Record types (which only show up temporarily in constructor -- signatures) should have been removed by now diff --git a/testsuite/tests/typecheck/should_fail/T14761a.hs b/testsuite/tests/typecheck/should_fail/T14761a.hs new file mode 100644 index 0000000..f195320 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T14761a.hs @@ -0,0 +1,3 @@ +module T14761a where + +data A = A { a :: {-# UNPACK #-} Maybe Int} diff --git a/testsuite/tests/typecheck/should_fail/T14761a.stderr b/testsuite/tests/typecheck/should_fail/T14761a.stderr new file mode 100644 index 0000000..8eb4580 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T14761a.stderr @@ -0,0 +1,7 @@ + +T14761a.hs:3:19: + Unexpected UNPACK annotation: {-# UNPACK #-}Maybe + UNPACK annotation cannot appear nested inside a type + In the type ‘{-# UNPACK #-}Maybe Int’ + In the definition of data constructor ‘A’ + In the data declaration for ‘A’ diff --git a/testsuite/tests/typecheck/should_fail/T14761b.hs b/testsuite/tests/typecheck/should_fail/T14761b.hs new file mode 100644 index 0000000..cd51962 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T14761b.hs @@ -0,0 +1,5 @@ +{-# LANGUAGE BangPatterns #-} + +module T14761b where + +data A = A { a :: ! Maybe Int} diff --git a/testsuite/tests/typecheck/should_fail/T14761b.stderr b/testsuite/tests/typecheck/should_fail/T14761b.stderr new file mode 100644 index 0000000..8357187 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T14761b.stderr @@ -0,0 +1,7 @@ + +T14761b.hs:5:19: + Unexpected strictness annotation: !Maybe + strictness annotation cannot appear nested inside a type + In the type ‘!Maybe Int’ + In the definition of data constructor ‘A’ + In the data declaration for ‘A’ diff --git a/testsuite/tests/typecheck/should_fail/T7210.stderr b/testsuite/tests/typecheck/should_fail/T7210.stderr index a7ee2af..314ffa7 100644 --- a/testsuite/tests/typecheck/should_fail/T7210.stderr +++ b/testsuite/tests/typecheck/should_fail/T7210.stderr @@ -1,6 +1,7 @@ T7210.hs:5:19: Unexpected strictness annotation: !IntMap + strictness annotation cannot appear nested inside a type In the type ‘!IntMap Int’ In the definition of data constructor ‘C’ In the data declaration for ‘T’ diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index b8c3c4c..20ed5a4 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -465,3 +465,5 @@ test('MissingExportList03', normal, compile_fail, ['']) test('T14618', normal, compile_fail, ['']) test('T14607', normal, compile, ['']) test('T14605', normal, compile_fail, ['']) +test('T14761a', normal, compile_fail, ['']) +test('T14761b', normal, compile_fail, ['']) From git at git.haskell.org Sun Feb 18 17:06:33 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Feb 2018 17:06:33 +0000 (UTC) Subject: [commit: packages/haskeline] master: Update homepage (#70) (9a3d39c) Message-ID: <20180218170633.BD5283A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/9a3d39c5c2bbb20c2a8cd3a5b867755c41fecb25 >--------------------------------------------------------------- commit 9a3d39c5c2bbb20c2a8cd3a5b867755c41fecb25 Author: Taylor Fausak Date: Tue Nov 7 18:07:04 2017 -0600 Update homepage (#70) Unfortunately trac.haskell.org doesn't exist anymore. >--------------------------------------------------------------- 9a3d39c5c2bbb20c2a8cd3a5b867755c41fecb25 haskeline.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/haskeline.cabal b/haskeline.cabal index e15ada4..700fada 100644 --- a/haskeline.cabal +++ b/haskeline.cabal @@ -16,7 +16,7 @@ Description: Haskell programs. . Haskeline runs both on POSIX-compatible systems and on Windows. -Homepage: http://trac.haskell.org/haskeline +Homepage: https://github.com/judah/haskeline Bug-Reports: https://github.com/judah/haskeline/issues Stability: Stable Build-Type: Simple From git at git.haskell.org Sun Feb 18 17:06:35 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Feb 2018 17:06:35 +0000 (UTC) Subject: [commit: packages/haskeline] master: Bump version to 0.7.4.1 and add changelog. (6f7e422) Message-ID: <20180218170635.C274D3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/6f7e422f6d47a54621951d72c2de41bbd872e586 >--------------------------------------------------------------- commit 6f7e422f6d47a54621951d72c2de41bbd872e586 Author: Judah Jacobson Date: Sat Dec 2 04:19:44 2017 -0800 Bump version to 0.7.4.1 and add changelog. >--------------------------------------------------------------- 6f7e422f6d47a54621951d72c2de41bbd872e586 Changelog | 5 +++++ haskeline.cabal | 2 +- 2 files changed, 6 insertions(+), 1 deletion(-) diff --git a/Changelog b/Changelog index e3e6d05..941eaca 100644 --- a/Changelog +++ b/Changelog @@ -1,3 +1,8 @@ +Changed in version 0.7.4.1: + * Bump upper bound on base to support ghc-8.4 + * Use `TChan` from `stm` rather than `Chan` + * Update the homepage since trac.haskell.org has shut down + Changed in version 0.7.4.0: * Properly process Unicode key events on Windows. * Add an instance MonadExcept IdentityT. diff --git a/haskeline.cabal b/haskeline.cabal index 700fada..1123a45 100644 --- a/haskeline.cabal +++ b/haskeline.cabal @@ -1,6 +1,6 @@ Name: haskeline Cabal-Version: >=1.10 -Version: 0.7.4.0 +Version: 0.7.4.1 Category: User Interfaces License: BSD3 License-File: LICENSE From git at git.haskell.org Sun Feb 18 17:06:37 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Feb 2018 17:06:37 +0000 (UTC) Subject: [commit: packages/haskeline] master: Add a `stack.yaml` file, for convenience. (30c2f57) Message-ID: <20180218170637.C8DED3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/30c2f5769ef9bb13e0f0f5bac987f62755dd8ea2 >--------------------------------------------------------------- commit 30c2f5769ef9bb13e0f0f5bac987f62755dd8ea2 Author: Judah Jacobson Date: Sat Dec 2 04:22:11 2017 -0800 Add a `stack.yaml` file, for convenience. >--------------------------------------------------------------- 30c2f5769ef9bb13e0f0f5bac987f62755dd8ea2 .gitignore | 1 + stack.yaml | 4 ++++ 2 files changed, 5 insertions(+) diff --git a/.gitignore b/.gitignore index b19cb2b..a41c477 100644 --- a/.gitignore +++ b/.gitignore @@ -2,3 +2,4 @@ GNUmakefile dist/ dist-install ghc.mk +.stack-work diff --git a/stack.yaml b/stack.yaml new file mode 100644 index 0000000..bb59f14 --- /dev/null +++ b/stack.yaml @@ -0,0 +1,4 @@ +resolver: lts-9.14 + +packages: +- . From git at git.haskell.org Sun Feb 18 17:06:39 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Feb 2018 17:06:39 +0000 (UTC) Subject: [commit: packages/haskeline] master: Clean up the rest of the references to trac.haskell.org. (#73) (0c1a6b1) Message-ID: <20180218170639.CEAC63A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/0c1a6b1a7ec05df9520972bb3a857ba4aa7d29cd >--------------------------------------------------------------- commit 0c1a6b1a7ec05df9520972bb3a857ba4aa7d29cd Author: Judah Jacobson Date: Sun Dec 10 21:40:13 2017 -0800 Clean up the rest of the references to trac.haskell.org. (#73) Also bump to 0.7.4.2. >--------------------------------------------------------------- 0c1a6b1a7ec05df9520972bb3a857ba4aa7d29cd Changelog | 3 +++ README.md | 6 +++--- System/Console/Haskeline.hs | 2 +- 3 files changed, 7 insertions(+), 4 deletions(-) diff --git a/Changelog b/Changelog index 941eaca..9740875 100644 --- a/Changelog +++ b/Changelog @@ -1,3 +1,6 @@ +Changed in version 0.7.4.2: + * Clean up the rest of the references to trac.haskell.org + Changed in version 0.7.4.1: * Bump upper bound on base to support ghc-8.4 * Use `TChan` from `stm` rather than `Chan` diff --git a/README.md b/README.md index 078f5f8..1b383e6 100644 --- a/README.md +++ b/README.md @@ -17,10 +17,10 @@ Further documentation is also available at ## Features: - - Provides a [rich line editing interface](http://trac.haskell.org/haskeline/wiki/KeyBindings). - - A `~/.haskeline` file allows customization of [preferences](http://trac.haskell.org/haskeline/wiki/UserPrefs) and [custom key bindings](http://trac.haskell.org/haskeline/wiki/CustomKeyBindings). + - Provides a [rich line editing interface](https://github.com/judah/haskeline/wiki/KeyBindings). + - A `~/.haskeline` file allows customization of [preferences](https://github.com/judah/haskeline/wiki/UserPreferences) and [custom key bindings](https://github.com/judah/haskeline/wiki/CustomKeyBindings). - Runs on POSIX-compatible systems, using the [terminfo](http://github.com/judah/terminfo) library to support non-ANSI terminals. - Runs on Windows using MinGW. - - [Supports Unicode](http://trac.haskell.org/haskeline/wiki/UnicodeSupport) cross-platform. + - [Supports Unicode](https://github.com/judah/haskeline/wiki/UnicodeSupport) cross-platform. - History recall and incremental search. - Custom tab completion functions which may run in an arbitrary monad. diff --git a/System/Console/Haskeline.hs b/System/Console/Haskeline.hs index 5ba9a62..98c0c6c 100644 --- a/System/Console/Haskeline.hs +++ b/System/Console/Haskeline.hs @@ -4,7 +4,7 @@ A rich user interface for line input in command-line programs. Haskeline is Unicode-aware and runs both on POSIX-compatible systems and on Windows. Users may customize the interface with a @~/.haskeline@ file; see - for more information. + for more information. An example use of this library for a simple read-eval-print loop (REPL) is the following: From git at git.haskell.org Sun Feb 18 17:06:41 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Feb 2018 17:06:41 +0000 (UTC) Subject: [commit: packages/haskeline] master: Actually bump the Cabal version. (019e08f) Message-ID: <20180218170641.D4E883A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/019e08f2c91b7cc45e5fb98189193a9f5c2d2d57 >--------------------------------------------------------------- commit 019e08f2c91b7cc45e5fb98189193a9f5c2d2d57 Author: Judah Jacobson Date: Sun Dec 10 21:44:30 2017 -0800 Actually bump the Cabal version. >--------------------------------------------------------------- 019e08f2c91b7cc45e5fb98189193a9f5c2d2d57 haskeline.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/haskeline.cabal b/haskeline.cabal index 1123a45..991a402 100644 --- a/haskeline.cabal +++ b/haskeline.cabal @@ -1,6 +1,6 @@ Name: haskeline Cabal-Version: >=1.10 -Version: 0.7.4.1 +Version: 0.7.4.2 Category: User Interfaces License: BSD3 License-File: LICENSE From git at git.haskell.org Sun Feb 18 19:38:28 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Feb 2018 19:38:28 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: Bump primitive submodule to 0.6.3.0 (b0271df) Message-ID: <20180218193828.A7F413A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/b0271df6e00c60324e053143b4502fa93a52cda5/ghc >--------------------------------------------------------------- commit b0271df6e00c60324e053143b4502fa93a52cda5 Author: Ben Gamari Date: Thu Feb 15 11:42:35 2018 -0500 Bump primitive submodule to 0.6.3.0 >--------------------------------------------------------------- b0271df6e00c60324e053143b4502fa93a52cda5 libraries/primitive | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/primitive b/libraries/primitive index 260cc97..53f72ce 160000 --- a/libraries/primitive +++ b/libraries/primitive @@ -1 +1 @@ -Subproject commit 260cc9755ee6928876e5174998425cd5863c34a2 +Subproject commit 53f72ce69a4dfde5345cf5809a8b4a1993523367 From git at git.haskell.org Sun Feb 18 19:38:31 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Feb 2018 19:38:31 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: Bump parsec submodule to 0.3.13.0 (c02655a) Message-ID: <20180218193831.75E533A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/c02655aae791337303eb7cc454b473f68d44965d/ghc >--------------------------------------------------------------- commit c02655aae791337303eb7cc454b473f68d44965d Author: Ben Gamari Date: Thu Feb 15 11:43:35 2018 -0500 Bump parsec submodule to 0.3.13.0 >--------------------------------------------------------------- c02655aae791337303eb7cc454b473f68d44965d libraries/parsec | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/parsec b/libraries/parsec index 1c56e08..00dd731 160000 --- a/libraries/parsec +++ b/libraries/parsec @@ -1 +1 @@ -Subproject commit 1c56e0885173accbd3296aa5591a3e0c18084e7a +Subproject commit 00dd731bc12746ac7d4341348abe733c5373cdb7 From git at git.haskell.org Sun Feb 18 19:38:34 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Feb 2018 19:38:34 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: base: Fix changelog entry for openTempFile (c8a02e2) Message-ID: <20180218193834.412813A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/c8a02e29bee00ef12c8f1accd0a9fff0b99bed24/ghc >--------------------------------------------------------------- commit c8a02e29bee00ef12c8f1accd0a9fff0b99bed24 Author: Ben Gamari Date: Thu Feb 15 13:01:09 2018 -0500 base: Fix changelog entry for openTempFile This change is present in 4.11.0.0. (cherry picked from commit abecb2619acea5cf6ebaa7412401d9e660daf82c) >--------------------------------------------------------------- c8a02e29bee00ef12c8f1accd0a9fff0b99bed24 libraries/base/changelog.md | 15 +++++++++++++-- 1 file changed, 13 insertions(+), 2 deletions(-) diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index c52ef0a..dd0a4af 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -1,11 +1,11 @@ # Changelog for [`base` package](http://hackage.haskell.org/package/base) -## 4.11.1.0 *TBA* - * `System.IO.openTempFile` is now thread-safe on Windows. ## 4.11.0.0 *TBA* * Bundled with GHC 8.4.1 + * `System.IO.openTempFile` is now thread-safe on Windows. + * Deprecated `GHC.Stats.GCStats` interface has been removed. * Add `showHFloat` to `Numeric` @@ -76,6 +76,17 @@ * `getExecutablePath` now resolves symlinks on Windows (#14483) + * Deprecated STM invariant checking primitives (`checkInv`, `always`, and + `alwaysSucceeds`) in `GHC.Conc.Sync` (#14324). + +## 4.10.1.0 *November 2017* + * Bundled with GHC 8.2.2 + + * The file locking primitives provided by `GHC.IO.Handle` now use + Linux open file descriptor locking if available. + + * Fixed bottoming definition of `clearBit` for `Natural` + ## 4.10.0.0 *July 2017* * Bundled with GHC 8.2.1 From git at git.haskell.org Sun Feb 18 19:38:37 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Feb 2018 19:38:37 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: Fix #14811 by wiring in $tcUnit# (a66ddb5) Message-ID: <20180218193837.74EC03A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/a66ddb5599a71c31be5f95972156e86debb3c7bf/ghc >--------------------------------------------------------------- commit a66ddb5599a71c31be5f95972156e86debb3c7bf Author: Ryan Scott Date: Fri Feb 16 13:51:27 2018 -0500 Fix #14811 by wiring in $tcUnit# Previously, we were skipping over `$tcUnit#` entirely when wiring in `Typeable` tycons, resulting in #14811. Easily fixed. Test Plan: make test TEST=T14811 Reviewers: bgamari, dfeuer Reviewed By: dfeuer Subscribers: dfeuer, rwbarton, thomie, carter GHC Trac Issues: #14811 Differential Revision: https://phabricator.haskell.org/D4414 (cherry picked from commit d5ac5820111bc957e72c8ce11e59d7cbbdd63526) >--------------------------------------------------------------- a66ddb5599a71c31be5f95972156e86debb3c7bf compiler/typecheck/TcTypeable.hs | 5 ++--- testsuite/tests/typecheck/should_compile/T14811.hs | 5 +++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 3 files changed, 8 insertions(+), 3 deletions(-) diff --git a/compiler/typecheck/TcTypeable.hs b/compiler/typecheck/TcTypeable.hs index 6fa875b..4c2a69a 100644 --- a/compiler/typecheck/TcTypeable.hs +++ b/compiler/typecheck/TcTypeable.hs @@ -345,9 +345,8 @@ mkPrimTypeableTodos -- Note [Built-in syntax and the OrigNameCache] in IfaceEnv for more. ghcPrimTypeableTyCons :: [TyCon] ghcPrimTypeableTyCons = concat - [ [ runtimeRepTyCon, vecCountTyCon, vecElemTyCon - , funTyCon, tupleTyCon Unboxed 0 ] - , map (tupleTyCon Unboxed) [2..mAX_TUPLE_SIZE] + [ [ runtimeRepTyCon, vecCountTyCon, vecElemTyCon, funTyCon ] + , map (tupleTyCon Unboxed) [0..mAX_TUPLE_SIZE] , map sumTyCon [2..mAX_SUM_SIZE] , primTyCons ] diff --git a/testsuite/tests/typecheck/should_compile/T14811.hs b/testsuite/tests/typecheck/should_compile/T14811.hs new file mode 100644 index 0000000..20c6ab9 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T14811.hs @@ -0,0 +1,5 @@ +{-# language UnboxedTuples #-} +module T14811 where + +data Foo a = Foo (# a #) +data Bar = Bar (# #) diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index 9583bc5..f38a1ff 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -592,3 +592,4 @@ test('T14590', normal, compile, ['-fdefer-type-errors -fno-max-valid-substitutio test('T14273', normal, compile, ['-fdefer-type-errors -fno-max-valid-substitutions']) test('T14732', normal, compile, ['']) test('T14763', normal, compile, ['']) +test('T14811', normal, compile, ['']) From git at git.haskell.org Sun Feb 18 19:38:40 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Feb 2018 19:38:40 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: Collect CCs in CorePrep, including CCs in unfoldings (301b99e) Message-ID: <20180218193840.44AF03A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/301b99ea0fedd64b849cd5d68121413a7ce89ee7/ghc >--------------------------------------------------------------- commit 301b99ea0fedd64b849cd5d68121413a7ce89ee7 Author: Ömer Sinan Ağacan Date: Tue Feb 13 09:03:57 2018 +0300 Collect CCs in CorePrep, including CCs in unfoldings This patch includes two changes: 1. Move cost centre collection from `SCCfinal` to `CorePrep`, to be able to collect cost centres in unfoldings. `CorePrep` drops unfoldings, so that's the latest stage in the compilation pipeline for this. After this change `SCCfinal` no longer collects all cost centres, but it still generates & collects CAF cost centres + updates cost centre stacks of `StgRhsClosure` and `StgRhsCon`s. This fixes #5889. 2. Initialize cost centre stack fields of `StgRhs` in `coreToStg`. With this we no longer need to update cost centre stack fields in `SCCfinal`, so that module is removed. Cost centre initialization explained in Note [Cost-centre initialization plan]. Because with -fcaf-all we need to attach a new cost-centre to each CAF, `coreTopBindToStg` now returns `CollectedCCs`. Test Plan: validate Reviewers: simonpj, bgamari, simonmar Reviewed By: simonpj, bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #5889 Differential Revision: https://phabricator.haskell.org/D4325 (cherry picked from commit 5957405808fe89e9b108dc0bc3cf4b56aec37775) >--------------------------------------------------------------- 301b99ea0fedd64b849cd5d68121413a7ce89ee7 compiler/coreSyn/CorePrep.hs | 58 ++++- compiler/deSugar/Coverage.hs | 9 +- compiler/ghc.cabal.in | 1 - compiler/main/HscMain.hs | 20 +- compiler/profiling/CostCentre.hs | 23 +- compiler/profiling/SCCfinal.hs | 287 --------------------- compiler/simplStg/SimplStg.hs | 42 +-- compiler/stgSyn/CoreToStg.hs | 227 +++++++++++----- testsuite/tests/profiling/should_compile/all.T | 2 +- .../simplCore/should_compile/noinline01.stderr | 16 +- 10 files changed, 256 insertions(+), 429 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 301b99ea0fedd64b849cd5d68121413a7ce89ee7 From git at git.haskell.org Sun Feb 18 19:38:43 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Feb 2018 19:38:43 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: testsuite: Add test for #14768 (29e70fd) Message-ID: <20180218193843.5E8BA3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/29e70fdb451793afbc452e29a929e78589e6494a/ghc >--------------------------------------------------------------- commit 29e70fdb451793afbc452e29a929e78589e6494a Author: Ben Gamari Date: Tue Feb 6 17:33:21 2018 -0500 testsuite: Add test for #14768 (cherry picked from commit da4681303892804ea08b60bfd47cbb82ca8e6589) >--------------------------------------------------------------- 29e70fdb451793afbc452e29a929e78589e6494a testsuite/tests/simplCore/should_run/T14768.hs | 59 ++++++++++++++++++++++++++ testsuite/tests/simplCore/should_run/all.T | 1 + 2 files changed, 60 insertions(+) diff --git a/testsuite/tests/simplCore/should_run/T14768.hs b/testsuite/tests/simplCore/should_run/T14768.hs new file mode 100644 index 0000000..116cb82 --- /dev/null +++ b/testsuite/tests/simplCore/should_run/T14768.hs @@ -0,0 +1,59 @@ +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE TypeFamilies #-} + +module Main where + +import Control.Monad (forM_, liftM) +import qualified Data.Vector.Generic as G +import qualified Data.Vector.Generic.Mutable as M +import qualified Data.Vector.Primitive as P +import qualified Data.Vector.Unboxed as U +import qualified Data.Vector.Unboxed.Mutable as MU +import GHC.Exts + +vec :: U.Vector Moebius +vec = U.singleton Moebius0 + +main :: IO () +main = print $ U.head vec == U.head vec + +data Moebius = Moebius0 | Moebius1 | Moebius2 + deriving (Eq) + +fromMoebius :: Moebius -> Int +fromMoebius Moebius0 = 0 +fromMoebius Moebius1 = 1 +fromMoebius Moebius2 = 2 + +toMoebius :: Int -> Moebius +toMoebius (I# i#) = tagToEnum# i# + +newtype instance U.MVector s Moebius = MV_Moebius (P.MVector s Int) +newtype instance U.Vector Moebius = V_Moebius (P.Vector Int) + +instance U.Unbox Moebius + +instance M.MVector U.MVector Moebius where + basicLength (MV_Moebius v) = M.basicLength v + basicUnsafeSlice i n (MV_Moebius v) = MV_Moebius $ M.basicUnsafeSlice i n v + basicOverlaps (MV_Moebius v1) (MV_Moebius v2) = M.basicOverlaps v1 v2 + basicUnsafeNew n = MV_Moebius `liftM` M.basicUnsafeNew n + basicInitialize (MV_Moebius v) = M.basicInitialize v + basicUnsafeReplicate n x = MV_Moebius `liftM` M.basicUnsafeReplicate n (fromMoebius x) + basicUnsafeRead (MV_Moebius v) i = toMoebius `liftM` M.basicUnsafeRead v i + basicUnsafeWrite (MV_Moebius v) i x = M.basicUnsafeWrite v i (fromMoebius x) + basicClear (MV_Moebius v) = M.basicClear v + basicSet (MV_Moebius v) x = M.basicSet v (fromMoebius x) + basicUnsafeCopy (MV_Moebius v1) (MV_Moebius v2) = M.basicUnsafeCopy v1 v2 + basicUnsafeMove (MV_Moebius v1) (MV_Moebius v2) = M.basicUnsafeMove v1 v2 + basicUnsafeGrow (MV_Moebius v) n = MV_Moebius `liftM` M.basicUnsafeGrow v n + +instance G.Vector U.Vector Moebius where + basicUnsafeFreeze (MV_Moebius v) = V_Moebius `liftM` G.basicUnsafeFreeze v + basicUnsafeThaw (V_Moebius v) = MV_Moebius `liftM` G.basicUnsafeThaw v + basicLength (V_Moebius v) = G.basicLength v + basicUnsafeSlice i n (V_Moebius v) = V_Moebius $ G.basicUnsafeSlice i n v + basicUnsafeIndexM (V_Moebius v) i = toMoebius `liftM` G.basicUnsafeIndexM v i + basicUnsafeCopy (MV_Moebius mv) (V_Moebius v) = G.basicUnsafeCopy mv v + elemseq _ = seq diff --git a/testsuite/tests/simplCore/should_run/all.T b/testsuite/tests/simplCore/should_run/all.T index 4ba5a71..d922f90 100644 --- a/testsuite/tests/simplCore/should_run/all.T +++ b/testsuite/tests/simplCore/should_run/all.T @@ -78,3 +78,4 @@ test('T13429', normal, compile_and_run, ['']) test('T13429_2', normal, compile_and_run, ['']) test('T13750', normal, compile_and_run, ['']) test('T14178', normal, compile_and_run, ['']) +test('T14768', reqlib('vector'), compile_and_run, ['']) From git at git.haskell.org Sun Feb 18 19:38:46 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Feb 2018 19:38:46 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: Bump haskeline submodule to 0.7.4.2 (bd7f179) Message-ID: <20180218193846.258DC3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/bd7f179953ad57abcf31652ca208c1db8ece1cc3/ghc >--------------------------------------------------------------- commit bd7f179953ad57abcf31652ca208c1db8ece1cc3 Author: Ben Gamari Date: Sun Feb 18 11:29:56 2018 -0500 Bump haskeline submodule to 0.7.4.2 >--------------------------------------------------------------- bd7f179953ad57abcf31652ca208c1db8ece1cc3 libraries/haskeline | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/haskeline b/libraries/haskeline index 1436a8c..019e08f 160000 --- a/libraries/haskeline +++ b/libraries/haskeline @@ -1 +1 @@ -Subproject commit 1436a8c7c8ee5076c99e09fe20943bf6101237af +Subproject commit 019e08f2c91b7cc45e5fb98189193a9f5c2d2d57 From git at git.haskell.org Sun Feb 18 19:38:48 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Feb 2018 19:38:48 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: Bump text submodule to 1.2.3.0 (85f13a1) Message-ID: <20180218193848.E3C3D3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/85f13a1da0b83b38135c14a7fdba4ef6840c7cfa/ghc >--------------------------------------------------------------- commit 85f13a1da0b83b38135c14a7fdba4ef6840c7cfa Author: Ben Gamari Date: Sun Feb 18 11:31:41 2018 -0500 Bump text submodule to 1.2.3.0 >--------------------------------------------------------------- 85f13a1da0b83b38135c14a7fdba4ef6840c7cfa libraries/text | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/text b/libraries/text index 2d88a0a..a02c2da 160000 --- a/libraries/text +++ b/libraries/text @@ -1 +1 @@ -Subproject commit 2d88a0a3e8e3bb79260e5c8f61dd6c447f61c5f5 +Subproject commit a02c2dafafa425bd5f36c8629e98b98daf1cfa1e From git at git.haskell.org Sun Feb 18 19:38:51 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Feb 2018 19:38:51 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: Build Haddocks with --quickjump (2a7c428) Message-ID: <20180218193851.B26793A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/2a7c428f6e1ce187d772f3f2ee3b51d343810028/ghc >--------------------------------------------------------------- commit 2a7c428f6e1ce187d772f3f2ee3b51d343810028 Author: Ben Gamari Date: Sun Feb 18 11:01:59 2018 -0500 Build Haddocks with --quickjump By request of @alexbiehl. CCing @snowleopard and @alpmestan as the same should be done in Hadrian. Bumps haddock submodule. Reviewers: alexbiehl Reviewed By: alexbiehl Subscribers: rwbarton, thomie, carter, snowleopard, alpmestan, alexbiehl Differential Revision: https://phabricator.haskell.org/D4365 (cherry picked from commit 9ff4cce373765cec064e2a41d4c6ddd84b873f04) >--------------------------------------------------------------- 2a7c428f6e1ce187d772f3f2ee3b51d343810028 rules/haddock.mk | 1 + utils/haddock | 2 +- 2 files changed, 2 insertions(+), 1 deletion(-) diff --git a/rules/haddock.mk b/rules/haddock.mk index 35748c3..37182bc 100644 --- a/rules/haddock.mk +++ b/rules/haddock.mk @@ -65,6 +65,7 @@ endif --dump-interface=$$($$($1_PACKAGE)-$$($1_$2_VERSION)_HADDOCK_FILE) \ --html \ --hoogle \ + --quickjump \ --title="$$($1_PACKAGE)-$$($1_$2_VERSION)$$(if $$(strip $$($1_$2_SYNOPSIS)),: $$(strip $$($1_$2_SYNOPSIS)),)" \ --prologue="$1/$2/haddock-prologue.txt" \ --optghc="-D__HADDOCK_VERSION__=$$(HADDOCK_VERSION_STRING)" \ diff --git a/utils/haddock b/utils/haddock index ac33472..5141e4b 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit ac33472e834d381f95fd56586e57e6653263055c +Subproject commit 5141e4b76af8462e49abdf48e44bb9cddb183383 From git at git.haskell.org Sun Feb 18 19:38:57 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Feb 2018 19:38:57 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: CBE: re-introduce bgamari's fixes (5aba104) Message-ID: <20180218193857.D5C8C3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/5aba104267ff952de8836e970f1c9c77ec549aa0/ghc >--------------------------------------------------------------- commit 5aba104267ff952de8836e970f1c9c77ec549aa0 Author: Michal Terepeta Date: Sun Feb 18 11:09:40 2018 -0500 CBE: re-introduce bgamari's fixes During some recent work on CBE we discovered that `zipWith` is used to check for equality, but that doesn't quite work if lists are of different lengths! This was fixed by bgamari, but unfortunately the fix had to be rolled back due to other changes in CBE in 50adbd7c5fe5894d3e6e2a58b353ed07e5f8949d. Since I wanted to have another look at CBE anyway, we agreed that the first thing to do would be to re-introduce the fix. Sadly I don't have any actual test case that would exercise this. Signed-off-by: Michal Terepeta Test Plan: ./validate Reviewers: bgamari, simonmar Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14226 Differential Revision: https://phabricator.haskell.org/D4387 (cherry picked from commit 4e513bf758c32804fc71b98215f96e8481697a36) >--------------------------------------------------------------- 5aba104267ff952de8836e970f1c9c77ec549aa0 compiler/cmm/CmmCommonBlockElim.hs | 11 ++++++++--- 1 file changed, 8 insertions(+), 3 deletions(-) diff --git a/compiler/cmm/CmmCommonBlockElim.hs b/compiler/cmm/CmmCommonBlockElim.hs index f635520..7f4e290 100644 --- a/compiler/cmm/CmmCommonBlockElim.hs +++ b/compiler/cmm/CmmCommonBlockElim.hs @@ -209,7 +209,7 @@ eqMiddleWith eqBid (CmmStore l1 r1) (CmmStore l2 r2) = eqExprWith eqBid l1 l2 && eqExprWith eqBid r1 r2 eqMiddleWith eqBid (CmmUnsafeForeignCall t1 r1 a1) (CmmUnsafeForeignCall t2 r2 a2) - = t1 == t2 && r1 == r2 && and (zipWith (eqExprWith eqBid) a1 a2) + = t1 == t2 && r1 == r2 && eqListWith (eqExprWith eqBid) a1 a2 eqMiddleWith _ _ _ = False eqExprWith :: (BlockId -> BlockId -> Bool) @@ -224,7 +224,7 @@ eqExprWith eqBid = eq CmmStackSlot a1 i1 `eq` CmmStackSlot a2 i2 = eqArea a1 a2 && i1==i2 _e1 `eq` _e2 = False - xs `eqs` ys = and (zipWith eq xs ys) + xs `eqs` ys = eqListWith eq xs ys eqLit (CmmBlock id1) (CmmBlock id2) = eqBid id1 id2 eqLit l1 l2 = l1 == l2 @@ -247,7 +247,7 @@ eqBlockBodyWith eqBid block block' (_,m',l') = blockSplit block' nodes' = filter (not . dont_care) (blockToList m') - equal = and (zipWith (eqMiddleWith eqBid) nodes nodes') && + equal = eqListWith (eqMiddleWith eqBid) nodes nodes' && eqLastWith eqBid l l' @@ -266,6 +266,11 @@ eqMaybeWith eltEq (Just e) (Just e') = eltEq e e' eqMaybeWith _ Nothing Nothing = True eqMaybeWith _ _ _ = False +eqListWith :: (a -> b -> Bool) -> [a] -> [b] -> Bool +eqListWith f (a : as) (b : bs) = f a b && eqListWith f as bs +eqListWith _ [] [] = True +eqListWith _ _ _ = False + -- | Given a block map, ensure that all "target" blocks are covered by -- the same ticks as the respective "source" blocks. This not only -- means copying ticks, but also adjusting tick scopes where From git at git.haskell.org Sun Feb 18 19:38:55 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Feb 2018 19:38:55 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: Implement stopgap solution for #14728 (5423035) Message-ID: <20180218193855.1A9063A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/5423035358cfd3aad274fd3c22e4e531003e7c83/ghc >--------------------------------------------------------------- commit 5423035358cfd3aad274fd3c22e4e531003e7c83 Author: Ryan Scott Date: Sun Feb 18 11:00:40 2018 -0500 Implement stopgap solution for #14728 It turns out that one can produce ill-formed Core by combining `GeneralizedNewtypeDeriving`, `TypeInType`, and `TypeFamilies`, as demonstrated in #14728. The root of the problem is allowing the last parameter of a class to appear in a //kind// of an associated type family, as our current approach to deriving associated type family instances simply doesn't work well for that situation. Although it might be possible to properly implement this feature today (see https://ghc.haskell.org/trac/ghc/ticket/14728#comment:3 for a sketch of how this might work), there does not currently exist a performant implementation of the algorithm needed to accomplish this. Until such an implementation surfaces, we will make this corner case of `GeneralizedNewtypeDeriving` an error. Test Plan: make test TEST="T14728a T14728b" Reviewers: bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14728 Differential Revision: https://phabricator.haskell.org/D4402 (cherry picked from commit 1ede46d415757f53af33bc6672bd9d3fba7f205d) >--------------------------------------------------------------- 5423035358cfd3aad274fd3c22e4e531003e7c83 compiler/typecheck/TcDeriv.hs | 43 ++++++++++++++++++++-- testsuite/tests/deriving/should_fail/T14728a.hs | 20 ++++++++++ .../tests/deriving/should_fail/T14728a.stderr | 7 ++++ testsuite/tests/deriving/should_fail/T14728b.hs | 16 ++++++++ .../tests/deriving/should_fail/T14728b.stderr | 7 ++++ testsuite/tests/deriving/should_fail/all.T | 2 + 6 files changed, 92 insertions(+), 3 deletions(-) diff --git a/compiler/typecheck/TcDeriv.hs b/compiler/typecheck/TcDeriv.hs index 33ce581..a93712c 100644 --- a/compiler/typecheck/TcDeriv.hs +++ b/compiler/typecheck/TcDeriv.hs @@ -1314,6 +1314,8 @@ mkNewTypeEqn && ats_ok -- Check (b) from Note [GND and associated type families] && isNothing at_without_last_cls_tv + -- Check (d) from Note [GND and associated type families] + && isNothing at_last_cls_tv_in_kinds -- Check that eta reduction is OK eta_ok = rep_tc_args `lengthAtLeast` nt_eta_arity @@ -1330,6 +1332,12 @@ mkNewTypeEqn at_without_last_cls_tv = find (\tc -> last_cls_tv `notElem` tyConTyVars tc) atf_tcs + at_last_cls_tv_in_kinds + = find (\tc -> any (at_last_cls_tv_in_kind . tyVarKind) + (tyConTyVars tc) + || at_last_cls_tv_in_kind (tyConResKind tc)) atf_tcs + at_last_cls_tv_in_kind kind + = last_cls_tv `elemVarSet` exactTyCoVarsOfType kind at_tcs = classATs cls last_cls_tv = ASSERT( notNull cls_tyvars ) last cls_tyvars @@ -1337,14 +1345,22 @@ mkNewTypeEqn cant_derive_err = vcat [ ppUnless eta_ok eta_msg , ppUnless ats_ok ats_msg - , maybe empty at_tv_msg - at_without_last_cls_tv] + , maybe empty at_without_last_cls_tv_msg + at_without_last_cls_tv + , maybe empty at_last_cls_tv_in_kinds_msg + at_last_cls_tv_in_kinds + ] eta_msg = text "cannot eta-reduce the representation type enough" ats_msg = text "the class has associated data types" - at_tv_msg at_tc = hang + at_without_last_cls_tv_msg at_tc = hang (text "the associated type" <+> quotes (ppr at_tc) <+> text "is not parameterized over the last type variable") 2 (text "of the class" <+> quotes (ppr cls)) + at_last_cls_tv_in_kinds_msg at_tc = hang + (text "the associated type" <+> quotes (ppr at_tc) + <+> text "contains the last type variable") + 2 (text "of the class" <+> quotes (ppr cls) + <+> text "in a kind, which is not (yet) allowed") MASSERT( cls_tys `lengthIs` (classArity cls - 1) ) case mb_strat of @@ -1530,6 +1546,27 @@ However, we must watch out for three things: GHC's termination checker isn't sophisticated enough to conclude that the definition of T MyInt terminates, so UndecidableInstances is required. +(d) For the time being, we do not allow the last type variable of the class to + appear in a /kind/ of an associated type family definition. For instance: + + class C a where + type T1 a -- OK + type T2 (x :: a) -- Illegal: a appears in the kind of x + type T3 y :: a -- Illegal: a appears in the kind of (T3 y) + + The reason we disallow this is because our current approach to deriving + associated type family instances—i.e., by unwrapping the newtype's type + constructor as shown above—is ill-equipped to handle the scenario when + the last type variable appears as an implicit argument. In the worst case, + allowing the last variable to appear in a kind can result in improper Core + being generated (see #14728). + + There is hope for this feature being added some day, as one could + conceivably take a newtype axiom (which witnesses a coercion between a + newtype and its representation type) at lift that through each associated + type at the Core level. See #14728, comment:3 for a sketch of how this + might work. Until then, we disallow this featurette wholesale. + ************************************************************************ * * \subsection[TcDeriv-normal-binds]{Bindings for the various classes} diff --git a/testsuite/tests/deriving/should_fail/T14728a.hs b/testsuite/tests/deriving/should_fail/T14728a.hs new file mode 100644 index 0000000..28cf8e0 --- /dev/null +++ b/testsuite/tests/deriving/should_fail/T14728a.hs @@ -0,0 +1,20 @@ +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE StandaloneDeriving #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE TypeInType #-} +module T14728a where + +import Data.Functor.Identity +import Data.Kind + +class C (a :: Type) where + type T a (x :: a) :: Type + type U z :: a + +instance C () where + type T () '() = Bool + +deriving instance C (Identity a) + +f :: T (Identity ()) ('Identity '()) +f = True diff --git a/testsuite/tests/deriving/should_fail/T14728a.stderr b/testsuite/tests/deriving/should_fail/T14728a.stderr new file mode 100644 index 0000000..b76d073 --- /dev/null +++ b/testsuite/tests/deriving/should_fail/T14728a.stderr @@ -0,0 +1,7 @@ + +T14728a.hs:17:1: error: + • Can't make a derived instance of ‘C (Identity a)’ + (even with cunning GeneralizedNewtypeDeriving): + the associated type ‘T’ contains the last type variable + of the class ‘C’ in a kind, which is not (yet) allowed + • In the stand-alone deriving instance for ‘C (Identity a)’ diff --git a/testsuite/tests/deriving/should_fail/T14728b.hs b/testsuite/tests/deriving/should_fail/T14728b.hs new file mode 100644 index 0000000..7fdfcb3 --- /dev/null +++ b/testsuite/tests/deriving/should_fail/T14728b.hs @@ -0,0 +1,16 @@ +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE StandaloneDeriving #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE TypeInType #-} +module T14728b where + +import Data.Functor.Identity +import Data.Kind + +class C (a :: Type) where + type U z :: a + +instance C () where + type U z = '() + +deriving instance C (Identity a) diff --git a/testsuite/tests/deriving/should_fail/T14728b.stderr b/testsuite/tests/deriving/should_fail/T14728b.stderr new file mode 100644 index 0000000..ee74f8b4 --- /dev/null +++ b/testsuite/tests/deriving/should_fail/T14728b.stderr @@ -0,0 +1,7 @@ + +T14728b.hs:16:1: error: + • Can't make a derived instance of ‘C (Identity a)’ + (even with cunning GeneralizedNewtypeDeriving): + the associated type ‘U’ contains the last type variable + of the class ‘C’ in a kind, which is not (yet) allowed + • In the stand-alone deriving instance for ‘C (Identity a)’ diff --git a/testsuite/tests/deriving/should_fail/all.T b/testsuite/tests/deriving/should_fail/all.T index c9b8469..acd3486 100644 --- a/testsuite/tests/deriving/should_fail/all.T +++ b/testsuite/tests/deriving/should_fail/all.T @@ -69,3 +69,5 @@ test('T12512', omit_ways(['ghci']), compile_fail, ['']) test('T12801', normal, compile_fail, ['']) test('T14365', [extra_files(['T14365B.hs','T14365B.hs-boot'])], multimod_compile_fail, ['T14365A','']) +test('T14728a', normal, compile_fail, ['']) +test('T14728b', normal, compile_fail, ['']) From git at git.haskell.org Mon Feb 19 12:43:11 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Feb 2018 12:43:11 +0000 (UTC) Subject: [commit: ghc] master: Increase the amount of parallelism in circleci. (5b63240) Message-ID: <20180219124311.28F243A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5b63240f9822507a33bca6c5c05462832a9f13ab/ghc >--------------------------------------------------------------- commit 5b63240f9822507a33bca6c5c05462832a9f13ab Author: Facundo Domínguez Date: Fri Feb 16 08:18:52 2018 -0300 Increase the amount of parallelism in circleci. Summary: Set THREADS=CPUS+1 in circleci. Reviewers: bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4415 >--------------------------------------------------------------- 5b63240f9822507a33bca6c5c05462832a9f13ab .circleci/config.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.circleci/config.yml b/.circleci/config.yml index b93c651..3e5a77f 100644 --- a/.circleci/config.yml +++ b/.circleci/config.yml @@ -22,7 +22,7 @@ aliases: name: submodules command: .circleci/fetch-submodules.sh - &buildenv - THREADS: 3 + THREADS: 9 SKIP_PERF_TESTS: YES VERBOSE: 2 - &boot From git at git.haskell.org Mon Feb 19 20:06:19 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Feb 2018 20:06:19 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: Bump primitive submodule to 0.6.3.0 (b0271df) Message-ID: <20180219200619.6B2533A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/b0271df6e00c60324e053143b4502fa93a52cda5/ghc >--------------------------------------------------------------- commit b0271df6e00c60324e053143b4502fa93a52cda5 Author: Ben Gamari Date: Thu Feb 15 11:42:35 2018 -0500 Bump primitive submodule to 0.6.3.0 >--------------------------------------------------------------- b0271df6e00c60324e053143b4502fa93a52cda5 libraries/primitive | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/primitive b/libraries/primitive index 260cc97..53f72ce 160000 --- a/libraries/primitive +++ b/libraries/primitive @@ -1 +1 @@ -Subproject commit 260cc9755ee6928876e5174998425cd5863c34a2 +Subproject commit 53f72ce69a4dfde5345cf5809a8b4a1993523367 From git at git.haskell.org Mon Feb 19 20:06:22 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Feb 2018 20:06:22 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: Bump parsec submodule to 0.3.13.0 (ee31f81) Message-ID: <20180219200622.32DB93A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/ee31f81f8bc6e1c1071ed39705c251cf75b383aa/ghc >--------------------------------------------------------------- commit ee31f81f8bc6e1c1071ed39705c251cf75b383aa Author: Ben Gamari Date: Thu Feb 15 11:43:35 2018 -0500 Bump parsec submodule to 0.3.13.0 >--------------------------------------------------------------- ee31f81f8bc6e1c1071ed39705c251cf75b383aa libraries/parsec | 2 +- utils/ghc-cabal/ghc.mk | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/libraries/parsec b/libraries/parsec index 1c56e08..00dd731 160000 --- a/libraries/parsec +++ b/libraries/parsec @@ -1 +1 @@ -Subproject commit 1c56e0885173accbd3296aa5591a3e0c18084e7a +Subproject commit 00dd731bc12746ac7d4341348abe733c5373cdb7 diff --git a/utils/ghc-cabal/ghc.mk b/utils/ghc-cabal/ghc.mk index e0d2afe..70e418e 100644 --- a/utils/ghc-cabal/ghc.mk +++ b/utils/ghc-cabal/ghc.mk @@ -75,7 +75,7 @@ $(ghc-cabal_DIST_BINARY): $(CABAL_LEXER_DEP) utils/ghc-cabal/Main.hs $(TOUCH_DEP -ilibraries/text \ libraries/text/cbits/cbits.c \ -Ilibraries/text/include \ - -ilibraries/parsec \ + -ilibraries/parsec/src \ $(utils/ghc-cabal_dist_EXTRA_HC_OPTS) \ $(EXTRA_HC_OPTS) "$(TOUCH_CMD)" $@ From git at git.haskell.org Mon Feb 19 20:06:24 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Feb 2018 20:06:24 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: base: Fix changelog entry for openTempFile (43cd969) Message-ID: <20180219200624.F3C233A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/43cd969d01cf4fe15432f28af500d85b52237379/ghc >--------------------------------------------------------------- commit 43cd969d01cf4fe15432f28af500d85b52237379 Author: Ben Gamari Date: Thu Feb 15 13:01:09 2018 -0500 base: Fix changelog entry for openTempFile This change is present in 4.11.0.0. (cherry picked from commit abecb2619acea5cf6ebaa7412401d9e660daf82c) >--------------------------------------------------------------- 43cd969d01cf4fe15432f28af500d85b52237379 libraries/base/changelog.md | 15 +++++++++++++-- 1 file changed, 13 insertions(+), 2 deletions(-) diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index c52ef0a..dd0a4af 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -1,11 +1,11 @@ # Changelog for [`base` package](http://hackage.haskell.org/package/base) -## 4.11.1.0 *TBA* - * `System.IO.openTempFile` is now thread-safe on Windows. ## 4.11.0.0 *TBA* * Bundled with GHC 8.4.1 + * `System.IO.openTempFile` is now thread-safe on Windows. + * Deprecated `GHC.Stats.GCStats` interface has been removed. * Add `showHFloat` to `Numeric` @@ -76,6 +76,17 @@ * `getExecutablePath` now resolves symlinks on Windows (#14483) + * Deprecated STM invariant checking primitives (`checkInv`, `always`, and + `alwaysSucceeds`) in `GHC.Conc.Sync` (#14324). + +## 4.10.1.0 *November 2017* + * Bundled with GHC 8.2.2 + + * The file locking primitives provided by `GHC.IO.Handle` now use + Linux open file descriptor locking if available. + + * Fixed bottoming definition of `clearBit` for `Natural` + ## 4.10.0.0 *July 2017* * Bundled with GHC 8.2.1 From git at git.haskell.org Mon Feb 19 20:06:28 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Feb 2018 20:06:28 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: Fix #14811 by wiring in $tcUnit# (0f78f18) Message-ID: <20180219200628.3FA673A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/0f78f18129d24f17154ae7dca84937fddd1f8b0c/ghc >--------------------------------------------------------------- commit 0f78f18129d24f17154ae7dca84937fddd1f8b0c Author: Ryan Scott Date: Fri Feb 16 13:51:27 2018 -0500 Fix #14811 by wiring in $tcUnit# Previously, we were skipping over `$tcUnit#` entirely when wiring in `Typeable` tycons, resulting in #14811. Easily fixed. Test Plan: make test TEST=T14811 Reviewers: bgamari, dfeuer Reviewed By: dfeuer Subscribers: dfeuer, rwbarton, thomie, carter GHC Trac Issues: #14811 Differential Revision: https://phabricator.haskell.org/D4414 (cherry picked from commit d5ac5820111bc957e72c8ce11e59d7cbbdd63526) >--------------------------------------------------------------- 0f78f18129d24f17154ae7dca84937fddd1f8b0c compiler/typecheck/TcTypeable.hs | 5 ++--- testsuite/tests/typecheck/should_compile/T14811.hs | 5 +++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 3 files changed, 8 insertions(+), 3 deletions(-) diff --git a/compiler/typecheck/TcTypeable.hs b/compiler/typecheck/TcTypeable.hs index 6fa875b..4c2a69a 100644 --- a/compiler/typecheck/TcTypeable.hs +++ b/compiler/typecheck/TcTypeable.hs @@ -345,9 +345,8 @@ mkPrimTypeableTodos -- Note [Built-in syntax and the OrigNameCache] in IfaceEnv for more. ghcPrimTypeableTyCons :: [TyCon] ghcPrimTypeableTyCons = concat - [ [ runtimeRepTyCon, vecCountTyCon, vecElemTyCon - , funTyCon, tupleTyCon Unboxed 0 ] - , map (tupleTyCon Unboxed) [2..mAX_TUPLE_SIZE] + [ [ runtimeRepTyCon, vecCountTyCon, vecElemTyCon, funTyCon ] + , map (tupleTyCon Unboxed) [0..mAX_TUPLE_SIZE] , map sumTyCon [2..mAX_SUM_SIZE] , primTyCons ] diff --git a/testsuite/tests/typecheck/should_compile/T14811.hs b/testsuite/tests/typecheck/should_compile/T14811.hs new file mode 100644 index 0000000..20c6ab9 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T14811.hs @@ -0,0 +1,5 @@ +{-# language UnboxedTuples #-} +module T14811 where + +data Foo a = Foo (# a #) +data Bar = Bar (# #) diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index 9583bc5..f38a1ff 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -592,3 +592,4 @@ test('T14590', normal, compile, ['-fdefer-type-errors -fno-max-valid-substitutio test('T14273', normal, compile, ['-fdefer-type-errors -fno-max-valid-substitutions']) test('T14732', normal, compile, ['']) test('T14763', normal, compile, ['']) +test('T14811', normal, compile, ['']) From git at git.haskell.org Mon Feb 19 20:06:31 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Feb 2018 20:06:31 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: Remove unused extern cost centre collection (ff78b94) Message-ID: <20180219200631.0ABDD3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/ff78b94f71542026af38c9db2fea12406110f6d9/ghc >--------------------------------------------------------------- commit ff78b94f71542026af38c9db2fea12406110f6d9 Author: Ömer Sinan Ağacan Date: Thu Jan 18 11:06:30 2018 -0500 Remove unused extern cost centre collection Reviewers: bgamari, simonmar Reviewed By: simonmar Subscribers: alexbiehl, rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4309 (cherry picked from commit 2a78cf773cb447ac91c4a23d7e921e091e499134) >--------------------------------------------------------------- ff78b94f71542026af38c9db2fea12406110f6d9 compiler/codeGen/StgCmmProf.hs | 2 +- compiler/profiling/CostCentre.hs | 1 - compiler/profiling/ProfInit.hs | 2 +- compiler/profiling/SCCfinal.hs | 25 +++++++++++-------------- compiler/simplStg/SimplStg.hs | 2 +- 5 files changed, 14 insertions(+), 18 deletions(-) diff --git a/compiler/codeGen/StgCmmProf.hs b/compiler/codeGen/StgCmmProf.hs index a91c4c0..e5e1379 100644 --- a/compiler/codeGen/StgCmmProf.hs +++ b/compiler/codeGen/StgCmmProf.hs @@ -209,7 +209,7 @@ ifProfilingL dflags xs initCostCentres :: CollectedCCs -> FCode () -- Emit the declarations -initCostCentres (local_CCs, ___extern_CCs, singleton_CCSs) +initCostCentres (local_CCs, singleton_CCSs) = do dflags <- getDynFlags when (gopt Opt_SccProfilingOn dflags) $ do mapM_ emitCostCentreDecl local_CCs diff --git a/compiler/profiling/CostCentre.hs b/compiler/profiling/CostCentre.hs index d1452ad..f89654d 100644 --- a/compiler/profiling/CostCentre.hs +++ b/compiler/profiling/CostCentre.hs @@ -182,7 +182,6 @@ data CostCentreStack -- code for a module. type CollectedCCs = ( [CostCentre] -- local cost-centres that need to be decl'd - , [CostCentre] -- "extern" cost-centres , [CostCentreStack] -- pre-defined "singleton" cost centre stacks ) diff --git a/compiler/profiling/ProfInit.hs b/compiler/profiling/ProfInit.hs index 557bdf0..931299a 100644 --- a/compiler/profiling/ProfInit.hs +++ b/compiler/profiling/ProfInit.hs @@ -23,7 +23,7 @@ import Module -- module; profilingInitCode :: Module -> CollectedCCs -> SDoc -profilingInitCode this_mod (local_CCs, ___extern_CCs, singleton_CCSs) +profilingInitCode this_mod (local_CCs, singleton_CCSs) = sdocWithDynFlags $ \dflags -> if not (gopt Opt_SccProfilingOn dflags) then empty diff --git a/compiler/profiling/SCCfinal.hs b/compiler/profiling/SCCfinal.hs index 4c582f4..8a2513f 100644 --- a/compiler/profiling/SCCfinal.hs +++ b/compiler/profiling/SCCfinal.hs @@ -30,7 +30,6 @@ import Id import Name import Module import UniqSupply ( UniqSupply ) -import ListSetOps ( removeDups ) import Outputable import DynFlags import CoreSyn ( Tickish(..) ) @@ -49,7 +48,7 @@ stgMassageForProfiling stgMassageForProfiling dflags mod_name _us stg_binds = let - ((local_ccs, extern_ccs, cc_stacks), + ((local_ccs, cc_stacks), stg_binds2) = initMM mod_name (do_top_bindings stg_binds) @@ -58,11 +57,9 @@ stgMassageForProfiling dflags mod_name _us stg_binds then ([],[]) -- don't need "all CAFs" CC else ([all_cafs_cc], [all_cafs_ccs]) - local_ccs_no_dups = fst (removeDups cmpCostCentre local_ccs) - extern_ccs_no_dups = fst (removeDups cmpCostCentre extern_ccs) + local_ccs_no_dups = nubSort local_ccs in ((fixed_ccs ++ local_ccs_no_dups, - extern_ccs_no_dups, fixed_cc_stacks ++ cc_stacks), stg_binds2) where @@ -248,7 +245,7 @@ initMM :: Module -- module name, which we may consult -> MassageM a -> (CollectedCCs, a) -initMM mod_name (MassageM m) = m mod_name ([],[],[]) +initMM mod_name (MassageM m) = m mod_name ([],[]) thenMM :: MassageM a -> (a -> MassageM b) -> MassageM b thenMM_ :: MassageM a -> (MassageM b) -> MassageM b @@ -264,11 +261,11 @@ thenMM_ expr cont = MassageM $ \mod ccs -> collectCC :: CostCentre -> MassageM () collectCC cc - = MassageM $ \mod_name (local_ccs, extern_ccs, ccss) + = MassageM $ \mod_name (local_ccs, ccss) -> if (cc `ccFromThisModule` mod_name) then - ((cc : local_ccs, extern_ccs, ccss), ()) - else -- must declare it "extern" - ((local_ccs, cc : extern_ccs, ccss), ()) + ((cc : local_ccs, ccss), ()) + else + ((local_ccs, ccss), ()) -- Version of collectCC used when we definitely want to declare this -- CC as local, even if its module name is not the same as the current @@ -276,12 +273,12 @@ collectCC cc -- test prof001,prof002. collectNewCC :: CostCentre -> MassageM () collectNewCC cc - = MassageM $ \_mod_name (local_ccs, extern_ccs, ccss) - -> ((cc : local_ccs, extern_ccs, ccss), ()) + = MassageM $ \_mod_name (local_ccs, ccss) + -> ((cc : local_ccs, ccss), ()) collectCCS :: CostCentreStack -> MassageM () collectCCS ccs - = MassageM $ \_mod_name (local_ccs, extern_ccs, ccss) + = MassageM $ \_mod_name (local_ccs, ccss) -> ASSERT(not (noCCSAttached ccs)) - ((local_ccs, extern_ccs, ccs : ccss), ()) + ((local_ccs, ccs : ccss), ()) diff --git a/compiler/simplStg/SimplStg.hs b/compiler/simplStg/SimplStg.hs index ad714ea..2af53e4 100644 --- a/compiler/simplStg/SimplStg.hs +++ b/compiler/simplStg/SimplStg.hs @@ -43,7 +43,7 @@ stg2stg dflags module_name binds (putLogMsg dflags NoReason SevDump noSrcSpan (defaultDumpStyle dflags) (text "VERBOSE STG-TO-STG:")) - ; (binds', us', ccs) <- end_pass us "Stg2Stg" ([],[],[]) binds + ; (binds', us', ccs) <- end_pass us "Stg2Stg" ([],[]) binds -- Do the main business! ; let (us0, us1) = splitUniqSupply us' From git at git.haskell.org Mon Feb 19 20:06:33 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Feb 2018 20:06:33 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: Collect CCs in CorePrep, including CCs in unfoldings (583e392) Message-ID: <20180219200633.D35A83A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/583e392a83c17e8baf45bc6ee5b998afae190a44/ghc >--------------------------------------------------------------- commit 583e392a83c17e8baf45bc6ee5b998afae190a44 Author: Ömer Sinan Ağacan Date: Tue Feb 13 09:03:57 2018 +0300 Collect CCs in CorePrep, including CCs in unfoldings This patch includes two changes: 1. Move cost centre collection from `SCCfinal` to `CorePrep`, to be able to collect cost centres in unfoldings. `CorePrep` drops unfoldings, so that's the latest stage in the compilation pipeline for this. After this change `SCCfinal` no longer collects all cost centres, but it still generates & collects CAF cost centres + updates cost centre stacks of `StgRhsClosure` and `StgRhsCon`s. This fixes #5889. 2. Initialize cost centre stack fields of `StgRhs` in `coreToStg`. With this we no longer need to update cost centre stack fields in `SCCfinal`, so that module is removed. Cost centre initialization explained in Note [Cost-centre initialization plan]. Because with -fcaf-all we need to attach a new cost-centre to each CAF, `coreTopBindToStg` now returns `CollectedCCs`. Test Plan: validate Reviewers: simonpj, bgamari, simonmar Reviewed By: simonpj, bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #5889 Differential Revision: https://phabricator.haskell.org/D4325 (cherry picked from commit 5957405808fe89e9b108dc0bc3cf4b56aec37775) >--------------------------------------------------------------- 583e392a83c17e8baf45bc6ee5b998afae190a44 compiler/coreSyn/CorePrep.hs | 58 ++++- compiler/deSugar/Coverage.hs | 9 +- compiler/ghc.cabal.in | 1 - compiler/main/HscMain.hs | 20 +- compiler/profiling/CostCentre.hs | 23 +- compiler/profiling/SCCfinal.hs | 284 --------------------- compiler/simplStg/SimplStg.hs | 47 +--- compiler/stgSyn/CoreToStg.hs | 227 +++++++++++----- testsuite/tests/profiling/should_compile/all.T | 2 +- .../simplCore/should_compile/noinline01.stderr | 16 +- 10 files changed, 258 insertions(+), 429 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 583e392a83c17e8baf45bc6ee5b998afae190a44 From git at git.haskell.org Mon Feb 19 20:06:36 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Feb 2018 20:06:36 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: Build Haddocks with --quickjump (01f6999) Message-ID: <20180219200636.952CB3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/01f69997550b875d74634df15a5644593e89c0eb/ghc >--------------------------------------------------------------- commit 01f69997550b875d74634df15a5644593e89c0eb Author: Ben Gamari Date: Sun Feb 18 11:01:59 2018 -0500 Build Haddocks with --quickjump By request of @alexbiehl. CCing @snowleopard and @alpmestan as the same should be done in Hadrian. Bumps haddock submodule. Reviewers: alexbiehl Reviewed By: alexbiehl Subscribers: rwbarton, thomie, carter, snowleopard, alpmestan, alexbiehl Differential Revision: https://phabricator.haskell.org/D4365 (cherry picked from commit 9ff4cce373765cec064e2a41d4c6ddd84b873f04) >--------------------------------------------------------------- 01f69997550b875d74634df15a5644593e89c0eb rules/haddock.mk | 1 + utils/haddock | 2 +- 2 files changed, 2 insertions(+), 1 deletion(-) diff --git a/rules/haddock.mk b/rules/haddock.mk index 35748c3..37182bc 100644 --- a/rules/haddock.mk +++ b/rules/haddock.mk @@ -65,6 +65,7 @@ endif --dump-interface=$$($$($1_PACKAGE)-$$($1_$2_VERSION)_HADDOCK_FILE) \ --html \ --hoogle \ + --quickjump \ --title="$$($1_PACKAGE)-$$($1_$2_VERSION)$$(if $$(strip $$($1_$2_SYNOPSIS)),: $$(strip $$($1_$2_SYNOPSIS)),)" \ --prologue="$1/$2/haddock-prologue.txt" \ --optghc="-D__HADDOCK_VERSION__=$$(HADDOCK_VERSION_STRING)" \ diff --git a/utils/haddock b/utils/haddock index ac33472..5141e4b 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit ac33472e834d381f95fd56586e57e6653263055c +Subproject commit 5141e4b76af8462e49abdf48e44bb9cddb183383 From git at git.haskell.org Mon Feb 19 20:06:46 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Feb 2018 20:06:46 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: Bump haskeline submodule to 0.7.4.2 (76bd578) Message-ID: <20180219200646.26F733A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/76bd578a4460b4305d0604c2e95a31fe801ee8bf/ghc >--------------------------------------------------------------- commit 76bd578a4460b4305d0604c2e95a31fe801ee8bf Author: Ben Gamari Date: Sun Feb 18 11:29:56 2018 -0500 Bump haskeline submodule to 0.7.4.2 >--------------------------------------------------------------- 76bd578a4460b4305d0604c2e95a31fe801ee8bf libraries/haskeline | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/haskeline b/libraries/haskeline index 1436a8c..019e08f 160000 --- a/libraries/haskeline +++ b/libraries/haskeline @@ -1 +1 @@ -Subproject commit 1436a8c7c8ee5076c99e09fe20943bf6101237af +Subproject commit 019e08f2c91b7cc45e5fb98189193a9f5c2d2d57 From git at git.haskell.org Mon Feb 19 20:06:43 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Feb 2018 20:06:43 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: testsuite: Add test for #14768 (0bdf1b7) Message-ID: <20180219200643.5DC7D3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/0bdf1b7af97898fa4489c37c1cc2ba0295edfe2d/ghc >--------------------------------------------------------------- commit 0bdf1b7af97898fa4489c37c1cc2ba0295edfe2d Author: Ben Gamari Date: Tue Feb 6 17:33:21 2018 -0500 testsuite: Add test for #14768 (cherry picked from commit da4681303892804ea08b60bfd47cbb82ca8e6589) >--------------------------------------------------------------- 0bdf1b7af97898fa4489c37c1cc2ba0295edfe2d testsuite/tests/simplCore/should_run/T14768.hs | 59 ++++++++++++++++++++++++++ testsuite/tests/simplCore/should_run/all.T | 1 + 2 files changed, 60 insertions(+) diff --git a/testsuite/tests/simplCore/should_run/T14768.hs b/testsuite/tests/simplCore/should_run/T14768.hs new file mode 100644 index 0000000..116cb82 --- /dev/null +++ b/testsuite/tests/simplCore/should_run/T14768.hs @@ -0,0 +1,59 @@ +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE TypeFamilies #-} + +module Main where + +import Control.Monad (forM_, liftM) +import qualified Data.Vector.Generic as G +import qualified Data.Vector.Generic.Mutable as M +import qualified Data.Vector.Primitive as P +import qualified Data.Vector.Unboxed as U +import qualified Data.Vector.Unboxed.Mutable as MU +import GHC.Exts + +vec :: U.Vector Moebius +vec = U.singleton Moebius0 + +main :: IO () +main = print $ U.head vec == U.head vec + +data Moebius = Moebius0 | Moebius1 | Moebius2 + deriving (Eq) + +fromMoebius :: Moebius -> Int +fromMoebius Moebius0 = 0 +fromMoebius Moebius1 = 1 +fromMoebius Moebius2 = 2 + +toMoebius :: Int -> Moebius +toMoebius (I# i#) = tagToEnum# i# + +newtype instance U.MVector s Moebius = MV_Moebius (P.MVector s Int) +newtype instance U.Vector Moebius = V_Moebius (P.Vector Int) + +instance U.Unbox Moebius + +instance M.MVector U.MVector Moebius where + basicLength (MV_Moebius v) = M.basicLength v + basicUnsafeSlice i n (MV_Moebius v) = MV_Moebius $ M.basicUnsafeSlice i n v + basicOverlaps (MV_Moebius v1) (MV_Moebius v2) = M.basicOverlaps v1 v2 + basicUnsafeNew n = MV_Moebius `liftM` M.basicUnsafeNew n + basicInitialize (MV_Moebius v) = M.basicInitialize v + basicUnsafeReplicate n x = MV_Moebius `liftM` M.basicUnsafeReplicate n (fromMoebius x) + basicUnsafeRead (MV_Moebius v) i = toMoebius `liftM` M.basicUnsafeRead v i + basicUnsafeWrite (MV_Moebius v) i x = M.basicUnsafeWrite v i (fromMoebius x) + basicClear (MV_Moebius v) = M.basicClear v + basicSet (MV_Moebius v) x = M.basicSet v (fromMoebius x) + basicUnsafeCopy (MV_Moebius v1) (MV_Moebius v2) = M.basicUnsafeCopy v1 v2 + basicUnsafeMove (MV_Moebius v1) (MV_Moebius v2) = M.basicUnsafeMove v1 v2 + basicUnsafeGrow (MV_Moebius v) n = MV_Moebius `liftM` M.basicUnsafeGrow v n + +instance G.Vector U.Vector Moebius where + basicUnsafeFreeze (MV_Moebius v) = V_Moebius `liftM` G.basicUnsafeFreeze v + basicUnsafeThaw (V_Moebius v) = MV_Moebius `liftM` G.basicUnsafeThaw v + basicLength (V_Moebius v) = G.basicLength v + basicUnsafeSlice i n (V_Moebius v) = V_Moebius $ G.basicUnsafeSlice i n v + basicUnsafeIndexM (V_Moebius v) i = toMoebius `liftM` G.basicUnsafeIndexM v i + basicUnsafeCopy (MV_Moebius mv) (V_Moebius v) = G.basicUnsafeCopy mv v + elemseq _ = seq diff --git a/testsuite/tests/simplCore/should_run/all.T b/testsuite/tests/simplCore/should_run/all.T index 4ba5a71..d922f90 100644 --- a/testsuite/tests/simplCore/should_run/all.T +++ b/testsuite/tests/simplCore/should_run/all.T @@ -78,3 +78,4 @@ test('T13429', normal, compile_and_run, ['']) test('T13429_2', normal, compile_and_run, ['']) test('T13750', normal, compile_and_run, ['']) test('T14178', normal, compile_and_run, ['']) +test('T14768', reqlib('vector'), compile_and_run, ['']) From git at git.haskell.org Mon Feb 19 20:06:39 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Feb 2018 20:06:39 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: Implement stopgap solution for #14728 (c21a8cc) Message-ID: <20180219200639.F36713A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/c21a8cc2210a8a1b01de1a05f4f83ad6a6bad652/ghc >--------------------------------------------------------------- commit c21a8cc2210a8a1b01de1a05f4f83ad6a6bad652 Author: Ryan Scott Date: Sun Feb 18 11:00:40 2018 -0500 Implement stopgap solution for #14728 It turns out that one can produce ill-formed Core by combining `GeneralizedNewtypeDeriving`, `TypeInType`, and `TypeFamilies`, as demonstrated in #14728. The root of the problem is allowing the last parameter of a class to appear in a //kind// of an associated type family, as our current approach to deriving associated type family instances simply doesn't work well for that situation. Although it might be possible to properly implement this feature today (see https://ghc.haskell.org/trac/ghc/ticket/14728#comment:3 for a sketch of how this might work), there does not currently exist a performant implementation of the algorithm needed to accomplish this. Until such an implementation surfaces, we will make this corner case of `GeneralizedNewtypeDeriving` an error. Test Plan: make test TEST="T14728a T14728b" Reviewers: bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14728 Differential Revision: https://phabricator.haskell.org/D4402 (cherry picked from commit 1ede46d415757f53af33bc6672bd9d3fba7f205d) >--------------------------------------------------------------- c21a8cc2210a8a1b01de1a05f4f83ad6a6bad652 compiler/typecheck/TcDeriv.hs | 43 ++++++++++++++++++++-- testsuite/tests/deriving/should_fail/T14728a.hs | 20 ++++++++++ .../tests/deriving/should_fail/T14728a.stderr | 7 ++++ testsuite/tests/deriving/should_fail/T14728b.hs | 16 ++++++++ .../tests/deriving/should_fail/T14728b.stderr | 7 ++++ testsuite/tests/deriving/should_fail/all.T | 2 + 6 files changed, 92 insertions(+), 3 deletions(-) diff --git a/compiler/typecheck/TcDeriv.hs b/compiler/typecheck/TcDeriv.hs index 33ce581..a93712c 100644 --- a/compiler/typecheck/TcDeriv.hs +++ b/compiler/typecheck/TcDeriv.hs @@ -1314,6 +1314,8 @@ mkNewTypeEqn && ats_ok -- Check (b) from Note [GND and associated type families] && isNothing at_without_last_cls_tv + -- Check (d) from Note [GND and associated type families] + && isNothing at_last_cls_tv_in_kinds -- Check that eta reduction is OK eta_ok = rep_tc_args `lengthAtLeast` nt_eta_arity @@ -1330,6 +1332,12 @@ mkNewTypeEqn at_without_last_cls_tv = find (\tc -> last_cls_tv `notElem` tyConTyVars tc) atf_tcs + at_last_cls_tv_in_kinds + = find (\tc -> any (at_last_cls_tv_in_kind . tyVarKind) + (tyConTyVars tc) + || at_last_cls_tv_in_kind (tyConResKind tc)) atf_tcs + at_last_cls_tv_in_kind kind + = last_cls_tv `elemVarSet` exactTyCoVarsOfType kind at_tcs = classATs cls last_cls_tv = ASSERT( notNull cls_tyvars ) last cls_tyvars @@ -1337,14 +1345,22 @@ mkNewTypeEqn cant_derive_err = vcat [ ppUnless eta_ok eta_msg , ppUnless ats_ok ats_msg - , maybe empty at_tv_msg - at_without_last_cls_tv] + , maybe empty at_without_last_cls_tv_msg + at_without_last_cls_tv + , maybe empty at_last_cls_tv_in_kinds_msg + at_last_cls_tv_in_kinds + ] eta_msg = text "cannot eta-reduce the representation type enough" ats_msg = text "the class has associated data types" - at_tv_msg at_tc = hang + at_without_last_cls_tv_msg at_tc = hang (text "the associated type" <+> quotes (ppr at_tc) <+> text "is not parameterized over the last type variable") 2 (text "of the class" <+> quotes (ppr cls)) + at_last_cls_tv_in_kinds_msg at_tc = hang + (text "the associated type" <+> quotes (ppr at_tc) + <+> text "contains the last type variable") + 2 (text "of the class" <+> quotes (ppr cls) + <+> text "in a kind, which is not (yet) allowed") MASSERT( cls_tys `lengthIs` (classArity cls - 1) ) case mb_strat of @@ -1530,6 +1546,27 @@ However, we must watch out for three things: GHC's termination checker isn't sophisticated enough to conclude that the definition of T MyInt terminates, so UndecidableInstances is required. +(d) For the time being, we do not allow the last type variable of the class to + appear in a /kind/ of an associated type family definition. For instance: + + class C a where + type T1 a -- OK + type T2 (x :: a) -- Illegal: a appears in the kind of x + type T3 y :: a -- Illegal: a appears in the kind of (T3 y) + + The reason we disallow this is because our current approach to deriving + associated type family instances—i.e., by unwrapping the newtype's type + constructor as shown above—is ill-equipped to handle the scenario when + the last type variable appears as an implicit argument. In the worst case, + allowing the last variable to appear in a kind can result in improper Core + being generated (see #14728). + + There is hope for this feature being added some day, as one could + conceivably take a newtype axiom (which witnesses a coercion between a + newtype and its representation type) at lift that through each associated + type at the Core level. See #14728, comment:3 for a sketch of how this + might work. Until then, we disallow this featurette wholesale. + ************************************************************************ * * \subsection[TcDeriv-normal-binds]{Bindings for the various classes} diff --git a/testsuite/tests/deriving/should_fail/T14728a.hs b/testsuite/tests/deriving/should_fail/T14728a.hs new file mode 100644 index 0000000..28cf8e0 --- /dev/null +++ b/testsuite/tests/deriving/should_fail/T14728a.hs @@ -0,0 +1,20 @@ +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE StandaloneDeriving #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE TypeInType #-} +module T14728a where + +import Data.Functor.Identity +import Data.Kind + +class C (a :: Type) where + type T a (x :: a) :: Type + type U z :: a + +instance C () where + type T () '() = Bool + +deriving instance C (Identity a) + +f :: T (Identity ()) ('Identity '()) +f = True diff --git a/testsuite/tests/deriving/should_fail/T14728a.stderr b/testsuite/tests/deriving/should_fail/T14728a.stderr new file mode 100644 index 0000000..b76d073 --- /dev/null +++ b/testsuite/tests/deriving/should_fail/T14728a.stderr @@ -0,0 +1,7 @@ + +T14728a.hs:17:1: error: + • Can't make a derived instance of ‘C (Identity a)’ + (even with cunning GeneralizedNewtypeDeriving): + the associated type ‘T’ contains the last type variable + of the class ‘C’ in a kind, which is not (yet) allowed + • In the stand-alone deriving instance for ‘C (Identity a)’ diff --git a/testsuite/tests/deriving/should_fail/T14728b.hs b/testsuite/tests/deriving/should_fail/T14728b.hs new file mode 100644 index 0000000..7fdfcb3 --- /dev/null +++ b/testsuite/tests/deriving/should_fail/T14728b.hs @@ -0,0 +1,16 @@ +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE StandaloneDeriving #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE TypeInType #-} +module T14728b where + +import Data.Functor.Identity +import Data.Kind + +class C (a :: Type) where + type U z :: a + +instance C () where + type U z = '() + +deriving instance C (Identity a) diff --git a/testsuite/tests/deriving/should_fail/T14728b.stderr b/testsuite/tests/deriving/should_fail/T14728b.stderr new file mode 100644 index 0000000..ee74f8b4 --- /dev/null +++ b/testsuite/tests/deriving/should_fail/T14728b.stderr @@ -0,0 +1,7 @@ + +T14728b.hs:16:1: error: + • Can't make a derived instance of ‘C (Identity a)’ + (even with cunning GeneralizedNewtypeDeriving): + the associated type ‘U’ contains the last type variable + of the class ‘C’ in a kind, which is not (yet) allowed + • In the stand-alone deriving instance for ‘C (Identity a)’ diff --git a/testsuite/tests/deriving/should_fail/all.T b/testsuite/tests/deriving/should_fail/all.T index c9b8469..acd3486 100644 --- a/testsuite/tests/deriving/should_fail/all.T +++ b/testsuite/tests/deriving/should_fail/all.T @@ -69,3 +69,5 @@ test('T12512', omit_ways(['ghci']), compile_fail, ['']) test('T12801', normal, compile_fail, ['']) test('T14365', [extra_files(['T14365B.hs','T14365B.hs-boot'])], multimod_compile_fail, ['T14365A','']) +test('T14728a', normal, compile_fail, ['']) +test('T14728b', normal, compile_fail, ['']) From git at git.haskell.org Mon Feb 19 20:06:51 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Feb 2018 20:06:51 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: CBE: re-introduce bgamari's fixes (af454c4) Message-ID: <20180219200651.A65513A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/af454c454a577ce20ee782a0b0e04dfcaeacb143/ghc >--------------------------------------------------------------- commit af454c454a577ce20ee782a0b0e04dfcaeacb143 Author: Michal Terepeta Date: Sun Feb 18 11:09:40 2018 -0500 CBE: re-introduce bgamari's fixes During some recent work on CBE we discovered that `zipWith` is used to check for equality, but that doesn't quite work if lists are of different lengths! This was fixed by bgamari, but unfortunately the fix had to be rolled back due to other changes in CBE in 50adbd7c5fe5894d3e6e2a58b353ed07e5f8949d. Since I wanted to have another look at CBE anyway, we agreed that the first thing to do would be to re-introduce the fix. Sadly I don't have any actual test case that would exercise this. Signed-off-by: Michal Terepeta Test Plan: ./validate Reviewers: bgamari, simonmar Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14226 Differential Revision: https://phabricator.haskell.org/D4387 (cherry picked from commit 4e513bf758c32804fc71b98215f96e8481697a36) >--------------------------------------------------------------- af454c454a577ce20ee782a0b0e04dfcaeacb143 compiler/cmm/CmmCommonBlockElim.hs | 11 ++++++++--- 1 file changed, 8 insertions(+), 3 deletions(-) diff --git a/compiler/cmm/CmmCommonBlockElim.hs b/compiler/cmm/CmmCommonBlockElim.hs index f635520..7f4e290 100644 --- a/compiler/cmm/CmmCommonBlockElim.hs +++ b/compiler/cmm/CmmCommonBlockElim.hs @@ -209,7 +209,7 @@ eqMiddleWith eqBid (CmmStore l1 r1) (CmmStore l2 r2) = eqExprWith eqBid l1 l2 && eqExprWith eqBid r1 r2 eqMiddleWith eqBid (CmmUnsafeForeignCall t1 r1 a1) (CmmUnsafeForeignCall t2 r2 a2) - = t1 == t2 && r1 == r2 && and (zipWith (eqExprWith eqBid) a1 a2) + = t1 == t2 && r1 == r2 && eqListWith (eqExprWith eqBid) a1 a2 eqMiddleWith _ _ _ = False eqExprWith :: (BlockId -> BlockId -> Bool) @@ -224,7 +224,7 @@ eqExprWith eqBid = eq CmmStackSlot a1 i1 `eq` CmmStackSlot a2 i2 = eqArea a1 a2 && i1==i2 _e1 `eq` _e2 = False - xs `eqs` ys = and (zipWith eq xs ys) + xs `eqs` ys = eqListWith eq xs ys eqLit (CmmBlock id1) (CmmBlock id2) = eqBid id1 id2 eqLit l1 l2 = l1 == l2 @@ -247,7 +247,7 @@ eqBlockBodyWith eqBid block block' (_,m',l') = blockSplit block' nodes' = filter (not . dont_care) (blockToList m') - equal = and (zipWith (eqMiddleWith eqBid) nodes nodes') && + equal = eqListWith (eqMiddleWith eqBid) nodes nodes' && eqLastWith eqBid l l' @@ -266,6 +266,11 @@ eqMaybeWith eltEq (Just e) (Just e') = eltEq e e' eqMaybeWith _ Nothing Nothing = True eqMaybeWith _ _ _ = False +eqListWith :: (a -> b -> Bool) -> [a] -> [b] -> Bool +eqListWith f (a : as) (b : bs) = f a b && eqListWith f as bs +eqListWith _ [] [] = True +eqListWith _ _ _ = False + -- | Given a block map, ensure that all "target" blocks are covered by -- the same ticks as the respective "source" blocks. This not only -- means copying ticks, but also adjusting tick scopes where From git at git.haskell.org Mon Feb 19 20:06:48 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Feb 2018 20:06:48 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: Bump text submodule to 1.2.3.0 (ff39d00) Message-ID: <20180219200648.E0FEC3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/ff39d000d9285f763691b07e47821ac21d0115f6/ghc >--------------------------------------------------------------- commit ff39d000d9285f763691b07e47821ac21d0115f6 Author: Ben Gamari Date: Sun Feb 18 11:31:41 2018 -0500 Bump text submodule to 1.2.3.0 >--------------------------------------------------------------- ff39d000d9285f763691b07e47821ac21d0115f6 libraries/text | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/text b/libraries/text index 2d88a0a..a02c2da 160000 --- a/libraries/text +++ b/libraries/text @@ -1 +1 @@ -Subproject commit 2d88a0a3e8e3bb79260e5c8f61dd6c447f61c5f5 +Subproject commit a02c2dafafa425bd5f36c8629e98b98daf1cfa1e From git at git.haskell.org Mon Feb 19 20:06:54 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Feb 2018 20:06:54 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: Bump haddock submodule (0e5c823) Message-ID: <20180219200654.72FAF3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/0e5c8232089468b1667490b23d927060acd7cb55/ghc >--------------------------------------------------------------- commit 0e5c8232089468b1667490b23d927060acd7cb55 Author: Ben Gamari Date: Mon Feb 19 00:00:06 2018 -0500 Bump haddock submodule >--------------------------------------------------------------- 0e5c8232089468b1667490b23d927060acd7cb55 testsuite/tests/perf/haddock/all.T | 6 ++++-- utils/haddock | 2 +- 2 files changed, 5 insertions(+), 3 deletions(-) diff --git a/testsuite/tests/perf/haddock/all.T b/testsuite/tests/perf/haddock/all.T index 576ac38..061957b 100644 --- a/testsuite/tests/perf/haddock/all.T +++ b/testsuite/tests/perf/haddock/all.T @@ -9,7 +9,7 @@ test('haddock.base', [(platform('x86_64-unknown-mingw32'), 24286343184, 5) # 2017-02-19 24286343184 (x64/Windows) - Generalize kind of (->) - ,(wordsize(64), 19694554424, 5) + ,(wordsize(64), 21081999344, 5) # 2012-08-14: 5920822352 (amd64/Linux) # 2012-09-20: 5829972376 (amd64/Linux) # 2012-10-08: 5902601224 (amd64/Linux) @@ -43,6 +43,7 @@ test('haddock.base', # 2017-06-06: 25173968808 (x86_64/Linux) - Don't pass on -dcore-lint in Haddock.mk # 2017-07-12: 23677299848 (x86_64/Linux) - Use getNameToInstancesIndex # 2017-08-22: 19694554424 (x86_64/Linux) - Various Haddock optimizations + # 2018-02-19: 21081999344 (x86_64/Linux) - Bump haddock submodule ,(platform('i386-unknown-mingw32'), 2885173512, 5) # 2013-02-10: 3358693084 (x86/Windows) @@ -69,7 +70,7 @@ test('haddock.Cabal', [extra_files(['../../../../libraries/Cabal/Cabal/dist-install/haddock.t']), unless(in_tree_compiler(), skip), req_haddock ,stats_num_field('bytes allocated', - [(wordsize(64), 25699561072, 5) + [(wordsize(64), 27433417704, 5) # 2012-08-14: 3255435248 (amd64/Linux) # 2012-08-29: 3324606664 (amd64/Linux, new codegen) # 2012-10-08: 3373401360 (amd64/Linux) @@ -122,6 +123,7 @@ test('haddock.Cabal', # 2017-11-06: 18936339648 (amd64/Linux) - Unknown # 2017-11-09: 20104611952 (amd64/Linux) - Bump Cabal # 2018-02-03: 25699561072 (x86_64/Linux) - Bump haddock submodule + # 2018-02-19: 27433417704 (x86_64/Linux) - Bump haddock submodule ,(platform('i386-unknown-mingw32'), 3293415576, 5) # 2012-10-30: 1733638168 (x86/Windows) diff --git a/utils/haddock b/utils/haddock index 5141e4b..d66092e 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit 5141e4b76af8462e49abdf48e44bb9cddb183383 +Subproject commit d66092ee99639de628dbc4fce8a9936875f47d8c From git at git.haskell.org Mon Feb 19 21:48:39 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Feb 2018 21:48:39 +0000 (UTC) Subject: [commit: ghc] master: Bump haddock submodule again (9fc4608) Message-ID: <20180219214839.6E44E3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9fc4608e5ed09199f7a7469f22275919c9bba2de/ghc >--------------------------------------------------------------- commit 9fc4608e5ed09199f7a7469f22275919c9bba2de Author: Ben Gamari Date: Sun Feb 18 12:02:44 2018 -0500 Bump haddock submodule again >--------------------------------------------------------------- 9fc4608e5ed09199f7a7469f22275919c9bba2de utils/haddock | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/haddock b/utils/haddock index 0ef6a26..06fc493 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit 0ef6a26d49fc2b3a5785a55d95b64f77c40e58ad +Subproject commit 06fc4934e96bd2e647496ec0082d6ef362328f64 From git at git.haskell.org Mon Feb 19 21:48:42 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Feb 2018 21:48:42 +0000 (UTC) Subject: [commit: ghc] master: Bump filepath submodule (fc04a8f) Message-ID: <20180219214842.5A5613A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fc04a8f39661bb9031706a4f1c6ed15397e10ab5/ghc >--------------------------------------------------------------- commit fc04a8f39661bb9031706a4f1c6ed15397e10ab5 Author: Ben Gamari Date: Tue Jan 23 01:09:52 2018 -0500 Bump filepath submodule >--------------------------------------------------------------- fc04a8f39661bb9031706a4f1c6ed15397e10ab5 libraries/filepath | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/filepath b/libraries/filepath index 9c64a63..0991bf3 160000 --- a/libraries/filepath +++ b/libraries/filepath @@ -1 +1 @@ -Subproject commit 9c64a634c144392f36cdad5c8c067824093a64d6 +Subproject commit 0991bf392dbd56b5db9f155ee64fb122ca55017c From git at git.haskell.org Mon Feb 19 21:48:45 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Feb 2018 21:48:45 +0000 (UTC) Subject: [commit: ghc] master: Bump primitive submodule to 0.6.3.0 (bd0af2a) Message-ID: <20180219214845.208FF3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bd0af2a61df1c4b5d9ba746fc91496cb41e494a3/ghc >--------------------------------------------------------------- commit bd0af2a61df1c4b5d9ba746fc91496cb41e494a3 Author: Ben Gamari Date: Thu Feb 15 11:42:35 2018 -0500 Bump primitive submodule to 0.6.3.0 >--------------------------------------------------------------- bd0af2a61df1c4b5d9ba746fc91496cb41e494a3 libraries/primitive | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/primitive b/libraries/primitive index 260cc97..53f72ce 160000 --- a/libraries/primitive +++ b/libraries/primitive @@ -1 +1 @@ -Subproject commit 260cc9755ee6928876e5174998425cd5863c34a2 +Subproject commit 53f72ce69a4dfde5345cf5809a8b4a1993523367 From git at git.haskell.org Mon Feb 19 21:48:47 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Feb 2018 21:48:47 +0000 (UTC) Subject: [commit: ghc] master: Bump stm submodule to 2.4.5.0 (9ad3fa1) Message-ID: <20180219214847.DE3043A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9ad3fa1ddd3d02e01a964d6f4e50fb80e6e6e776/ghc >--------------------------------------------------------------- commit 9ad3fa1ddd3d02e01a964d6f4e50fb80e6e6e776 Author: Ben Gamari Date: Sat Feb 3 16:23:05 2018 -0500 Bump stm submodule to 2.4.5.0 >--------------------------------------------------------------- 9ad3fa1ddd3d02e01a964d6f4e50fb80e6e6e776 libraries/stm | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/stm b/libraries/stm index 8194700..5ea70d4 160000 --- a/libraries/stm +++ b/libraries/stm @@ -1 +1 @@ -Subproject commit 819470093eccb81d058408076df8903e781f551c +Subproject commit 5ea70d4e15d461888866796a164bf9c177a1e8b8 From git at git.haskell.org Mon Feb 19 21:48:50 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Feb 2018 21:48:50 +0000 (UTC) Subject: [commit: ghc] master: Bump haskeline submodule to 0.7.4.2 (1ee5abc) Message-ID: <20180219214850.A986D3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1ee5abcda16f7db18789daff652840b0fd9ec137/ghc >--------------------------------------------------------------- commit 1ee5abcda16f7db18789daff652840b0fd9ec137 Author: Ben Gamari Date: Sun Feb 18 11:29:56 2018 -0500 Bump haskeline submodule to 0.7.4.2 >--------------------------------------------------------------- 1ee5abcda16f7db18789daff652840b0fd9ec137 libraries/haskeline | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/haskeline b/libraries/haskeline index 1436a8c..019e08f 160000 --- a/libraries/haskeline +++ b/libraries/haskeline @@ -1 +1 @@ -Subproject commit 1436a8c7c8ee5076c99e09fe20943bf6101237af +Subproject commit 019e08f2c91b7cc45e5fb98189193a9f5c2d2d57 From git at git.haskell.org Mon Feb 19 21:48:53 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Feb 2018 21:48:53 +0000 (UTC) Subject: [commit: ghc] master: Bump pretty submodule (d20524e) Message-ID: <20180219214853.74C323A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d20524e715e9d5119578360e06bb23de9438b3ec/ghc >--------------------------------------------------------------- commit d20524e715e9d5119578360e06bb23de9438b3ec Author: Ben Gamari Date: Mon Jan 29 01:28:13 2018 -0500 Bump pretty submodule >--------------------------------------------------------------- d20524e715e9d5119578360e06bb23de9438b3ec libraries/pretty | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/pretty b/libraries/pretty index 445e92d..c3a1469 160000 --- a/libraries/pretty +++ b/libraries/pretty @@ -1 +1 @@ -Subproject commit 445e92dd7508978caba5563c1e79b2758dff4767 +Subproject commit c3a1469306b35fa5d023dc570554f97f1a90435d From git at git.haskell.org Mon Feb 19 21:49:02 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Feb 2018 21:49:02 +0000 (UTC) Subject: [commit: ghc] master: Bump text submodule to 1.2.3.0 (2cb19b4) Message-ID: <20180219214902.1A7943A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2cb19b472ff4cdeca0d83c713c853d12c1434691/ghc >--------------------------------------------------------------- commit 2cb19b472ff4cdeca0d83c713c853d12c1434691 Author: Ben Gamari Date: Sun Feb 18 11:31:41 2018 -0500 Bump text submodule to 1.2.3.0 >--------------------------------------------------------------- 2cb19b472ff4cdeca0d83c713c853d12c1434691 libraries/text | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/text b/libraries/text index 2d88a0a..a02c2da 160000 --- a/libraries/text +++ b/libraries/text @@ -1 +1 @@ -Subproject commit 2d88a0a3e8e3bb79260e5c8f61dd6c447f61c5f5 +Subproject commit a02c2dafafa425bd5f36c8629e98b98daf1cfa1e From git at git.haskell.org Mon Feb 19 21:48:59 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Feb 2018 21:48:59 +0000 (UTC) Subject: [commit: ghc] master: Bump parsec submodule to 0.3.13.0 (e26d774) Message-ID: <20180219214859.4CE733A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e26d774b0754efd62402cea8f29cd6340bd3e4be/ghc >--------------------------------------------------------------- commit e26d774b0754efd62402cea8f29cd6340bd3e4be Author: Ben Gamari Date: Thu Feb 15 11:43:35 2018 -0500 Bump parsec submodule to 0.3.13.0 >--------------------------------------------------------------- e26d774b0754efd62402cea8f29cd6340bd3e4be libraries/parsec | 2 +- utils/ghc-cabal/ghc.mk | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/libraries/parsec b/libraries/parsec index 1c56e08..00dd731 160000 --- a/libraries/parsec +++ b/libraries/parsec @@ -1 +1 @@ -Subproject commit 1c56e0885173accbd3296aa5591a3e0c18084e7a +Subproject commit 00dd731bc12746ac7d4341348abe733c5373cdb7 diff --git a/utils/ghc-cabal/ghc.mk b/utils/ghc-cabal/ghc.mk index e0d2afe..70e418e 100644 --- a/utils/ghc-cabal/ghc.mk +++ b/utils/ghc-cabal/ghc.mk @@ -75,7 +75,7 @@ $(ghc-cabal_DIST_BINARY): $(CABAL_LEXER_DEP) utils/ghc-cabal/Main.hs $(TOUCH_DEP -ilibraries/text \ libraries/text/cbits/cbits.c \ -Ilibraries/text/include \ - -ilibraries/parsec \ + -ilibraries/parsec/src \ $(utils/ghc-cabal_dist_EXTRA_HC_OPTS) \ $(EXTRA_HC_OPTS) "$(TOUCH_CMD)" $@ From git at git.haskell.org Mon Feb 19 21:48:56 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Feb 2018 21:48:56 +0000 (UTC) Subject: [commit: ghc] master: Bump process submodule (2382bbf) Message-ID: <20180219214856.8165C3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2382bbf860673e9454e90e2fae8aadbc283a98ad/ghc >--------------------------------------------------------------- commit 2382bbf860673e9454e90e2fae8aadbc283a98ad Author: Ben Gamari Date: Tue Jan 23 01:09:34 2018 -0500 Bump process submodule >--------------------------------------------------------------- 2382bbf860673e9454e90e2fae8aadbc283a98ad libraries/process | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/process b/libraries/process index 2364a36..7c0b581 160000 --- a/libraries/process +++ b/libraries/process @@ -1 +1 @@ -Subproject commit 2364a36549d461adc4886ef33f259638336a87d2 +Subproject commit 7c0b58141290b50a338bf391adc0a8c43513165b From git at git.haskell.org Tue Feb 20 03:13:08 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 20 Feb 2018 03:13:08 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Bump allocations for T1969 and T5837 (71294f3) Message-ID: <20180220031308.E164E3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/71294f30fa20ea9c4653f76da20a5f8170ee415b/ghc >--------------------------------------------------------------- commit 71294f30fa20ea9c4653f76da20a5f8170ee415b Author: Ben Gamari Date: Mon Feb 19 19:36:22 2018 -0500 testsuite: Bump allocations for T1969 and T5837 Sadly it's not immediately obvious where this regression came from: * T5837 started failing on OS X with 0c2350c293b82e4cb24a66e00b904933bdb1c8f3 * It's not clear when T1969 started failing due to the recent out of memory issues on Harbormaster >--------------------------------------------------------------- 71294f30fa20ea9c4653f76da20a5f8170ee415b testsuite/tests/perf/compiler/all.T | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index 1ac19e5..1ae69e7 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -73,7 +73,7 @@ test('T1969', # 2017-03-24 9261052 (x86/Linux, 64-bit machine) # 2017-04-06 9418680 (x86/Linux, 64-bit machine) - (wordsize(64), 19199872, 15)]), + (wordsize(64), 22311600, 15)]), # 2014-09-10 10463640, 10 # post-AMP-update (somewhat stabelish) # looks like the peak is around ~10M, but we're # unlikely to GC exactly on the peak. @@ -89,6 +89,7 @@ test('T1969', # 2017-02-14 16393848 Early inline patch # 2017-03-31 16679176 Fix memory leak in simplifier # 2017-08-25 19199872 Refactor the Mighty Simplifier + # 2018-02-19 22311600 (amd64/Linux) Unknown compiler_stats_num_field('bytes allocated', [(platform('i386-unknown-mingw32'), 301784492, 5), @@ -664,7 +665,7 @@ test('T5837', # 2017-04-21 54985248 (x64/Windows) - Unknown # 2017-12-24 54793816 (x64/Windows) - Unknown - (wordsize(64), 52089424, 7)]) + (wordsize(64), 55813608, 7)]) # sample: 3926235424 (amd64/Linux, 15/2/2012) # 2012-10-02 81879216 # 2012-09-20 87254264 amd64/Linux @@ -702,6 +703,7 @@ test('T5837', # 2017-02-25 52625920 amd64/Linux Early inlining patch # 2017-09-06 56782344 amd64/Linux Drift manifest in unrelated LLVM patch # 2017-10-24 52089424 amd64/linux Fix space leak in BinIface.getSymbolTable + # 2018-02-19 55813608 amd64/Linux Unknown ], compile, ['-freduction-depth=50']) From git at git.haskell.org Tue Feb 20 04:02:45 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 20 Feb 2018 04:02:45 +0000 (UTC) Subject: [commit: ghc] master: Change how includes for input file directory works (eb2daa2) Message-ID: <20180220040245.79D733A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/eb2daa2b6a83412382aa0fcda598f8b3d40fde2c/ghc >--------------------------------------------------------------- commit eb2daa2b6a83412382aa0fcda598f8b3d40fde2c Author: Tamar Christina Date: Mon Feb 19 22:13:46 2018 -0500 Change how includes for input file directory works GHC Used to only allow for one include mode, namely `-I`. The problem with `-I` includes is that it supercedes all other includes, including the system include paths. This is not a problem for paths requested by the user, but it is a problem for the ones we implicitly derive and add. In particular we add the source directory of the input file to the include path. This is problematic because it causes any file with the name of a system include, to inadvertently loop as the wrong file gets included. Since this is an implicitly include, and as far as I can tell, only done so local includes are found (as the sources given to GCC reside in a temp folder) then switch from `-I` to `-iquote`. This requires a submodule update for haddock Test Plan: ./validate Reviewers: austin, bgamari, hvr Reviewed By: bgamari Subscribers: carter, rwbarton, thomie GHC Trac Issues: #14312 Differential Revision: https://phabricator.haskell.org/D4080 >--------------------------------------------------------------- eb2daa2b6a83412382aa0fcda598f8b3d40fde2c compiler/deSugar/DsForeign.hs | 3 ++- compiler/iface/FlagChecker.hs | 3 ++- compiler/main/DriverPipeline.hs | 26 +++++++++++++++++-------- compiler/main/DynFlags.hs | 42 +++++++++++++++++++++++++++++++++++----- docs/users_guide/8.6.1-notes.rst | 3 +++ utils/haddock | 2 +- 6 files changed, 63 insertions(+), 16 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc eb2daa2b6a83412382aa0fcda598f8b3d40fde2c From git at git.haskell.org Tue Feb 20 04:45:26 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 20 Feb 2018 04:45:26 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T14684' created Message-ID: <20180220044526.0C98E3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T14684 Referencing: fe98cd7538ce18dec260b50ca756d06929ae0b3b From git at git.haskell.org Tue Feb 20 04:45:29 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 20 Feb 2018 04:45:29 +0000 (UTC) Subject: [commit: ghc] wip/T14684: Combine the CoreAlts with the most common RHS (fe98cd7) Message-ID: <20180220044529.C81723A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14684 Link : http://ghc.haskell.org/trac/ghc/changeset/fe98cd7538ce18dec260b50ca756d06929ae0b3b/ghc >--------------------------------------------------------------- commit fe98cd7538ce18dec260b50ca756d06929ae0b3b Author: Simon Jakobi Date: Mon Feb 19 23:44:52 2018 -0500 Combine the CoreAlts with the most common RHS Unless there already is a DEFAULT alternative, look for the most common RHS and create a new DEFAULT alt. Previously, only the very first RHS was considered. Test Plan: make test TEST="T7360 T14684" Reviewers: bgamari Subscribers: AndreasK, mpickering, rwbarton, thomie, carter GHC Trac Issues: #14684 Differential Revision: https://phabricator.haskell.org/D4419 >--------------------------------------------------------------- fe98cd7538ce18dec260b50ca756d06929ae0b3b compiler/coreSyn/CoreUtils.hs | 87 ++++++++++++++-------- testsuite/tests/simplCore/should_compile/Makefile | 3 + testsuite/tests/simplCore/should_compile/T14684.hs | 18 +++++ .../tests/simplCore/should_compile/T14684.stdout | 6 ++ testsuite/tests/simplCore/should_compile/all.T | 4 + 5 files changed, 88 insertions(+), 30 deletions(-) diff --git a/compiler/coreSyn/CoreUtils.hs b/compiler/coreSyn/CoreUtils.hs index 3d5f4bc..157d6d2 100644 --- a/compiler/coreSyn/CoreUtils.hs +++ b/compiler/coreSyn/CoreUtils.hs @@ -61,6 +61,7 @@ module CoreUtils ( import GhcPrelude import CoreSyn +import TrieMap import PrelNames ( makeStaticName ) import PprCore import CoreFVs( exprFreeVars ) @@ -692,16 +693,26 @@ DEFAULT alternative. I've occasionally seen this making a big difference: case e of =====> case e of + DEFAULT -> f x DEFAULT -> f x C _ -> f x D v -> ....v.... - D v -> ....v.... DEFAULT -> f x - DEFAULT -> f x + D v -> ....v.... -The point is that we merge common RHSs, at least for the DEFAULT case. -[One could do something more elaborate but I've never seen it needed.] -To avoid an expensive test, we just merge branches equal to the *first* -alternative; this picks up the common cases - a) all branches equal - b) some branches equal to the DEFAULT (which occurs first) +Our method of finding identical branches depends on whether or not +there already is a DEFAULT case: + + * If there is a DEFAULT case (which always comes first) we just look + for more branches with the same RHS and merge them into the existing + DEFAULT case. + + * Otherwise we look for the most common RHS and form a new DEFAULT + case from those alternatives: + + case a of =====> case a of + A -> f x DEFAULT -> g x + B -> g x A -> f x + C -> f x C -> f x + D -> g x + E -> g x The case where Combine Identical Alternatives transformation showed up was like this (base/Foreign/C/Err/Error.hs): @@ -717,9 +728,9 @@ where @is@ was something like This gave rise to a horrible sequence of cases case p of - (-1) -> $j p - 1 -> e1 DEFAULT -> $j p + (-1) -> $j p + 1 -> e1 and similarly in cascade for all the join points! @@ -773,33 +784,49 @@ missed the first one.) combineIdenticalAlts :: [AltCon] -- Constructors that cannot match DEFAULT -> [CoreAlt] - -> (Bool, -- True <=> something happened + -> (Bool, -- True <=> we combined some alts [AltCon], -- New constructors that cannot match DEFAULT [CoreAlt]) -- New alternatives -- See Note [Combine identical alternatives] --- True <=> we did some combining, result is a single DEFAULT alternative -combineIdenticalAlts imposs_deflt_cons ((con1,bndrs1,rhs1) : rest_alts) - | all isDeadBinder bndrs1 -- Remember the default - , not (null elim_rest) -- alternative comes first - = (True, imposs_deflt_cons', deflt_alt : filtered_rest) +combineIdenticalAlts imposs_deflt_cons alts + = case identical_alts of + (_con, _bndrs, rhs1) : elim_rest@(_ : _) + -> (True, imposs_deflt_cons', alts') + where + -- See Note + -- [Care with impossible-constructors when combining alternatives] + imposs_deflt_cons' = imposs_deflt_cons `minusList` elim_cons + elim_cons = map fstOf3 identical_alts + + alts' = deflt_alt : filter (not . cheapEqTicked rhs1 . thdOf3) alts + deflt_alt = (DEFAULT, [], mkTicks (concat tickss) rhs1) + tickss = map (stripTicksT tickishFloatable . thdOf3) elim_rest + _ -> (False, imposs_deflt_cons, alts) where - (elim_rest, filtered_rest) = partition identical_to_alt1 rest_alts - deflt_alt = (DEFAULT, [], mkTicks (concat tickss) rhs1) + identical_alts + = case alts of + (DEFAULT, [], rhs1) : _ + -> filter (cheapEqTicked rhs1 . thdOf3) dead_bindr_alts + _ -> most_common_alts -- See #14684 + dead_bindr_alts = filter (all isDeadBinder . sndOf3) alts + cheapEqTicked e1 e2 = cheapEqExpr' tickishFloatable e1 e2 + most_common_alts = foldCoreMap longest [] core_map + where + core_map = foldr updateCM emptyCoreMap dead_bindr_alts - -- See Note [Care with impossible-constructors when combining alternatives] - imposs_deflt_cons' = imposs_deflt_cons `minusList` elim_cons - elim_cons = elim_con1 ++ map fstOf3 elim_rest - elim_con1 = case con1 of -- Don't forget con1! - DEFAULT -> [] -- See Note [ - _ -> [con1] + updateCM :: CoreAlt -> CoreMap [CoreAlt] -> CoreMap [CoreAlt] + updateCM ca@(_, _, rhs) cm + = alterTM (stripTicksE tickishFloatable rhs) (prepend ca) cm - cheapEqTicked e1 e2 = cheapEqExpr' tickishFloatable e1 e2 - identical_to_alt1 (_con,bndrs,rhs) - = all isDeadBinder bndrs && rhs `cheapEqTicked` rhs1 - tickss = map (stripTicksT tickishFloatable . thdOf3) elim_rest + prepend x (Just xs) = Just (x : xs) + prepend x Nothing = Just [x] -combineIdenticalAlts imposs_cons alts - = (False, imposs_cons, alts) + longest :: [a] -> [a] -> [a] + longest xs ys = go xs ys + where + go _ [] = xs + go [] _ = ys + go (_:xs') (_:ys') = go xs' ys' {- ********************************************************************* * * diff --git a/testsuite/tests/simplCore/should_compile/Makefile b/testsuite/tests/simplCore/should_compile/Makefile index 33322f3..fa1c796 100644 --- a/testsuite/tests/simplCore/should_compile/Makefile +++ b/testsuite/tests/simplCore/should_compile/Makefile @@ -237,3 +237,6 @@ T14140: $(RM) -f T14140.o T14140.hi -'$(TEST_HC)' $(TEST_HC_OPTS) -O -c -ddump-simpl T14140.hs | grep '[2-9]# *->' # Expecting no output from the grep, hence "-" + +T14684: + '$(TEST_HC)' $(TEST_HC_OPTS) -c -O -ddump-simpl -dsuppress-uniques T14684.hs | grep -B1 -A4 "__DEFAULT -> 2#" diff --git a/testsuite/tests/simplCore/should_compile/T14684.hs b/testsuite/tests/simplCore/should_compile/T14684.hs new file mode 100644 index 0000000..30671eb --- /dev/null +++ b/testsuite/tests/simplCore/should_compile/T14684.hs @@ -0,0 +1,18 @@ +-- This is a test for the combine-identical-alternatives optimisation. +-- The alternatives with the most common RHS are combined into +-- a single DEFAULT alternative. + + +module T14684 where + +data Foo = Foo1 | Foo2 | Foo3 !Int | Foo4 | Foo5 | Foo6 + +fun1 :: Foo -> Int +{-# NOINLINE fun1 #-} +fun1 x = case x of + Foo1 -> 0 + Foo2 -> 1 + Foo3 {} -> 2 + Foo4 -> 1 + Foo5 -> 2 + Foo6 -> 2 diff --git a/testsuite/tests/simplCore/should_compile/T14684.stdout b/testsuite/tests/simplCore/should_compile/T14684.stdout new file mode 100644 index 0000000..7138806 --- /dev/null +++ b/testsuite/tests/simplCore/should_compile/T14684.stdout @@ -0,0 +1,6 @@ + case w of { + __DEFAULT -> 2#; + Foo1 -> 0#; + Foo2 -> 1#; + Foo4 -> 1# + } diff --git a/testsuite/tests/simplCore/should_compile/all.T b/testsuite/tests/simplCore/should_compile/all.T index e681ca7..e6c0957 100644 --- a/testsuite/tests/simplCore/should_compile/all.T +++ b/testsuite/tests/simplCore/should_compile/all.T @@ -290,3 +290,7 @@ test('T14152a', [extra_files(['T14152.hs']), pre_cmd('cp T14152.hs T14152a.hs'), compile, ['-fno-exitification -ddump-simpl']) test('T13990', normal, compile, ['-dcore-lint -O']) test('T14650', normal, compile, ['-O2']) +test('T14684', + normal, + run_command, + ['$MAKE -s --no-print-directory T14684']) From git at git.haskell.org Tue Feb 20 04:53:35 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 20 Feb 2018 04:53:35 +0000 (UTC) Subject: [commit: ghc] master: Document missing dataToTag# . tagToEnum# rule (517c194) Message-ID: <20180220045335.204B23A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/517c194095064c123b18b779c96c0866e0b3a6d9/ghc >--------------------------------------------------------------- commit 517c194095064c123b18b779c96c0866e0b3a6d9 Author: David Feuer Date: Mon Feb 19 23:48:22 2018 -0500 Document missing dataToTag# . tagToEnum# rule Explain why we don't have a rule to optimize `dataToTag# (tagToEnum# x)` to `x`. [skip ci] Reviewers: bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14282 Differential Revision: https://phabricator.haskell.org/D4375 >--------------------------------------------------------------- 517c194095064c123b18b779c96c0866e0b3a6d9 compiler/prelude/PrelRules.hs | 13 +++++++++++++ 1 file changed, 13 insertions(+) diff --git a/compiler/prelude/PrelRules.hs b/compiler/prelude/PrelRules.hs index c9a3bc7..73484b7 100644 --- a/compiler/prelude/PrelRules.hs +++ b/compiler/prelude/PrelRules.hs @@ -909,6 +909,19 @@ dataToTagRule = a `mplus` b guard $ ty1 `eqType` ty2 return tag + -- Why don't we simplify tagToEnum# (dataToTag# x) to x? We would + -- like to, but it seems tricky. See #14282. The trouble is that + -- we never actually see tagToEnum# (dataToTag# x). Because dataToTag# + -- is can_fail, this expression is immediately transformed into + -- + -- case dataToTag# @T x of wild + -- { __DEFAULT -> tagToEnum# @T wild } + -- + -- and wild has no unfolding. Simon Peyton Jones speculates one way around + -- might be to arrange to give unfoldings to case binders of CONLIKE + -- applications and mark dataToTag# CONLIKE, but he doubts it's really + -- worth the trouble. + -- dataToTag (K e1 e2) ==> tag-of K -- This also works (via exprIsConApp_maybe) for -- dataToTag x From git at git.haskell.org Tue Feb 20 05:27:36 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 20 Feb 2018 05:27:36 +0000 (UTC) Subject: [commit: ghc] master: circleci: Skip performance tests (81a5e05) Message-ID: <20180220052736.807683A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/81a5e05d376c075a38e55bc124ea6226c1f3bef7/ghc >--------------------------------------------------------------- commit 81a5e05d376c075a38e55bc124ea6226c1f3bef7 Author: Ben Gamari Date: Tue Feb 20 00:26:45 2018 -0500 circleci: Skip performance tests Once we finally get the automation for #12758 we can re-enable these. >--------------------------------------------------------------- 81a5e05d376c075a38e55bc124ea6226c1f3bef7 .circleci/config.yml | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/.circleci/config.yml b/.circleci/config.yml index 3e5a77f..e4f09a3 100644 --- a/.circleci/config.yml +++ b/.circleci/config.yml @@ -68,11 +68,11 @@ aliases: - &test run: name: Test - command: make test + command: make test SKIP_PERF_TESTS=YES - &slowtest run: name: Full Test - command: make slowtest + command: make slowtest SKIP_PERF_TESTS=YES - &bindist run: name: Create bindist From git at git.haskell.org Tue Feb 20 18:00:13 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 20 Feb 2018 18:00:13 +0000 (UTC) Subject: [commit: ghc] master: Add ghc-prim.buildinfo to .gitignore (f511bb5) Message-ID: <20180220180013.28B1E3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f511bb58129f0446d9e74b10b22a127803f7eaf1/ghc >--------------------------------------------------------------- commit f511bb58129f0446d9e74b10b22a127803f7eaf1 Author: Ryan Scott Date: Tue Feb 20 12:49:19 2018 -0500 Add ghc-prim.buildinfo to .gitignore >--------------------------------------------------------------- f511bb58129f0446d9e74b10b22a127803f7eaf1 libraries/ghc-prim/.gitignore | 1 + 1 file changed, 1 insertion(+) diff --git a/libraries/ghc-prim/.gitignore b/libraries/ghc-prim/.gitignore index 9ae69e6..1186a2b 100644 --- a/libraries/ghc-prim/.gitignore +++ b/libraries/ghc-prim/.gitignore @@ -1,4 +1,5 @@ /dist/ /dist-install/ /ghc.mk +/ghc-prim.buildinfo /GNUmakefile From git at git.haskell.org Tue Feb 20 18:00:16 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 20 Feb 2018 18:00:16 +0000 (UTC) Subject: [commit: ghc] master: Slight refactor of stock deriving internals (f433659) Message-ID: <20180220180016.0B1EB3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f4336593a390e6317ac2852d8defb54bfa633d3e/ghc >--------------------------------------------------------------- commit f4336593a390e6317ac2852d8defb54bfa633d3e Author: Ryan Scott Date: Tue Feb 20 12:50:34 2018 -0500 Slight refactor of stock deriving internals Summary: Before, the `hasStockDeriving` function, which determines how derived bindings should be generated for stock classes, was awkwardly separated from the `checkSideConditions` function, which checks invariants of the same classes that `hasStockDeriving` does. As a result, there was a fair deal of hoopla needed to actually use `hasStockDeriving`. But this hoopla really isn't required—we should be using `hasStockDeriving` from within `checkSideConditions`, since they're looking up information about the same classes! By doing this, we can eliminate some kludgy code in the form of `mk_eqn_stock'`, which had an unreachable `pprPanic` that was stinking up the place. Reviewers: bgamari, dfeuer Reviewed By: bgamari Subscribers: dfeuer, rwbarton, thomie, carter GHC Trac Issues: #13154 Differential Revision: https://phabricator.haskell.org/D4370 >--------------------------------------------------------------- f4336593a390e6317ac2852d8defb54bfa633d3e compiler/typecheck/TcDeriv.hs | 16 +++------------- compiler/typecheck/TcDerivUtils.hs | 10 ++++++---- 2 files changed, 9 insertions(+), 17 deletions(-) diff --git a/compiler/typecheck/TcDeriv.hs b/compiler/typecheck/TcDeriv.hs index b78cba7..294b42c 100644 --- a/compiler/typecheck/TcDeriv.hs +++ b/compiler/typecheck/TcDeriv.hs @@ -1103,20 +1103,10 @@ mk_eqn_stock go_for_it bale_out , denv_mtheta = mtheta } <- ask dflags <- getDynFlags case checkSideConditions dflags mtheta cls cls_tys tc rep_tc of - CanDerive -> mk_eqn_stock' go_for_it + CanDerive gen_fn -> go_for_it $ DerivSpecStock gen_fn DerivableClassError msg -> bale_out msg _ -> bale_out (nonStdErr cls) -mk_eqn_stock' :: (DerivSpecMechanism -> DerivM EarlyDerivSpec) - -> DerivM EarlyDerivSpec -mk_eqn_stock' go_for_it - = do cls <- asks denv_cls - go_for_it $ - case hasStockDeriving cls of - Just gen_fn -> DerivSpecStock gen_fn - Nothing -> - pprPanic "mk_eqn_stock': Not a stock class!" (ppr cls) - mk_eqn_anyclass :: (DerivSpecMechanism -> DerivM EarlyDerivSpec) -> (SDoc -> DerivM EarlyDerivSpec) -> DerivM EarlyDerivSpec @@ -1150,7 +1140,7 @@ mk_eqn_no_mechanism go_for_it bale_out -- NB: pass the *representation* tycon to checkSideConditions NonDerivableClass msg -> bale_out (dac_error msg) DerivableClassError msg -> bale_out msg - CanDerive -> mk_eqn_stock' go_for_it + CanDerive gen_fn -> go_for_it $ DerivSpecStock gen_fn DerivableViaInstance -> go_for_it DerivSpecAnyClass {- @@ -1420,7 +1410,7 @@ mkNewTypeEqn <+> text "for instantiating" <+> ppr cls ] mk_data_eqn DerivSpecAnyClass -- CanDerive - CanDerive -> mk_eqn_stock' mk_data_eqn + CanDerive gen_fn -> mk_data_eqn $ DerivSpecStock gen_fn {- Note [Recursive newtypes] diff --git a/compiler/typecheck/TcDerivUtils.hs b/compiler/typecheck/TcDerivUtils.hs index eae2fa5..c9804ba 100644 --- a/compiler/typecheck/TcDerivUtils.hs +++ b/compiler/typecheck/TcDerivUtils.hs @@ -10,9 +10,8 @@ Error-checking and other utilities for @deriving@ clauses or declarations. module TcDerivUtils ( DerivM, DerivEnv(..), - DerivSpec(..), pprDerivSpec, - DerivSpecMechanism(..), isDerivSpecStock, - isDerivSpecNewtype, isDerivSpecAnyClass, + DerivSpec(..), pprDerivSpec, DerivSpecMechanism(..), + isDerivSpecStock, isDerivSpecNewtype, isDerivSpecAnyClass, DerivContext, DerivStatus(..), PredOrigin(..), ThetaOrigin(..), mkPredOrigin, mkThetaOrigin, mkThetaOriginFromPreds, substPredOrigin, @@ -215,6 +214,8 @@ type DerivContext = Maybe ThetaType -- Just theta <=> Standalone deriving: context supplied by programmer data DerivStatus = CanDerive -- Stock class, can derive + (SrcSpan -> TyCon -> [Type] + -> TcM (LHsBinds GhcPs, BagDerivStuff, [Name])) | DerivableClassError SDoc -- Stock class, but can't do it | DerivableViaInstance -- See Note [Deriving any class] | NonDerivableClass SDoc -- Non-stock class @@ -425,12 +426,13 @@ checkSideConditions dflags mtheta cls cls_tys tc rep_tc = case (cond dflags tc rep_tc) of NotValid err -> DerivableClassError err -- Class-specific error IsValid | null (filterOutInvisibleTypes (classTyCon cls) cls_tys) - -> CanDerive -- All stock derivable classes are unary in the sense that -- there should be not types in cls_tys (i.e., no type args -- other than last). Note that cls_types can contain -- invisible types as well (e.g., for Generic1, which is -- poly-kinded), so make sure those are not counted. + , Just gen_fn <- hasStockDeriving cls + -> CanDerive gen_fn | otherwise -> DerivableClassError (classArgsErr cls cls_tys) -- e.g. deriving( Eq s ) From git at git.haskell.org Tue Feb 20 18:16:05 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 20 Feb 2018 18:16:05 +0000 (UTC) Subject: [commit: ghc] master: Revert "Move `iserv` into `utils` and change package name (abfe104) Message-ID: <20180220181605.717D63A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/abfe10487d2dba49bf511297f14575f9089cc5b1/ghc >--------------------------------------------------------------- commit abfe10487d2dba49bf511297f14575f9089cc5b1 Author: Ben Gamari Date: Tue Feb 20 00:26:45 2018 -0500 Revert "Move `iserv` into `utils` and change package name See Phab:D4377 for the rationale. We will try this again. This reverts commit 7c173b9043f7a9a5da46c5b0cc5fc3b38d1a7019. >--------------------------------------------------------------- abfe10487d2dba49bf511297f14575f9089cc5b1 .gitignore | 3 +- ghc.mk | 13 +- {libraries/libiserv => iserv}/Makefile | 0 {libraries/libiserv => iserv}/cbits/iservmain.c | 0 {utils/iserv => iserv}/ghc.mk | 66 +++--- .../iserv-proxy.cabal => iserv/iserv-bin.cabal | 72 +++++- {libraries/libiserv => iserv}/proxy-src/Remote.hs | 0 {libraries/libiserv => iserv}/src/GHCi/Utils.hsc | 0 {libraries/libiserv => iserv}/src/Lib.hs | 0 {libraries/libiserv => iserv}/src/Main.hs | 0 .../libiserv => iserv}/src/Remote/Message.hs | 0 {libraries/libiserv => iserv}/src/Remote/Slave.hs | 0 libraries/libiserv/ghc.mk | 5 - libraries/libiserv/libiserv.cabal | 39 --- utils/iserv-proxy/Makefile | 15 -- utils/iserv-proxy/ghc.mk | 113 --------- utils/iserv-proxy/src/Main.hs | 262 --------------------- utils/iserv/Makefile | 15 -- utils/iserv/cbits/iservmain.c | 17 -- utils/iserv/iserv.cabal | 44 ---- utils/iserv/src/Main.hs | 63 ----- 21 files changed, 108 insertions(+), 619 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc abfe10487d2dba49bf511297f14575f9089cc5b1 From git at git.haskell.org Wed Feb 21 00:04:29 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Feb 2018 00:04:29 +0000 (UTC) Subject: [commit: ghc] wip/T2893: Generalise quantified constraints (c477f53) Message-ID: <20180221000429.BFDFF3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T2893 Link : http://ghc.haskell.org/trac/ghc/changeset/c477f53799deb46b4987ac788ad67d1bcbb8eb0c/ghc >--------------------------------------------------------------- commit c477f53799deb46b4987ac788ad67d1bcbb8eb0c Author: Simon Peyton Jones Date: Wed Feb 21 00:00:35 2018 +0000 Generalise quantified constraints This patch fixes Trac #14733, by generalising quantified consrtraints to allow type variables in the head, thus f :: forall m a. (forall b. m b) => D (m a) Notice the 'm' in the head of the quantified constraint, not a class. This entailed some re-engineering, but it's nice. >--------------------------------------------------------------- c477f53799deb46b4987ac788ad67d1bcbb8eb0c compiler/typecheck/TcCanonical.hs | 45 +++--- compiler/typecheck/TcInteract.hs | 305 +++++++++++++++++++++++--------------- compiler/typecheck/TcSMonad.hs | 160 ++++++++++---------- compiler/typecheck/TcValidity.hs | 50 +++---- compiler/types/Type.hs | 7 +- 5 files changed, 315 insertions(+), 252 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c477f53799deb46b4987ac788ad67d1bcbb8eb0c From git at git.haskell.org Wed Feb 21 02:27:06 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Feb 2018 02:27:06 +0000 (UTC) Subject: [commit: ghc] branch 'wip/docker-ghcci' created Message-ID: <20180221022706.DC84C3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/docker-ghcci Referencing: 698678c2c14e4706343e52911d918a7adf718727 From git at git.haskell.org Wed Feb 21 02:27:09 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Feb 2018 02:27:09 +0000 (UTC) Subject: [commit: ghc] wip/docker-ghcci: circleci: Use Docker images from ghcci (698678c) Message-ID: <20180221022709.A4BC93A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/docker-ghcci Link : http://ghc.haskell.org/trac/ghc/changeset/698678c2c14e4706343e52911d918a7adf718727/ghc >--------------------------------------------------------------- commit 698678c2c14e4706343e52911d918a7adf718727 Author: Ben Gamari Date: Tue Feb 20 21:24:14 2018 -0500 circleci: Use Docker images from ghcci Summary: The new Docker images create an unprivileged user to run the testsuite under. Not only does this seem far more sane from a security standpoint, but it avoids the spurious test failure noted in #14706. Test Plan: Test on CircleCI Subscribers: dfeuer, rwbarton, thomie, carter GHC Trac Issues: #14706 Differential Revision: https://phabricator.haskell.org/D4360 >--------------------------------------------------------------- 698678c2c14e4706343e52911d918a7adf718727 .circleci/config.yml | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/.circleci/config.yml b/.circleci/config.yml index 80bccd7..1a542b1 100644 --- a/.circleci/config.yml +++ b/.circleci/config.yml @@ -98,7 +98,7 @@ jobs: "validate-x86_64-linux": resource_class: xlarge docker: - - image: haskell:8.2 + - image: ghcci:x86_64-linux environment: <<: *buildenv steps: @@ -117,7 +117,7 @@ jobs: "validate-x86_64-freebsd": resource_class: xlarge docker: - - image: tweag/toolchain-x86_64-freebsd + - image: ghcci:x86_64-freebsd environment: TARGET: FreeBSD <<: *buildenv @@ -158,7 +158,7 @@ jobs: "validate-hadrian-x86_64-linux": resource_class: xlarge docker: - - image: haskell:8.2 + - image: ghcci:x86_64-linux environment: <<: *buildenv steps: @@ -174,7 +174,7 @@ jobs: "validate-x86_64-linux-unreg": resource_class: xlarge docker: - - image: haskell:8.2 + - image: ghcci:x86_64-linux environment: <<: *buildenv steps: @@ -190,7 +190,7 @@ jobs: "validate-x86_64-linux-llvm": resource_class: xlarge docker: - - image: haskell:8.2 + - image: ghcci:x86_64-linux environment: <<: *buildenv BUILD_FLAVOUR: perf-llvm From git at git.haskell.org Wed Feb 21 03:30:02 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Feb 2018 03:30:02 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: Bump hadrian submodule (99d3e39) Message-ID: <20180221033002.997A23A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/99d3e39f1d82f332351cbae602f460b42f7d62fe/ghc >--------------------------------------------------------------- commit 99d3e39f1d82f332351cbae602f460b42f7d62fe Author: Ryan Scott Date: Fri Feb 16 13:51:27 2018 -0500 Bump hadrian submodule >--------------------------------------------------------------- 99d3e39f1d82f332351cbae602f460b42f7d62fe hadrian | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/hadrian b/hadrian index 86216e2..63a5563 160000 --- a/hadrian +++ b/hadrian @@ -1 +1 @@ -Subproject commit 86216e249f307a778bef3755afb7474910bc60cc +Subproject commit 63a556382f4b3154ed2ce3a6c8a36f79d9b8e3b1 From git at git.haskell.org Wed Feb 21 03:30:05 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Feb 2018 03:30:05 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: Improve unboxed sum documentation (792834b) Message-ID: <20180221033005.6E5883A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/792834bcd4b3417af61211b1b44358a42fd18bb1/ghc >--------------------------------------------------------------- commit 792834bcd4b3417af61211b1b44358a42fd18bb1 Author: David Feuer Date: Mon Feb 5 09:45:30 2018 -0500 Improve unboxed sum documentation * Clarify the representation of sums without fields. * Try to improve language, clarity, and examples. Fixes #14752 Reviewers: osa1, bgamari Reviewed By: osa1 Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14752 Differential Revision: https://phabricator.haskell.org/D4379 (cherry picked from commit d987f71aa3200ce0c94bc57c43b4fcc92eaccf76) >--------------------------------------------------------------- 792834bcd4b3417af61211b1b44358a42fd18bb1 docs/users_guide/glasgow_exts.rst | 67 +++++++++++++++++++++++---------------- 1 file changed, 39 insertions(+), 28 deletions(-) diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index 6bca784..d2086f6 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -284,21 +284,21 @@ for an unboxed sum type with N alternatives is :: (# t_1 | t_2 | ... | t_N #) -where `t_1` ... `t_N` are types (which can be unlifted, including unboxed tuple -and sums). +where ``t_1`` ... ``t_N`` are types (which can be unlifted, including unboxed +tuples and sums). Unboxed tuples can be used for multi-arity alternatives. For example: :: (# (# Int, String #) | Bool #) -Term level syntax is similar. Leading and preceding bars (`|`) indicate which -alternative it is. Here is two terms of the type shown above: :: +The term level syntax is similar. Leading and preceding bars (`|`) indicate which +alternative it is. Here are two terms of the type shown above: :: (# (# 1, "foo" #) | #) -- first alternative (# | True #) -- second alternative -Pattern syntax reflects the term syntax: :: +The pattern syntax reflects the term syntax: :: case x of (# (# i, str #) | #) -> ... @@ -307,45 +307,56 @@ Pattern syntax reflects the term syntax: :: Unboxed sums are "unboxed" in the sense that, instead of allocating sums in the heap and representing values as pointers, unboxed sums are represented as their components, just like unboxed tuples. These "components" depend on alternatives -of a sum type. Code generator tries to generate as compact layout as possible. -In the best case, size of an unboxed sum is size of its biggest alternative + -one word (for tag). The algorithm for generating memory layout for a sum type -works like this: +of a sum type. Like unboxed tuples, unboxed sums are lazy in their lifted +components. + +The code generator tries to generate as compact layout as possible for each +unboxed sum. In the best case, size of an unboxed sum is size of its biggest +alternative plus one word (for a tag). The algorithm for generating the memory +layout for a sum type works like this: - All types are classified as one of these classes: 32bit word, 64bit word, 32bit float, 64bit float, pointer. - For each alternative of the sum type, a layout that consists of these fields - is generated. For example, if an alternative has `Int`, `Float#` and `String` - fields, the layout will have an 32bit word, 32bit float and pointer fields. + is generated. For example, if an alternative has ``Int``, ``Float#`` and + ``String`` fields, the layout will have an 32bit word, 32bit float and + pointer fields. - Layout fields are then overlapped so that the final layout will be as compact - as possible. E.g. say two alternatives have these fields: :: + as possible. For example, suppose we have the unboxed sum: :: - Word32, String, Float# - Float#, Float#, Maybe Int + (# (# Word32#, String, Float# #) + | (# Float#, Float#, Maybe Int #) #) - Final layout will be something like :: + The final layout will be something like :: Int32, Float32, Float32, Word32, Pointer - First `Int32` is for the tag. It has two `Float32` fields because floating - point types can't overlap with other types, because of limitations of the code - generator that we're hoping to overcome in the future, and second alternative - needs two `Float32` fields. `Word32` field is for the `Word32` in the first - alternative. `Pointer` field is shared between `String` and `Maybe Int` values - of the alternatives. - - In the case of enumeration types (like `Bool`), the unboxed sum layout only - has an `Int32` field (i.e. the whole thing is represented by an integer). + The first ``Int32`` is for the tag. There are two ``Float32`` fields because + floating point types can't overlap with other types, because of limitations of + the code generator that we're hoping to overcome in the future. The second + alternative needs two ``Float32`` fields: The ``Word32`` field is for the + ``Word32#`` in the first alternative. The ``Pointer`` field is shared between + ``String`` and ``Maybe Int`` values of the alternatives. -In the example above, a value of this type is thus represented as 5 values. As -an another example, this is the layout for unboxed version of `Maybe a` type: :: + As another example, this is the layout for the unboxed version of ``Maybe a`` + type, ``(# (# #) | a #)``: :: Int32, Pointer -The `Pointer` field is not used when tag says that it's `Nothing`. Otherwise -`Pointer` points to the value in `Just`. + The ``Pointer`` field is not used when tag says that it's ``Nothing``. + Otherwise ``Pointer`` points to the value in ``Just``. As mentioned + above, this type is lazy in its lifted field. Therefore, the type :: + + data Maybe' a = Maybe' (# (# #) | a #) + + is *precisely* isomorphic to the type ``Maybe a``, although its memory + representation is different. + + In the degenerate case where all the alternatives have zero width, such + as the ``Bool``-like ``(# (# #) | (# #) #)``, the unboxed sum layout only + has an ``Int32`` tag field (i.e., the whole thing is represented by an integer). .. _syntax-extns: From git at git.haskell.org Wed Feb 21 05:04:01 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Feb 2018 05:04:01 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T14068-inline' created Message-ID: <20180221050401.9DC1F3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T14068-inline Referencing: 20b00bd9fcb5e0e5b115f0796f2b59005856234d From git at git.haskell.org Wed Feb 21 05:04:04 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Feb 2018 05:04:04 +0000 (UTC) Subject: [commit: ghc] wip/T14068-inline: Revert "Prevent inlining of loopified programs" (20b00bd) Message-ID: <20180221050404.7E9743A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T14068-inline Link : http://ghc.haskell.org/trac/ghc/changeset/20b00bd9fcb5e0e5b115f0796f2b59005856234d/ghc >--------------------------------------------------------------- commit 20b00bd9fcb5e0e5b115f0796f2b59005856234d Author: Joachim Breitner Date: Wed Feb 21 00:03:27 2018 -0500 Revert "Prevent inlining of loopified programs" This reverts commit b4ab3a5f1fa051be9c5689f7ecef16458b2d700d, to get new measurements on how loopification fares with inlining enabled. >--------------------------------------------------------------- 20b00bd9fcb5e0e5b115f0796f2b59005856234d compiler/coreSyn/CoreOpt.hs | 8 +------- compiler/stranal/WorkWrap.hs | 1 - 2 files changed, 1 insertion(+), 8 deletions(-) diff --git a/compiler/coreSyn/CoreOpt.hs b/compiler/coreSyn/CoreOpt.hs index d97a015..57812e4 100644 --- a/compiler/coreSyn/CoreOpt.hs +++ b/compiler/coreSyn/CoreOpt.hs @@ -675,14 +675,8 @@ loopificationJoinPointBinding_maybe bndr rhs zapFragileIdInfo $ localiseId $ bndr - -- RULES etc stay with bindr' - -- Also, previously, the function was recursive, and hence not inlineable. - -- To tread with caution, let's keep it this way - bndr' = (`setIdUnfolding` noUnfolding) $ - (`setInlinePragma` neverInlinePragma) $ - (`setIdOccInfo` noOccInfo) $ - bndr + bndr' = zapIdTailCallInfo bndr in Just (bndr', join_bndr, mkLams bndrs body) | otherwise diff --git a/compiler/stranal/WorkWrap.hs b/compiler/stranal/WorkWrap.hs index 4eb2f10..ac8798e 100644 --- a/compiler/stranal/WorkWrap.hs +++ b/compiler/stranal/WorkWrap.hs @@ -479,7 +479,6 @@ splitFun dflags fam_envs fn_id fn_info wrap_dmds res_info rhs work_act = case work_inline of -- See Note [Activation for workers] NoInline -> inl_act inl_prag - NoUserInline | isNeverActive (inl_act inl_prag) -> NeverActive _ -> wrap_act work_prag = InlinePragma { inl_src = SourceText "{-# INLINE" , inl_inline = work_inline From git at git.haskell.org Wed Feb 21 06:48:00 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Feb 2018 06:48:00 +0000 (UTC) Subject: [commit: ghc] master: Add references to #6087 (a032ff7) Message-ID: <20180221064800.2FFA03A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a032ff77210736df45cf49820c882f40dc10230e/ghc >--------------------------------------------------------------- commit a032ff77210736df45cf49820c882f40dc10230e Author: Ömer Sinan Ağacan Date: Wed Feb 21 09:47:13 2018 +0300 Add references to #6087 [skip ci] >--------------------------------------------------------------- a032ff77210736df45cf49820c882f40dc10230e compiler/main/DynFlags.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index e6b9cf6..01432b6 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -441,7 +441,7 @@ data GeneralFlag | Opt_CallArity | Opt_Exitification | Opt_Strictness - | Opt_LateDmdAnal + | Opt_LateDmdAnal -- #6087 | Opt_KillAbsence | Opt_KillOneShot | Opt_FullLaziness @@ -4304,6 +4304,8 @@ impliedXFlags -- available flags. The second contains a detailed description of the -- flags. Both places should contain information whether a flag is implied by -- -O0, -O or -O2. +-- +-- (See #6087 about adding -flate-dmd-anal in this list) optLevelFlags :: [([Int], GeneralFlag)] optLevelFlags -- see Note [Documenting optimisation flags] From git at git.haskell.org Wed Feb 21 06:50:13 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Feb 2018 06:50:13 +0000 (UTC) Subject: [commit: ghc] branch 'wip/cheap-build-osa1' created Message-ID: <20180221065013.DEBB93A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/cheap-build-osa1 Referencing: 75ad6a28d80f441f05a73b002f57e844cc1464b9 From git at git.haskell.org Wed Feb 21 06:50:16 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Feb 2018 06:50:16 +0000 (UTC) Subject: [commit: ghc] wip/cheap-build-osa1: Implement cheapBuild (7a87c59) Message-ID: <20180221065016.BB8AA3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/cheap-build-osa1 Link : http://ghc.haskell.org/trac/ghc/changeset/7a87c59c2f00248e0368999f5cd23877a04c2e28/ghc >--------------------------------------------------------------- commit 7a87c59c2f00248e0368999f5cd23877a04c2e28 Author: David Feuer Date: Mon Jan 30 21:38:12 2017 -0500 Implement cheapBuild Summary: Ben Gamari's `cheapBuild` patch with some extras Use cheapBuild for enumerating Chars Use cheapBuild for enumerating Ints Add cheapBuild rules for other consumers `GHC.List` fuses a number of functions other than `foldr` with `build`. Make those fuse with `cheapBuild` too. Reviewers: austin, hvr, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D3047 >--------------------------------------------------------------- 7a87c59c2f00248e0368999f5cd23877a04c2e28 libraries/base/GHC/List.hs | 16 ++++++++++++++++ 1 file changed, 16 insertions(+) diff --git a/libraries/base/GHC/List.hs b/libraries/base/GHC/List.hs index af50213..e177e07 100644 --- a/libraries/base/GHC/List.hs +++ b/libraries/base/GHC/List.hs @@ -59,6 +59,8 @@ badHead = errorEmptyList "head" {-# RULES "head/build" forall (g::forall b.(a->b->b)->b->b) . head (build g) = g (\x _ -> x) badHead +"head/cheapBuild" forall (g::forall b.(a->b->b)->b->b) . + head (cheapBuild g) = g (\x _ -> x) badHead "head/augment" forall xs (g::forall b. (a->b->b) -> b -> b) . head (augment g xs) = g (\x _ -> x) (head xs) #-} @@ -756,6 +758,8 @@ and (x:xs) = x && and xs {-# RULES "and/build" forall (g::forall b.(Bool->b->b)->b->b) . and (build g) = g (&&) True +"and/cheapBuild" forall (g::forall b.(Bool->b->b)->b->b) . + and (cheapBuild g) = g (&&) True #-} #endif @@ -773,6 +777,8 @@ or (x:xs) = x || or xs {-# RULES "or/build" forall (g::forall b.(Bool->b->b)->b->b) . or (build g) = g (||) False +"or/cheapBuild" forall (g::forall b.(Bool->b->b)->b->b) . + or (cheapBuild g) = g (||) False #-} #endif @@ -793,6 +799,8 @@ any p (x:xs) = p x || any p xs {-# RULES "any/build" forall p (g::forall b.(a->b->b)->b->b) . any p (build g) = g ((||) . p) False +"any/cheapBuild" forall p (g::forall b.(a->b->b)->b->b) . + any p (cheapBuild g) = g ((||) . p) False #-} #endif @@ -812,6 +820,8 @@ all p (x:xs) = p x && all p xs {-# RULES "all/build" forall p (g::forall b.(a->b->b)->b->b) . all p (build g) = g ((&&) . p) True +"all/cheapBuild" forall p (g::forall b.(a->b->b)->b->b) . + all p (cheapBuild g) = g ((&&) . p) True #-} #endif @@ -829,6 +839,8 @@ elem x (y:ys) = x==y || elem x ys {-# RULES "elem/build" forall x (g :: forall b . Eq a => (a -> b -> b) -> b -> b) . elem x (build g) = g (\ y r -> (x == y) || r) False +"elem/cheapBuild" forall x (g :: forall b . Eq a => (a -> b -> b) -> b -> b) + . elem x (cheapBuild g) = g (\ y r -> (x == y) || r) False #-} #endif @@ -843,6 +855,8 @@ notElem x (y:ys)= x /= y && notElem x ys {-# RULES "notElem/build" forall x (g :: forall b . Eq a => (a -> b -> b) -> b -> b) . notElem x (build g) = g (\ y r -> (x /= y) && r) True +"notElem/cheapBuild" forall x (g :: forall b . Eq a => (a -> b -> b) -> b -> b) + . notElem x (cheapBuild g) = g (\ y r -> (x /= y) && r) True #-} #endif @@ -926,6 +940,8 @@ foldr2_left k _z x r (y:ys) = k x y (r ys) {-# RULES "foldr2/left" forall k z ys (g::forall b.(a->b->b)->b->b) . foldr2 k z (build g) ys = g (foldr2_left k z) (\_ -> z) ys +"foldr2/cheapleft" forall k z ys (g::forall b.(a->b->b)->b->b) . + foldr2 k z (cheapBuild g) ys = g (foldr2_left k z) (\_ -> z) ys #-} -- There used to be a foldr2/right rule, allowing foldr2 to fuse with a build -- form on the right. However, this causes trouble if the right list ends in From git at git.haskell.org Wed Feb 21 06:50:19 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Feb 2018 06:50:19 +0000 (UTC) Subject: [commit: ghc] wip/cheap-build-osa1: Implement cheapBuild (8dd6a97) Message-ID: <20180221065019.8AF473A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/cheap-build-osa1 Link : http://ghc.haskell.org/trac/ghc/changeset/8dd6a971d6785b09ac4da2505ee918a2aa20f0bd/ghc >--------------------------------------------------------------- commit 8dd6a971d6785b09ac4da2505ee918a2aa20f0bd Author: Ben Gamari Date: Tue Aug 4 09:07:11 2015 +0200 Implement cheapBuild >--------------------------------------------------------------- 8dd6a971d6785b09ac4da2505ee918a2aa20f0bd compiler/coreSyn/CoreUnfold.hs | 5 +++-- compiler/prelude/PrelNames.hs | 9 +++++--- libraries/base/GHC/Base.hs | 48 ++++++++++++++++++++++++++++++++++++------ 3 files changed, 50 insertions(+), 12 deletions(-) diff --git a/compiler/coreSyn/CoreUnfold.hs b/compiler/coreSyn/CoreUnfold.hs index 2e2b7a3..115d635 100644 --- a/compiler/coreSyn/CoreUnfold.hs +++ b/compiler/coreSyn/CoreUnfold.hs @@ -748,8 +748,9 @@ funSize :: DynFlags -> [Id] -> Id -> Int -> Int -> ExprSize -- Size for functions that are not constructors or primops -- Note [Function applications] funSize dflags top_args fun n_val_args voids - | fun `hasKey` buildIdKey = buildSize - | fun `hasKey` augmentIdKey = augmentSize + | fun `hasKey` buildIdKey = buildSize + | fun `hasKey` cheapBuildIdKey = buildSize + | fun `hasKey` augmentIdKey = augmentSize | otherwise = SizeIs size arg_discount res_discount where some_val_args = n_val_args > 0 diff --git a/compiler/prelude/PrelNames.hs b/compiler/prelude/PrelNames.hs index df13eaa..f6cff88 100644 --- a/compiler/prelude/PrelNames.hs +++ b/compiler/prelude/PrelNames.hs @@ -322,7 +322,7 @@ basicKnownKeyNames -- List operations concatName, filterName, mapName, - zipName, foldrName, buildName, augmentName, appendName, + zipName, foldrName, buildName, cheapBuildName, augmentName, appendName, -- FFI primitive types that are not wired-in. stablePtrTyConName, ptrTyConName, funPtrTyConName, @@ -1059,7 +1059,8 @@ groupWithName :: Name groupWithName = varQual gHC_EXTS (fsLit "groupWith") groupWithIdKey -- Random PrelBase functions -fromStringName, otherwiseIdName, foldrName, buildName, augmentName, +fromStringName, otherwiseIdName, foldrName, + buildName, cheapBuildName, augmentName, mapName, appendName, assertName, breakpointName, breakpointCondName, breakpointAutoName, opaqueTyConName, dollarName :: Name @@ -1067,6 +1068,7 @@ dollarName = varQual gHC_BASE (fsLit "$") dollarIdKey otherwiseIdName = varQual gHC_BASE (fsLit "otherwise") otherwiseIdKey foldrName = varQual gHC_BASE (fsLit "foldr") foldrIdKey buildName = varQual gHC_BASE (fsLit "build") buildIdKey +cheapBuildName = varQual gHC_BASE (fsLit "cheapBuild") cheapBuildIdKey augmentName = varQual gHC_BASE (fsLit "augment") augmentIdKey mapName = varQual gHC_BASE (fsLit "map") mapIdKey appendName = varQual gHC_BASE (fsLit "++") appendIdKey @@ -2072,7 +2074,7 @@ typeLitNatDataConKey = mkPreludeDataConUnique 108 -} wildCardKey, absentErrorIdKey, augmentIdKey, appendIdKey, - buildIdKey, errorIdKey, foldrIdKey, recSelErrorIdKey, + buildIdKey, cheapBuildIdKey, errorIdKey, foldrIdKey, recSelErrorIdKey, seqIdKey, eqStringIdKey, noMethodBindingErrorIdKey, nonExhaustiveGuardsErrorIdKey, runtimeErrorIdKey, patErrorIdKey, voidPrimIdKey, @@ -2105,6 +2107,7 @@ voidPrimIdKey = mkPreludeMiscIdUnique 21 typeErrorIdKey = mkPreludeMiscIdUnique 22 divIntIdKey = mkPreludeMiscIdUnique 23 modIntIdKey = mkPreludeMiscIdUnique 24 +cheapBuildIdKey = mkPreludeMiscIdUnique 25 unsafeCoerceIdKey, concatIdKey, filterIdKey, zipIdKey, bindIOIdKey, returnIOIdKey, newStablePtrIdKey, diff --git a/libraries/base/GHC/Base.hs b/libraries/base/GHC/Base.hs index 17d4151..77662ba 100644 --- a/libraries/base/GHC/Base.hs +++ b/libraries/base/GHC/Base.hs @@ -197,6 +197,7 @@ not True = False otherwise = True build = errorWithoutStackTrace "urk" +cheapBuild = errorWithoutStackTrace "urk" foldr = errorWithoutStackTrace "urk" #endif @@ -1046,6 +1047,13 @@ build :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a] build g = g (:) [] +-- | 'cheapBuild' is just like build, except that the simplifier views +-- it as cheap to construct (similar to to a data constructor). +cheapBuild :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a] +{-# INLINE CONLIKE [1] cheapBuild #-} +cheapBuild g = g (:) [] +-- See Note [cheapBuild] + -- | A list producer that can be fused with 'foldr'. -- This function is merely -- @@ -1060,14 +1068,16 @@ augment :: forall a. (forall b. (a->b->b) -> b -> b) -> [a] -> [a] augment g xs = g (:) xs {-# RULES -"fold/build" forall k z (g::forall b. (a->b->b) -> b -> b) . - foldr k z (build g) = g k z +"fold/build" forall k z (g::forall b. (a->b->b) -> b -> b) . + foldr k z (build g) = g k z +"fold/cheapBuild" forall k z (g::forall b. (a->b->b) -> b -> b) . + foldr k z (cheapBuild g) = g k z -"foldr/augment" forall k z xs (g::forall b. (a->b->b) -> b -> b) . - foldr k z (augment g xs) = g k (foldr k z xs) +"foldr/augment" forall k z xs (g::forall b. (a->b->b) -> b -> b) . + foldr k z (augment g xs) = g k (foldr k z xs) -"foldr/id" foldr (:) [] = \x -> x -"foldr/app" [1] forall ys. foldr (:) ys = \xs -> xs ++ ys +"foldr/id" foldr (:) [] = \x -> x +"foldr/app" [1] forall ys. foldr (:) ys = \xs -> xs ++ ys -- Only activate this from phase 1, because that's -- when we disable the rule that expands (++) into foldr @@ -1084,17 +1094,41 @@ augment g xs = g (:) xs "foldr/cons/build" forall k z x (g::forall b. (a->b->b) -> b -> b) . foldr k z (x:build g) = k x (g k z) +"foldr/cons/cheapBuild" + forall k z x (g::forall b. (a->b->b) -> b -> b) . + foldr k z (x:cheapBuild g) = k x (g k z) "augment/build" forall (g::forall b. (a->b->b) -> b -> b) (h::forall b. (a->b->b) -> b -> b) . augment g (build h) = build (\c n -> g c (h c n)) +"augment/cheapBuild" + forall (g::forall b. (a->b->b) -> b -> b) + (h::forall b. (a->b->b) -> b -> b) . + augment g (cheapBuild h) = cheapBuild (\c n -> g c (h c n)) "augment/nil" forall (g::forall b. (a->b->b) -> b -> b) . - augment g [] = build g + augment g [] = build g #-} -- This rule is true, but not (I think) useful: -- augment g (augment h t) = augment (\cn -> g c (h c n)) t + +{- +Note [cheapBuild] +~~~~~~~~~~~~~~~~~ +cheapBuild is just like build, except that it is CONLIKE +It is used in situations where fusion is more imortant than sharing, +ie in situation where its argument function 'g' in (cheapBuild g) is +cheap. +Main example: enumerations of one kind or another: + f x = let xs = [x..] + go = \y. ....go y'....(map (h y) xs)... + in ... +Here we woud like to fuse the map with the [x..]. + +See Trac #7206. +-} + ---------------------------------------------- -- map ---------------------------------------------- From git at git.haskell.org Wed Feb 21 06:50:25 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Feb 2018 06:50:25 +0000 (UTC) Subject: [commit: ghc] wip/cheap-build-osa1: Use cheapBuild for enumerating Chars (3b255ae) Message-ID: <20180221065025.208B53A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/cheap-build-osa1 Link : http://ghc.haskell.org/trac/ghc/changeset/3b255ae98bf01cbdb0387c6027c1adf338952ccb/ghc >--------------------------------------------------------------- commit 3b255ae98bf01cbdb0387c6027c1adf338952ccb Author: Ben Gamari Date: Tue Aug 4 09:08:39 2015 +0200 Use cheapBuild for enumerating Chars >--------------------------------------------------------------- 3b255ae98bf01cbdb0387c6027c1adf338952ccb libraries/base/GHC/Enum.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/libraries/base/GHC/Enum.hs b/libraries/base/GHC/Enum.hs index feb4585..e2655c9 100644 --- a/libraries/base/GHC/Enum.hs +++ b/libraries/base/GHC/Enum.hs @@ -320,9 +320,9 @@ instance Enum Char where -- See Note [How the Enum rules work] {-# RULES -"eftChar" [~1] forall x y. eftChar x y = build (\c n -> eftCharFB c n x y) -"efdChar" [~1] forall x1 x2. efdChar x1 x2 = build (\ c n -> efdCharFB c n x1 x2) -"efdtChar" [~1] forall x1 x2 l. efdtChar x1 x2 l = build (\ c n -> efdtCharFB c n x1 x2 l) +"eftChar" [~1] forall x y. eftChar x y = cheapBuild (\c n -> eftCharFB c n x y) +"efdChar" [~1] forall x1 x2. efdChar x1 x2 = cheapBuild (\ c n -> efdCharFB c n x1 x2) +"efdtChar" [~1] forall x1 x2 l. efdtChar x1 x2 l = cheapBuild (\ c n -> efdtCharFB c n x1 x2 l) "eftCharList" [1] eftCharFB (:) [] = eftChar "efdCharList" [1] efdCharFB (:) [] = efdChar "efdtCharList" [1] efdtCharFB (:) [] = efdtChar From git at git.haskell.org Wed Feb 21 06:50:27 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Feb 2018 06:50:27 +0000 (UTC) Subject: [commit: ghc] wip/cheap-build-osa1: Use cheapBuild for enumerating Ints (5e6b43c) Message-ID: <20180221065027.DFB273A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/cheap-build-osa1 Link : http://ghc.haskell.org/trac/ghc/changeset/5e6b43c79115a06a49ec3076208138c421177497/ghc >--------------------------------------------------------------- commit 5e6b43c79115a06a49ec3076208138c421177497 Author: Ben Gamari Date: Tue Aug 4 09:09:13 2015 +0200 Use cheapBuild for enumerating Ints >--------------------------------------------------------------- 5e6b43c79115a06a49ec3076208138c421177497 libraries/base/GHC/Enum.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/libraries/base/GHC/Enum.hs b/libraries/base/GHC/Enum.hs index e2655c9..1df43b0 100644 --- a/libraries/base/GHC/Enum.hs +++ b/libraries/base/GHC/Enum.hs @@ -455,7 +455,7 @@ instance Enum Int where -- In particular, we have rules for deforestation {-# RULES -"eftInt" [~1] forall x y. eftInt x y = build (\ c n -> eftIntFB c n x y) +"eftInt" [~1] forall x y. eftInt x y = cheapBuild (\ c n -> eftIntFB c n x y) "eftIntList" [1] eftIntFB (:) [] = eftInt #-} @@ -497,7 +497,7 @@ eftIntFB c n x0 y | isTrue# (x0 ># y) = n -- See Note [How the Enum rules work] {-# RULES "efdtInt" [~1] forall x1 x2 y. - efdtInt x1 x2 y = build (\ c n -> efdtIntFB c n x1 x2 y) + efdtInt x1 x2 y = cheapBuild (\ c n -> efdtIntFB c n x1 x2 y) "efdtIntUpList" [1] efdtIntFB (:) [] = efdtInt #-} From git at git.haskell.org Wed Feb 21 06:50:30 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Feb 2018 06:50:30 +0000 (UTC) Subject: [commit: ghc] wip/cheap-build-osa1: Export cheapBuild in GHC.Exts (d422999) Message-ID: <20180221065030.BC0663A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/cheap-build-osa1 Link : http://ghc.haskell.org/trac/ghc/changeset/d4229993d93f4315b0b094b83c41dada8d18f391/ghc >--------------------------------------------------------------- commit d4229993d93f4315b0b094b83c41dada8d18f391 Author: Ömer Sinan Ağacan Date: Mon Feb 19 13:46:09 2018 +0300 Export cheapBuild in GHC.Exts >--------------------------------------------------------------- d4229993d93f4315b0b094b83c41dada8d18f391 libraries/base/GHC/Exts.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/base/GHC/Exts.hs b/libraries/base/GHC/Exts.hs index a306437..d0b9828 100755 --- a/libraries/base/GHC/Exts.hs +++ b/libraries/base/GHC/Exts.hs @@ -35,7 +35,7 @@ module GHC.Exts isTrue#, -- * Fusion - build, augment, + build, cheapBuild, augment, -- * Overloaded string literals IsString(..), From git at git.haskell.org Wed Feb 21 06:50:22 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Feb 2018 06:50:22 +0000 (UTC) Subject: [commit: ghc] wip/cheap-build-osa1: Move forcing of enumFromT arguemnts inwards (86d8059) Message-ID: <20180221065022.577473A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/cheap-build-osa1 Link : http://ghc.haskell.org/trac/ghc/changeset/86d80595ea57028d153a0bc73a4674d0a49ec818/ghc >--------------------------------------------------------------- commit 86d80595ea57028d153a0bc73a4674d0a49ec818 Author: Simon Peyton Jones Date: Tue Apr 4 15:13:02 2017 +0100 Move forcing of enumFromT arguemnts inwards Proof of concept. See comments on Trac #13422 >--------------------------------------------------------------- 86d80595ea57028d153a0bc73a4674d0a49ec818 libraries/base/GHC/Enum.hs | 37 +++++++++++++++++++------------------ 1 file changed, 19 insertions(+), 18 deletions(-) diff --git a/libraries/base/GHC/Enum.hs b/libraries/base/GHC/Enum.hs index 1df43b0..c65db90 100644 --- a/libraries/base/GHC/Enum.hs +++ b/libraries/base/GHC/Enum.hs @@ -435,12 +435,12 @@ instance Enum Int where fromEnum x = x {-# INLINE enumFrom #-} - enumFrom (I# x) = eftInt x maxInt# - where !(I# maxInt#) = maxInt + enumFrom x = eftInt x maxInt +-- where !(I# maxInt#) = maxInt -- Blarg: technically I guess enumFrom isn't strict! {-# INLINE enumFromTo #-} - enumFromTo (I# x) (I# y) = eftInt x y + enumFromTo x y = eftInt x y {-# INLINE enumFromThen #-} enumFromThen (I# x1) (I# x2) = efdInt x1 x2 @@ -467,24 +467,25 @@ instance Enum Int where -} {-# NOINLINE [1] eftInt #-} -eftInt :: Int# -> Int# -> [Int] +eftInt :: Int -> Int -> [Int] -- [x1..x2] -eftInt x0 y | isTrue# (x0 ># y) = [] - | otherwise = go x0 - where - go x = I# x : if isTrue# (x ==# y) - then [] - else go (x +# 1#) +eftInt (I# x0) (I# y) + | isTrue# (x0 ># y) = [] + | otherwise = go x0 + where + go x = I# x : if isTrue# (x ==# y) + then [] + else go (x +# 1#) {-# INLINE [0] eftIntFB #-} -- See Note [Inline FB functions] in GHC.List -eftIntFB :: (Int -> r -> r) -> r -> Int# -> Int# -> r -eftIntFB c n x0 y | isTrue# (x0 ># y) = n - | otherwise = go x0 - where - go x = I# x `c` if isTrue# (x ==# y) - then n - else go (x +# 1#) - -- Watch out for y=maxBound; hence ==, not > +eftIntFB :: (Int -> r -> r) -> r -> Int -> Int -> r +eftIntFB c n (I# x0) (I# y) + | isTrue# (x0 ># y) = n + | otherwise = go x0 + where + go x = I# x `c` if isTrue# (x ==# y) + then n -- Watch out for y=maxBound; hence ==, not > + else go (x +# 1#) -- Be very careful not to have more than one "c" -- so that when eftInfFB is inlined we can inline -- whatever is bound to "c" From git at git.haskell.org Wed Feb 21 06:50:33 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Feb 2018 06:50:33 +0000 (UTC) Subject: [commit: ghc] wip/cheap-build-osa1: Apply #13422 comment:4 to Char and Word (75ad6a2) Message-ID: <20180221065033.84F0A3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/cheap-build-osa1 Link : http://ghc.haskell.org/trac/ghc/changeset/75ad6a28d80f441f05a73b002f57e844cc1464b9/ghc >--------------------------------------------------------------- commit 75ad6a28d80f441f05a73b002f57e844cc1464b9 Author: Ömer Sinan Ağacan Date: Mon Feb 19 16:04:04 2018 +0300 Apply #13422 comment:4 to Char and Word >--------------------------------------------------------------- 75ad6a28d80f441f05a73b002f57e844cc1464b9 libraries/base/GHC/Base.hs | 11 +++++++ libraries/base/GHC/Enum.hs | 73 ++++++++++++++++++++-------------------------- 2 files changed, 43 insertions(+), 41 deletions(-) diff --git a/libraries/base/GHC/Base.hs b/libraries/base/GHC/Base.hs index 77662ba..89c4217 100644 --- a/libraries/base/GHC/Base.hs +++ b/libraries/base/GHC/Base.hs @@ -1278,6 +1278,17 @@ minInt = I# (-0x8000000000000000#) maxInt = I# 0x7FFFFFFFFFFFFFFF# #endif +maxWord :: Word +-- use unboxed literals for maxBound, because GHC doesn't optimise +-- (fromInteger 0xffffffff :: Word). +#if WORD_SIZE_IN_BITS == 32 +maxWord = W# (int2Word# 0xFFFFFFFF#) +#elif WORD_SIZE_IN_BITS == 64 +maxWord = W# (int2Word# 0xFFFFFFFFFFFFFFFF#) +#else +#error Unhandled value for WORD_SIZE_IN_BITS +#endif + ---------------------------------------------- -- The function type ---------------------------------------------- diff --git a/libraries/base/GHC/Enum.hs b/libraries/base/GHC/Enum.hs index c65db90..704e7b4 100644 --- a/libraries/base/GHC/Enum.hs +++ b/libraries/base/GHC/Enum.hs @@ -306,11 +306,10 @@ instance Enum Char where fromEnum = ord {-# INLINE enumFrom #-} - enumFrom (C# x) = eftChar (ord# x) 0x10FFFF# - -- Blarg: technically I guess enumFrom isn't strict! + enumFrom x = eftChar x (chr 0x10FFFF) {-# INLINE enumFromTo #-} - enumFromTo (C# x) (C# y) = eftChar (ord# x) (ord# y) + enumFromTo x y = eftChar x y {-# INLINE enumFromThen #-} enumFromThen (C# x1) (C# x2) = efdChar (ord# x1) (ord# x2) @@ -332,16 +331,20 @@ instance Enum Char where -- We can do better than for Ints because we don't -- have hassles about arithmetic overflow at maxBound {-# INLINE [0] eftCharFB #-} -- See Note [Inline FB functions] in GHC.List -eftCharFB :: (Char -> a -> a) -> a -> Int# -> Int# -> a -eftCharFB c n x0 y = go x0 +eftCharFB :: (Char -> a -> a) -> a -> Char -> Char -> a +eftCharFB c n (C# x0) (C# y0) = go (ord# x0) where + y = ord# y0 go x | isTrue# (x ># y) = n | otherwise = C# (chr# x) `c` go (x +# 1#) {-# NOINLINE [1] eftChar #-} -eftChar :: Int# -> Int# -> String -eftChar x y | isTrue# (x ># y ) = [] - | otherwise = C# (chr# x) : eftChar (x +# 1#) y +eftChar :: Char -> Char -> String +eftChar (C# x0) (C# y0) = go (ord# x0) (ord# y0) + where + go x y + | isTrue# (x ># y) = [] + | otherwise = C# (chr# x) : go (x +# 1#) y -- For enumFromThenTo we give up on inlining @@ -436,8 +439,6 @@ instance Enum Int where {-# INLINE enumFrom #-} enumFrom x = eftInt x maxInt --- where !(I# maxInt#) = maxInt - -- Blarg: technically I guess enumFrom isn't strict! {-# INLINE enumFromTo #-} enumFromTo x y = eftInt x y @@ -591,16 +592,7 @@ efdtIntDnFB c n x1 x2 y -- Be careful about underflow! -- | @since 2.01 instance Bounded Word where minBound = 0 - - -- use unboxed literals for maxBound, because GHC doesn't optimise - -- (fromInteger 0xffffffff :: Word). -#if WORD_SIZE_IN_BITS == 32 - maxBound = W# (int2Word# 0xFFFFFFFF#) -#elif WORD_SIZE_IN_BITS == 64 - maxBound = W# (int2Word# 0xFFFFFFFFFFFFFFFF#) -#else -#error Unhandled value for WORD_SIZE_IN_BITS -#endif + maxBound = maxWord -- | @since 2.01 instance Enum Word where @@ -618,12 +610,10 @@ instance Enum Word where | otherwise = fromEnumError "Word" x {-# INLINE enumFrom #-} - enumFrom (W# x#) = eftWord x# maxWord# - where !(W# maxWord#) = maxBound - -- Blarg: technically I guess enumFrom isn't strict! + enumFrom x = eftWord x maxWord {-# INLINE enumFromTo #-} - enumFromTo (W# x) (W# y) = eftWord x y + enumFromTo x y = eftWord x y {-# INLINE enumFromThen #-} enumFromThen (W# x1) (W# x2) = efdWord x1 x2 @@ -641,7 +631,7 @@ maxIntWord = W# (case maxInt of I# i -> int2Word# i) -- In particular, we have rules for deforestation {-# RULES -"eftWord" [~1] forall x y. eftWord x y = build (\ c n -> eftWordFB c n x y) +"eftWord" [~1] forall x y. eftWord x y = cheapBuild (\ c n -> eftWordFB c n x y) "eftWordList" [1] eftWordFB (:) [] = eftWord #-} @@ -649,24 +639,25 @@ maxIntWord = W# (case maxInt of I# i -> int2Word# i) -- See Note [How the Enum rules work]. {-# NOINLINE [1] eftWord #-} -eftWord :: Word# -> Word# -> [Word] +eftWord :: Word -> Word -> [Word] -- [x1..x2] -eftWord x0 y | isTrue# (x0 `gtWord#` y) = [] - | otherwise = go x0 - where - go x = W# x : if isTrue# (x `eqWord#` y) - then [] - else go (x `plusWord#` 1##) +eftWord (W# x0) (W# y) + | isTrue# (x0 `gtWord#` y) = [] + | otherwise = go x0 + where + go x = W# x : if isTrue# (x `eqWord#` y) + then [] + else go (x `plusWord#` 1##) {-# INLINE [0] eftWordFB #-} -- See Note [Inline FB functions] in GHC.List -eftWordFB :: (Word -> r -> r) -> r -> Word# -> Word# -> r -eftWordFB c n x0 y | isTrue# (x0 `gtWord#` y) = n - | otherwise = go x0 - where - go x = W# x `c` if isTrue# (x `eqWord#` y) - then n - else go (x `plusWord#` 1##) - -- Watch out for y=maxBound; hence ==, not > +eftWordFB :: (Word -> r -> r) -> r -> Word -> Word -> r +eftWordFB c n (W# x0) (W# y) + | isTrue# (x0 `gtWord#` y) = n + | otherwise = go x0 + where + go x = W# x `c` if isTrue# (x `eqWord#` y) + then n -- Watch out for y=maxBound; hence ==, not > + else go (x `plusWord#` 1##) -- Be very careful not to have more than one "c" -- so that when eftInfFB is inlined we can inline -- whatever is bound to "c" @@ -679,7 +670,7 @@ eftWordFB c n x0 y | isTrue# (x0 `gtWord#` y) = n -- See Note [How the Enum rules work] {-# RULES "efdtWord" [~1] forall x1 x2 y. - efdtWord x1 x2 y = build (\ c n -> efdtWordFB c n x1 x2 y) + efdtWord x1 x2 y = cheapBuild (\ c n -> efdtWordFB c n x1 x2 y) "efdtWordUpList" [1] efdtWordFB (:) [] = efdtWord #-} From git at git.haskell.org Wed Feb 21 17:03:26 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Feb 2018 17:03:26 +0000 (UTC) Subject: [commit: ghc] master: Don't use ld.gold when building libraries for GHCi (0a3629a) Message-ID: <20180221170326.87DE23A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0a3629af36e89de73b7012c726fd533c4c5460fb/ghc >--------------------------------------------------------------- commit 0a3629af36e89de73b7012c726fd533c4c5460fb Author: Simon Marlow Date: Wed Feb 21 14:16:00 2018 +0000 Don't use ld.gold when building libraries for GHCi Summary: ld.gold is buggy when using -r and a linker script. See upstream bug https://sourceware.org/bugzilla/show_bug.cgi?id=22266 This has been causing various brokenness for the GHC runtime linker, where we load these broken object files. Test Plan: Test program from #14675 Reviewers: bgamari, RyanGlScott, alpmestan, hvr, erikd Subscribers: rwbarton, thomie, erikd, carter GHC Trac Issues: #14328, #14675, #14291 Differential Revision: https://phabricator.haskell.org/D4431 >--------------------------------------------------------------- 0a3629af36e89de73b7012c726fd533c4c5460fb aclocal.m4 | 13 ++++++++++--- configure.ac | 2 ++ mk/config.mk.in | 1 + rules/build-package-way.mk | 7 +++++-- 4 files changed, 18 insertions(+), 5 deletions(-) diff --git a/aclocal.m4 b/aclocal.m4 index 6f37972..5ad3752 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -2340,6 +2340,7 @@ AC_DEFUN([FIND_LD],[ # Make sure the user didn't specify LD manually. if test "z$LD" != "z"; then AC_CHECK_TARGET_TOOL([LD], [ld]) + LD_NO_GOLD=$LD return fi @@ -2352,10 +2353,16 @@ AC_DEFUN([FIND_LD],[ if test "x$TmpLd" = "x"; then continue; fi out=`$TmpLd --version` + LD_NO_GOLD=$TmpLd case $out in - "GNU ld"*) FP_CC_LINKER_FLAG_TRY(bfd, $2) ;; - "GNU gold"*) FP_CC_LINKER_FLAG_TRY(gold, $2) ;; - "LLD"*) FP_CC_LINKER_FLAG_TRY(lld, $2) ;; + "GNU ld"*) + FP_CC_LINKER_FLAG_TRY(bfd, $2) ;; + "GNU gold"*) + FP_CC_LINKER_FLAG_TRY(gold, $2) + LD_NO_GOLD=ld + ;; + "LLD"*) + FP_CC_LINKER_FLAG_TRY(lld, $2) ;; *) AC_MSG_NOTICE([unknown linker version $out]) ;; esac if test "z$$2" = "z"; then diff --git a/configure.ac b/configure.ac index 216a97f..216f43f 100644 --- a/configure.ac +++ b/configure.ac @@ -544,8 +544,10 @@ FIND_LD([$target],[GccUseLdOpt]) CONF_GCC_LINKER_OPTS_STAGE1="$CONF_GCC_LINKER_OPTS_STAGE1 $GccUseLdOpt" CONF_GCC_LINKER_OPTS_STAGE2="$CONF_GCC_LINKER_OPTS_STAGE2 $GccUseLdOpt" LdCmd="$LD" +LdNoGoldCmd="$LD_NO_GOLD" CFLAGS="$CFLAGS $GccUseLdOpt" AC_SUBST([LdCmd]) +AC_SUBST([LdNoGoldCmd]) FP_PROG_LD_IS_GNU FP_PROG_LD_BUILD_ID diff --git a/mk/config.mk.in b/mk/config.mk.in index 86c626d..e5ec04a 100644 --- a/mk/config.mk.in +++ b/mk/config.mk.in @@ -727,6 +727,7 @@ HaveDtrace = @HaveDtrace@ USE_DTRACE = $(HaveDtrace) DTRACE = @DtraceCmd@ +LD_NO_GOLD = @LdNoGoldCmd@ LD = @LdCmd@ NM = @NmCmd@ AR = @ArCmd@ diff --git a/rules/build-package-way.mk b/rules/build-package-way.mk index 9c101c4..8d14b7a 100644 --- a/rules/build-package-way.mk +++ b/rules/build-package-way.mk @@ -121,8 +121,11 @@ BINDIST_LIBS += $$($1_$2_GHCI_LIB) endif endif $$($1_$2_GHCI_LIB) : $$($1_$2_$3_HS_OBJS) $$($1_$2_$3_CMM_OBJS) $$($1_$2_$3_C_OBJS) $$($1_$2_$3_S_OBJS) $$($1_$2_EXTRA_OBJS) $$($1_$2_LD_SCRIPT) - $$(call cmd,LD) $$(CONF_LD_LINKER_OPTS_STAGE$4) -r $$(if $$($1_$2_LD_SCRIPT),$$($1_$2_LD_SCRIPT_CMD) $$($1_$2_LD_SCRIPT)) -o $$@ $$(EXTRA_LD_LINKER_OPTS) $$($1_$2_$3_HS_OBJS) $$($1_$2_$3_CMM_OBJS) $$($1_$2_$3_C_OBJS) $$($1_$2_$3_S_OBJS) $$($1_$2_EXTRA_OBJS) - + $$(call cmd,LD_NO_GOLD) $$(CONF_LD_LINKER_OPTS_STAGE$4) -r $$(if $$($1_$2_LD_SCRIPT),$$($1_$2_LD_SCRIPT_CMD) $$($1_$2_LD_SCRIPT)) -o $$@ $$(EXTRA_LD_LINKER_OPTS) $$($1_$2_$3_HS_OBJS) $$($1_$2_$3_CMM_OBJS) $$($1_$2_$3_C_OBJS) $$($1_$2_$3_S_OBJS) $$($1_$2_EXTRA_OBJS) +# NB. LD_NO_GOLD above: see #14328 (symptoms: #14675,#14291). At least +# some versions of ld.gold appear to have a bug that causes the +# generated GHCi library to have some bogus relocations. Performance +# isn't critical here, so we fall back to the ordinary ld. ifeq "$$($1_$2_BUILD_GHCI_LIB)" "YES" # Don't bother making ghci libs for bootstrapping packages ifneq "$4" "0" From git at git.haskell.org Thu Feb 22 15:47:56 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Feb 2018 15:47:56 +0000 (UTC) Subject: [commit: ghc] master: Comments in Unify, fixing #12442 (3483423) Message-ID: <20180222154756.65E6B3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/34834234fff4a9dd0408d3b29e001cd132665327/ghc >--------------------------------------------------------------- commit 34834234fff4a9dd0408d3b29e001cd132665327 Author: Richard Eisenberg Date: Thu Feb 22 10:44:18 2018 -0500 Comments in Unify, fixing #12442 [ci skip] >--------------------------------------------------------------- 34834234fff4a9dd0408d3b29e001cd132665327 compiler/types/Unify.hs | 46 ++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 46 insertions(+) diff --git a/compiler/types/Unify.hs b/compiler/types/Unify.hs index b401e1b..2c9762c 100644 --- a/compiler/types/Unify.hs +++ b/compiler/types/Unify.hs @@ -70,6 +70,34 @@ Unification is much tricker than you might think. where x is the template type variable. Then we do not want to bind x to a/b! This is a kind of occurs check. The necessary locals accumulate in the RnEnv2. + +Note [tcMatchTy vs tcMatchTyKi] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +This module offers two variants of matching: with kinds and without. +The TyKi variant takes two types, of potentially different kinds, +and matches them. Along the way, it necessarily also matches their +kinds. The Ty variant instead assumes that the kinds are already +eqType and so skips matching up the kinds. + +How do you choose between them? + +1. If you know that the kinds of the two types are eqType, use + the Ty variant. It is more efficient, as it does less work. + +2. If the kinds of variables in the template type might mention type families, + use the Ty variant (and do other work to make sure the kinds + work out). These pure unification functions do a straightforward + syntactic unification and do no complex reasoning about type + families. Note that the types of the variables in instances can indeed + mention type families, so instance lookup must use the Ty variant. + + (Nothing goes terribly wrong -- no panics -- if there might be type + families in kinds in the TyKi variant. You just might get match + failure even though a reducing a type family would lead to success.) + +3. Otherwise, if you're sure that the variable kinds to not mention + type families and you're not already sure that the kind of the template + equals the kind of the target, then use the TyKi versio.n -} -- | @tcMatchTy t1 t2@ produces a substitution (over fvs(t1)) @@ -83,15 +111,18 @@ Unification is much tricker than you might think. -- by the match, because tcMatchTy (and similar functions) are -- always used on top-level types, so we can bind any of the -- free variables of the LHS. +-- See also Note [tcMatchTy vs tcMatchTyKi] tcMatchTy :: Type -> Type -> Maybe TCvSubst tcMatchTy ty1 ty2 = tcMatchTys [ty1] [ty2] -- | Like 'tcMatchTy', but allows the kinds of the types to differ, -- and thus matches them as well. +-- See also Note [tcMatchTy vs tcMatchTyKi] tcMatchTyKi :: Type -> Type -> Maybe TCvSubst tcMatchTyKi ty1 ty2 = tcMatchTyKis [ty1] [ty2] -- | This is similar to 'tcMatchTy', but extends a substitution +-- See also Note [tcMatchTy vs tcMatchTyKi] tcMatchTyX :: TCvSubst -- ^ Substitution to extend -> Type -- ^ Template -> Type -- ^ Target @@ -99,6 +130,7 @@ tcMatchTyX :: TCvSubst -- ^ Substitution to extend tcMatchTyX subst ty1 ty2 = tcMatchTysX subst [ty1] [ty2] -- | Like 'tcMatchTy' but over a list of types. +-- See also Note [tcMatchTy vs tcMatchTyKi] tcMatchTys :: [Type] -- ^ Template -> [Type] -- ^ Target -> Maybe TCvSubst -- ^ One-shot; in principle the template @@ -109,6 +141,7 @@ tcMatchTys tys1 tys2 in_scope = mkInScopeSet (tyCoVarsOfTypes tys1 `unionVarSet` tyCoVarsOfTypes tys2) -- | Like 'tcMatchTyKi' but over a list of types. +-- See also Note [tcMatchTy vs tcMatchTyKi] tcMatchTyKis :: [Type] -- ^ Template -> [Type] -- ^ Target -> Maybe TCvSubst -- ^ One-shot substitution @@ -118,6 +151,7 @@ tcMatchTyKis tys1 tys2 in_scope = mkInScopeSet (tyCoVarsOfTypes tys1 `unionVarSet` tyCoVarsOfTypes tys2) -- | Like 'tcMatchTys', but extending a substitution +-- See also Note [tcMatchTy vs tcMatchTyKi] tcMatchTysX :: TCvSubst -- ^ Substitution to extend -> [Type] -- ^ Template -> [Type] -- ^ Target @@ -126,6 +160,7 @@ tcMatchTysX subst tys1 tys2 = tc_match_tys_x False subst tys1 tys2 -- | Like 'tcMatchTyKis', but extending a substitution +-- See also Note [tcMatchTy vs tcMatchTyKi] tcMatchTyKisX :: TCvSubst -- ^ Substitution to extend -> [Type] -- ^ Template -> [Type] -- ^ Target @@ -463,6 +498,17 @@ tc_unify_tys :: (TyVar -> BindFlag) -> CvSubstEnv -> [Type] -> [Type] -> UnifyResultM (TvSubstEnv, CvSubstEnv) +-- NB: It's tempting to ASSERT here that, if we're not matching kinds, then +-- the kinds of the types should be the same. However, this doesn't work, +-- as the types may be a dependent telescope, where later types have kinds +-- that mention variables occuring earlier in the list of types. Here's an +-- example (from typecheck/should_fail/T12709): +-- template: [rep :: RuntimeRep, a :: TYPE rep] +-- target: [LiftedRep :: RuntimeRep, Int :: TYPE LiftedRep] +-- We can see that matching the first pair will make the kinds of the second +-- pair equal. Yet, we still don't need a separate pass to unify the kinds +-- of these types, so it's appropriate to use the Ty variant of unification. +-- See also Note [tcMatchTy vs tcMatchTyKi]. tc_unify_tys bind_fn unif inj_check match_kis rn_env tv_env cv_env tys1 tys2 = initUM tv_env cv_env $ do { when match_kis $ From git at git.haskell.org Thu Feb 22 22:42:36 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Feb 2018 22:42:36 +0000 (UTC) Subject: [commit: ghc] wip/docker-ghcci: Try experimental public docker image (4d73935) Message-ID: <20180222224236.23AE13A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/docker-ghcci Link : http://ghc.haskell.org/trac/ghc/changeset/4d73935aaa2ed069b52c7fbdbe2c60ef53dfbab9/ghc >--------------------------------------------------------------- commit 4d73935aaa2ed069b52c7fbdbe2c60ef53dfbab9 Author: David Feuer Date: Thu Feb 22 17:42:04 2018 -0500 Try experimental public docker image >--------------------------------------------------------------- 4d73935aaa2ed069b52c7fbdbe2c60ef53dfbab9 .circleci/config.yml | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/.circleci/config.yml b/.circleci/config.yml index 1a542b1..bc318c6 100644 --- a/.circleci/config.yml +++ b/.circleci/config.yml @@ -98,7 +98,7 @@ jobs: "validate-x86_64-linux": resource_class: xlarge docker: - - image: ghcci:x86_64-linux + - image: dfeuer/ghcci:x86_64-linux-0.0.1 environment: <<: *buildenv steps: @@ -158,7 +158,7 @@ jobs: "validate-hadrian-x86_64-linux": resource_class: xlarge docker: - - image: ghcci:x86_64-linux + - image: dfeuer/ghcci:x86_64-linux-0.0.1 environment: <<: *buildenv steps: @@ -174,7 +174,7 @@ jobs: "validate-x86_64-linux-unreg": resource_class: xlarge docker: - - image: ghcci:x86_64-linux + - image: dfeuer/ghcci:x86_64-linux-0.0.1 environment: <<: *buildenv steps: @@ -190,7 +190,7 @@ jobs: "validate-x86_64-linux-llvm": resource_class: xlarge docker: - - image: ghcci:x86_64-linux + - image: dfeuer/ghcci:x86_64-linux-0.0.1 environment: <<: *buildenv BUILD_FLAVOUR: perf-llvm From git at git.haskell.org Fri Feb 23 16:37:51 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Feb 2018 16:37:51 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: Don't use ld.gold when building libraries for GHCi (b4e3278) Message-ID: <20180223163751.C437D3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/b4e32780a976193208eebbddf789eeb80351ac95/ghc >--------------------------------------------------------------- commit b4e32780a976193208eebbddf789eeb80351ac95 Author: Simon Marlow Date: Wed Feb 21 14:16:00 2018 +0000 Don't use ld.gold when building libraries for GHCi Summary: ld.gold is buggy when using -r and a linker script. See upstream bug https://sourceware.org/bugzilla/show_bug.cgi?id=22266 This has been causing various brokenness for the GHC runtime linker, where we load these broken object files. Test Plan: Test program from #14675 Reviewers: bgamari, RyanGlScott, alpmestan, hvr, erikd Subscribers: rwbarton, thomie, erikd, carter GHC Trac Issues: #14328, #14675, #14291 Differential Revision: https://phabricator.haskell.org/D4431 (cherry picked from commit 0a3629af36e89de73b7012c726fd533c4c5460fb) >--------------------------------------------------------------- b4e32780a976193208eebbddf789eeb80351ac95 aclocal.m4 | 13 ++++++++++--- configure.ac | 2 ++ mk/config.mk.in | 1 + rules/build-package-way.mk | 7 +++++-- 4 files changed, 18 insertions(+), 5 deletions(-) diff --git a/aclocal.m4 b/aclocal.m4 index 99ff1bf..cf93474 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -2355,6 +2355,7 @@ AC_DEFUN([FIND_LD],[ # Make sure the user didn't specify LD manually. if test "z$LD" != "z"; then AC_CHECK_TARGET_TOOL([LD], [ld]) + LD_NO_GOLD=$LD return fi @@ -2367,10 +2368,16 @@ AC_DEFUN([FIND_LD],[ if test "x$TmpLd" = "x"; then continue; fi out=`$TmpLd --version` + LD_NO_GOLD=$TmpLd case $out in - "GNU ld"*) FP_CC_LINKER_FLAG_TRY(bfd, $2) ;; - "GNU gold"*) FP_CC_LINKER_FLAG_TRY(gold, $2) ;; - "LLD"*) FP_CC_LINKER_FLAG_TRY(lld, $2) ;; + "GNU ld"*) + FP_CC_LINKER_FLAG_TRY(bfd, $2) ;; + "GNU gold"*) + FP_CC_LINKER_FLAG_TRY(gold, $2) + LD_NO_GOLD=ld + ;; + "LLD"*) + FP_CC_LINKER_FLAG_TRY(lld, $2) ;; *) AC_MSG_NOTICE([unknown linker version $out]) ;; esac if test "z$$2" = "z"; then diff --git a/configure.ac b/configure.ac index ec96d2c..57d76b4 100644 --- a/configure.ac +++ b/configure.ac @@ -544,8 +544,10 @@ FIND_LD([$target],[GccUseLdOpt]) CONF_GCC_LINKER_OPTS_STAGE1="$CONF_GCC_LINKER_OPTS_STAGE1 $GccUseLdOpt" CONF_GCC_LINKER_OPTS_STAGE2="$CONF_GCC_LINKER_OPTS_STAGE2 $GccUseLdOpt" LdCmd="$LD" +LdNoGoldCmd="$LD_NO_GOLD" CFLAGS="$CFLAGS $GccUseLdOpt" AC_SUBST([LdCmd]) +AC_SUBST([LdNoGoldCmd]) FP_PROG_LD_IS_GNU FP_PROG_LD_BUILD_ID diff --git a/mk/config.mk.in b/mk/config.mk.in index 86c626d..e5ec04a 100644 --- a/mk/config.mk.in +++ b/mk/config.mk.in @@ -727,6 +727,7 @@ HaveDtrace = @HaveDtrace@ USE_DTRACE = $(HaveDtrace) DTRACE = @DtraceCmd@ +LD_NO_GOLD = @LdNoGoldCmd@ LD = @LdCmd@ NM = @NmCmd@ AR = @ArCmd@ diff --git a/rules/build-package-way.mk b/rules/build-package-way.mk index 9c101c4..8d14b7a 100644 --- a/rules/build-package-way.mk +++ b/rules/build-package-way.mk @@ -121,8 +121,11 @@ BINDIST_LIBS += $$($1_$2_GHCI_LIB) endif endif $$($1_$2_GHCI_LIB) : $$($1_$2_$3_HS_OBJS) $$($1_$2_$3_CMM_OBJS) $$($1_$2_$3_C_OBJS) $$($1_$2_$3_S_OBJS) $$($1_$2_EXTRA_OBJS) $$($1_$2_LD_SCRIPT) - $$(call cmd,LD) $$(CONF_LD_LINKER_OPTS_STAGE$4) -r $$(if $$($1_$2_LD_SCRIPT),$$($1_$2_LD_SCRIPT_CMD) $$($1_$2_LD_SCRIPT)) -o $$@ $$(EXTRA_LD_LINKER_OPTS) $$($1_$2_$3_HS_OBJS) $$($1_$2_$3_CMM_OBJS) $$($1_$2_$3_C_OBJS) $$($1_$2_$3_S_OBJS) $$($1_$2_EXTRA_OBJS) - + $$(call cmd,LD_NO_GOLD) $$(CONF_LD_LINKER_OPTS_STAGE$4) -r $$(if $$($1_$2_LD_SCRIPT),$$($1_$2_LD_SCRIPT_CMD) $$($1_$2_LD_SCRIPT)) -o $$@ $$(EXTRA_LD_LINKER_OPTS) $$($1_$2_$3_HS_OBJS) $$($1_$2_$3_CMM_OBJS) $$($1_$2_$3_C_OBJS) $$($1_$2_$3_S_OBJS) $$($1_$2_EXTRA_OBJS) +# NB. LD_NO_GOLD above: see #14328 (symptoms: #14675,#14291). At least +# some versions of ld.gold appear to have a bug that causes the +# generated GHCi library to have some bogus relocations. Performance +# isn't critical here, so we fall back to the ordinary ld. ifeq "$$($1_$2_BUILD_GHCI_LIB)" "YES" # Don't bother making ghci libs for bootstrapping packages ifneq "$4" "0" From git at git.haskell.org Sat Feb 24 15:11:14 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 24 Feb 2018 15:11:14 +0000 (UTC) Subject: [commit: hadrian] master: Fix Haddock (#496) (8d6945d) Message-ID: <20180224151114.711693A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hadrian On branch : master Link : http://git.haskell.org/hadrian.git/commitdiff/8d6945d970926ae77ea0d05a2b6590920eabc985 >--------------------------------------------------------------- commit 8d6945d970926ae77ea0d05a2b6590920eabc985 Author: Andrey Mokhov Date: Sat Feb 3 01:56:47 2018 +0000 Fix Haddock (#496) See #492. >--------------------------------------------------------------- 8d6945d970926ae77ea0d05a2b6590920eabc985 src/Rules/Documentation.hs | 13 ++++++++----- src/Rules/Generate.hs | 6 ++++++ 2 files changed, 14 insertions(+), 5 deletions(-) diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs index 5a5698c..3043f8b 100644 --- a/src/Rules/Documentation.hs +++ b/src/Rules/Documentation.hs @@ -117,8 +117,11 @@ allHaddocks = do sequence [ pkgHaddockFile $ vanillaContext Stage1 pkg | pkg <- pkgs, isLibrary pkg, isHsPackage pkg ] -haddockHtmlLib :: FilePath -haddockHtmlLib = "inplace/lib/html/haddock-util.js" +-- TODO: This is fragile and will break if @README.md@ is removed. We need to +-- improve the story of program runtime dependencies on directories. +-- See: https://github.com/snowleopard/hadrian/issues/492. +haddockHtmlResourcesStamp :: FilePath +haddockHtmlResourcesStamp = "inplace/lib/html/README.md" -- | Find the haddock files for the dependencies of the current library haddockDependencies :: Context -> Action [FilePath] @@ -135,8 +138,8 @@ buildPackageDocumentation :: Context -> Rules () buildPackageDocumentation context at Context {..} = when (stage == Stage1) $ do -- Js and Css files for haddock output - when (package == haddock) $ haddockHtmlLib %> \_ -> do - let dir = takeDirectory haddockHtmlLib + when (package == haddock) $ haddockHtmlResourcesStamp %> \_ -> do + let dir = takeDirectory haddockHtmlResourcesStamp liftIO $ removeFiles dir ["//*"] copyDirectory "utils/haddock/haddock-api/resources/html" dir @@ -144,7 +147,7 @@ buildPackageDocumentation context at Context {..} = when (stage == Stage1) $ do "//" ++ pkgName package <.> "haddock" %> \file -> do haddocks <- haddockDependencies context srcs <- hsSources context - need $ srcs ++ haddocks ++ [haddockHtmlLib] + need $ srcs ++ haddocks ++ [haddockHtmlResourcesStamp] -- Build Haddock documentation -- TODO: pass the correct way from Rules via Context diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 8e2b65d..8616da0 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -141,6 +141,12 @@ generatePackageCode context@(Context stage pkg _) = when (pkg == rts) $ "//" ++ dir -/- "cmm/AutoApply.cmm" %> \file -> build $ target context GenApply [] [file] +-- TODO: These rules copy runtime dependencies of some executables, such as GHC +-- itself (file @ghc-usage.txt@) or Hsc2Hs (file @template-hsc.h@). Ideally, +-- these rules should be moved to package-specific settings, so that they can be +-- discovered more easily. We also need to add proper support for runtime +-- dependencies on directories, which is the case for Haddock -- for the current +-- workaround see "Rules.Documentation.haddockHtmlResourcesStamp". copyRules :: Rules () copyRules = do (inplaceLibPath -/- "ghc-usage.txt") <~ return "driver" From git at git.haskell.org Sat Feb 24 15:11:20 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 24 Feb 2018 15:11:20 +0000 (UTC) Subject: [commit: hadrian] master: Add support for runtime dependencies (c01865f) Message-ID: <20180224151120.8022E3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hadrian On branch : master Link : http://git.haskell.org/hadrian.git/commitdiff/c01865f4a844af0d11d95d3d2697c2de026a51b7 >--------------------------------------------------------------- commit c01865f4a844af0d11d95d3d2697c2de026a51b7 Author: Andrey Mokhov Date: Fri Feb 9 01:32:55 2018 +0000 Add support for runtime dependencies >--------------------------------------------------------------- c01865f4a844af0d11d95d3d2697c2de026a51b7 src/Base.hs | 24 +++++++++++++++++++----- src/Builder.hs | 36 +++++++++++++++++++++++++++--------- src/GHC.hs | 20 +------------------- src/Hadrian/Builder.hs | 22 ++++++++++++++-------- src/Rules/Documentation.hs | 8 +------- src/Rules/Install.hs | 15 ++++++++++++++- src/Rules/Test.hs | 5 ++--- src/Settings/Builders/Ghc.hs | 13 +------------ 8 files changed, 79 insertions(+), 64 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c01865f4a844af0d11d95d3d2697c2de026a51b7 From git at git.haskell.org Sat Feb 24 15:11:18 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 24 Feb 2018 15:11:18 +0000 (UTC) Subject: [commit: hadrian] master: Fix Hadrian after Cabal changes (#498) (fd51234) Message-ID: <20180224151118.79A963A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hadrian On branch : master Link : http://git.haskell.org/hadrian.git/commitdiff/fd51234fd35a5aa367be63f89bc27e96e2190978 >--------------------------------------------------------------- commit fd51234fd35a5aa367be63f89bc27e96e2190978 Author: Andrey Mokhov Date: Wed Feb 7 02:50:26 2018 +0000 Fix Hadrian after Cabal changes (#498) * Fix Hadrian after Cabal changes * Bump Cabal's lower bound >--------------------------------------------------------------- fd51234fd35a5aa367be63f89bc27e96e2190978 hadrian.cabal | 2 +- src/Hadrian/Haskell/Cabal/Parse.hs | 12 ++++++------ 2 files changed, 7 insertions(+), 7 deletions(-) diff --git a/hadrian.cabal b/hadrian.cabal index efc1251..0405601 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -118,7 +118,7 @@ executable hadrian other-extensions: MultiParamTypeClasses , TypeFamilies build-depends: base >= 4.8 && < 5 - , Cabal >= 2.0.0.2 && < 2.2 + , Cabal >= 2.1.0.0 && < 2.2 , containers == 0.5.* , directory >= 1.2 && < 1.4 , extra >= 1.4.7 diff --git a/src/Hadrian/Haskell/Cabal/Parse.hs b/src/Hadrian/Haskell/Cabal/Parse.hs index 578eeac..f097b62 100644 --- a/src/Hadrian/Haskell/Cabal/Parse.hs +++ b/src/Hadrian/Haskell/Cabal/Parse.hs @@ -13,12 +13,12 @@ module Hadrian.Haskell.Cabal.Parse (Cabal (..), parseCabal) where import Data.List.Extra import Development.Shake import Development.Shake.Classes -import qualified Distribution.Package as C -import qualified Distribution.PackageDescription as C -import qualified Distribution.PackageDescription.Parse as C -import qualified Distribution.Text as C -import qualified Distribution.Types.CondTree as C -import qualified Distribution.Verbosity as C +import qualified Distribution.Package as C +import qualified Distribution.PackageDescription as C +import qualified Distribution.PackageDescription.Parsec as C +import qualified Distribution.Text as C +import qualified Distribution.Types.CondTree as C +import qualified Distribution.Verbosity as C import Hadrian.Package From git at git.haskell.org Sat Feb 24 15:11:24 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 24 Feb 2018 15:11:24 +0000 (UTC) Subject: [commit: hadrian] master: Add unlit to GHC's runtime dependencies (81f180a) Message-ID: <20180224151124.8A4A23A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hadrian On branch : master Link : http://git.haskell.org/hadrian.git/commitdiff/81f180a0e3d485b388171c7b29946f7690177b3a >--------------------------------------------------------------- commit 81f180a0e3d485b388171c7b29946f7690177b3a Author: Andrey Mokhov Date: Fri Feb 9 02:30:00 2018 +0000 Add unlit to GHC's runtime dependencies >--------------------------------------------------------------- 81f180a0e3d485b388171c7b29946f7690177b3a src/Builder.hs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/src/Builder.hs b/src/Builder.hs index ae967ab..67e1634 100644 --- a/src/Builder.hs +++ b/src/Builder.hs @@ -145,12 +145,14 @@ instance H.Builder Builder where Ghc _ _ -> do win <- windowsHost touchyPath <- programPath (vanillaContext Stage0 touchy) - return $ [ inplaceLibPath -/- "ghc-usage.txt" + unlitPath <- builderPath Unlit + return $ [ ghcSplitPath -- TODO: Make conditional on --split-objects + , inplaceLibPath -/- "ghc-usage.txt" , inplaceLibPath -/- "ghci-usage.txt" , inplaceLibPath -/- "llvm-targets" , inplaceLibPath -/- "platformConstants" , inplaceLibPath -/- "settings" - , ghcSplitPath ] -- TODO: Make conditional on --split-objects + , unlitPath ] ++ [ touchyPath | win ] Haddock _ -> return [haddockHtmlResourcesStamp] From git at git.haskell.org Sat Feb 24 15:11:16 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 24 Feb 2018 15:11:16 +0000 (UTC) Subject: [commit: hadrian] master: Drop custom logic for Scav_thr and Evac_thr (#497) (1232d26) Message-ID: <20180224151116.746C63A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hadrian On branch : master Link : http://git.haskell.org/hadrian.git/commitdiff/1232d26576eb156301aedab77f17d509c6887c48 >--------------------------------------------------------------- commit 1232d26576eb156301aedab77f17d509c6887c48 Author: Andrey Mokhov Date: Sun Feb 4 02:31:10 2018 +0000 Drop custom logic for Scav_thr and Evac_thr (#497) See https://phabricator.haskell.org/D3237 >--------------------------------------------------------------- 1232d26576eb156301aedab77f17d509c6887c48 doc/user-settings.md | 2 +- src/Rules/Compile.hs | 2 +- src/Rules/Generate.hs | 9 ++------- src/Rules/Library.hs | 5 +---- src/Rules/PackageData.hs | 4 +--- src/Settings/Builders/RunTest.hs | 2 -- src/Settings/Packages/Rts.hs | 14 ++++++-------- 7 files changed, 12 insertions(+), 26 deletions(-) diff --git a/doc/user-settings.md b/doc/user-settings.md index e800d51..1a89dd4 100644 --- a/doc/user-settings.md +++ b/doc/user-settings.md @@ -87,7 +87,7 @@ You can combine several custom command line settings using `mconcat`: userArgs :: Args userArgs = mconcat [ builder Ghc ? package cabal ? arg "-O0" - , package rts ? input "//Evac_thr.c" ? pure [ "-DPARALLEL_GC", "-Irts/sm" ] ] + , package rts ? input "//PrimOps.c" ? pure ["-fno-PIC", "-static"] ] ``` You can match any combination of the `builder`, `stage`, `package`, `way`, `input` and `output` predicates when specifying custom command line arguments. File diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs index b7f3bc8..8bca888 100644 --- a/src/Rules/Compile.hs +++ b/src/Rules/Compile.hs @@ -25,7 +25,7 @@ compilePackage rs context at Context {..} = do buildWithResources rs $ target context (Ghc CompileHs stage) [src] [obj] priority 2.0 $ do - nonHs "c" %> compile (Ghc CompileCWithGhc) (obj2src "c" isGeneratedCFile ) + nonHs "c" %> compile (Ghc CompileCWithGhc) (obj2src "c" $ const False ) nonHs "cmm" %> compile (Ghc CompileHs) (obj2src "cmm" isGeneratedCmmFile) nonHs "s" %> compile (Ghc CompileHs) (obj2src "S" $ const False ) diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs index 8616da0..a8f3956 100644 --- a/src/Rules/Generate.hs +++ b/src/Rules/Generate.hs @@ -1,6 +1,6 @@ module Rules.Generate ( - isGeneratedCFile, isGeneratedCmmFile, generatePackageCode, generateRules, - copyRules, includesDependencies, generatedDependencies + isGeneratedCmmFile, generatePackageCode, generateRules, copyRules, + includesDependencies, generatedDependencies ) where import Base @@ -29,9 +29,6 @@ primopsTxt stage = contextDir (vanillaContext stage compiler) -/- "primops.txt" platformH :: Stage -> FilePath platformH stage = contextDir (vanillaContext stage compiler) -/- "ghc_boot_platform.h" -isGeneratedCFile :: FilePath -> Bool -isGeneratedCFile file = takeBaseName file `elem` ["Evac_thr", "Scav_thr"] - isGeneratedCmmFile :: FilePath -> Bool isGeneratedCmmFile file = takeBaseName file == "AutoApply" @@ -155,8 +152,6 @@ copyRules = do (inplaceLibPath -/- "platformConstants") <~ (buildRoot <&> (-/- generatedDir)) (inplaceLibPath -/- "settings") <~ return "." (inplaceLibPath -/- "template-hsc.h") <~ return (pkgPath hsc2hs) - "//c/sm/Evac_thr.c" %> copyFile (pkgPath rts -/- "sm/Evac.c") - "//c/sm/Scav_thr.c" %> copyFile (pkgPath rts -/- "sm/Scav.c") where pattern <~ mdir = pattern %> \file -> do dir <- mdir diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs index e6e5b16..7b7a179 100644 --- a/src/Rules/Library.hs +++ b/src/Rules/Library.hs @@ -89,10 +89,7 @@ cObjects :: Context -> Action [FilePath] cObjects context = do path <- buildPath context srcs <- pkgDataList (CSrcs path) - objs <- mapM (objectPath context) srcs - return $ if way context == threaded - then objs - else filter ((`notElem` ["Evac_thr", "Scav_thr"]) . takeBaseName) objs + mapM (objectPath context) srcs extraObjects :: Context -> Action [FilePath] extraObjects context diff --git a/src/Rules/PackageData.hs b/src/Rules/PackageData.hs index 2442b03..32a9117 100644 --- a/src/Rules/PackageData.hs +++ b/src/Rules/PackageData.hs @@ -75,12 +75,10 @@ packageCSources pkg | pkg /= rts = getDirectoryFiles (pkgPath pkg) ["*.c"] | otherwise = do windows <- windowsHost - rtsPath <- rtsBuildPath sources <- fmap (map unifyPath) . getDirectoryFiles (pkgPath pkg) . map (-/- "*.c") $ [ ".", "hooks", "sm", "eventlog", "linker" ] ++ [ if windows then "win32" else "posix" ] - return $ sources ++ [ rtsPath -/- "c/sm/Evac_thr.c" ] - ++ [ rtsPath -/- "c/sm/Scav_thr.c" ] + return sources packageAsmSources :: Package -> Action [FilePath] packageAsmSources pkg diff --git a/src/Settings/Builders/RunTest.hs b/src/Settings/Builders/RunTest.hs index 1f70a03..3094e8d 100644 --- a/src/Settings/Builders/RunTest.hs +++ b/src/Settings/Builders/RunTest.hs @@ -1,12 +1,10 @@ module Settings.Builders.RunTest (runTestBuilderArgs) where import Hadrian.Utilities -import Hadrian.Haskell.Cabal import Flavour import Rules.Test import Settings.Builders.Common -import Settings.Builders.Ghc import CommandLine ( TestArgs(..), defaultTestArgs ) -- Arguments to send to the runtest.py script. diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs index 7b3bb2d..fcbd795 100644 --- a/src/Settings/Packages/Rts.hs +++ b/src/Settings/Packages/Rts.hs @@ -59,11 +59,13 @@ rtsLibffiLibrary way = do -- This apparently doesn't work on OS X (Darwin) nor on Solaris. -- On Darwin we get errors of the form -- --- ld: absolute addressing (perhaps -mdynamic-no-pic) used in _stg_ap_0_fast from rts/dist/build/Apply.dyn_o not allowed in slidable image +-- ld: absolute addressing (perhaps -mdynamic-no-pic) used in _stg_ap_0_fast +-- from rts/dist/build/Apply.dyn_o not allowed in slidable image -- -- and lots of these warnings: -- --- ld: warning codegen in _stg_ap_pppv_fast (offset 0x0000005E) prevents image from loading in dyld shared cache +-- ld: warning codegen in _stg_ap_pppv_fast (offset 0x0000005E) prevents image +-- from loading in dyld shared cache -- -- On Solaris we get errors like: -- @@ -75,7 +77,7 @@ rtsLibffiLibrary way = do -- collect2: ld returned 1 exit status speedHack :: Action Bool speedHack = do - i386 <- anyTargetArch ["i386"] + i386 <- anyTargetArch ["i386"] goodOS <- not <$> anyTargetOs ["darwin", "solaris2"] return $ i386 && goodOS @@ -171,9 +173,6 @@ rtsPackageArgs = package rts ? do , (not <$> flag GccIsClang) ? inputs ["//Compact.c"] ? arg "-finline-limit=2500" - , inputs ["//Evac_thr.c", "//Scav_thr.c"] ? - pure ["-DPARALLEL_GC", "-Irts/sm"] - , input "//StgCRun.c" ? windowsHost ? arg "-Wno-return-local-addr" , input "//RetainerProfile.c" ? flag GccIsClang ? arg "-Wno-incompatible-pointer-types" @@ -183,8 +182,7 @@ rtsPackageArgs = package rts ? do , inputs [ "//Interpreter.c", "//Storage.c", "//Adjustor.c" ] ? arg "-Wno-strict-prototypes" , inputs ["//Interpreter.c", "//Adjustor.c", "//sm/Storage.c"] ? - anyTargetArch ["powerpc"] ? arg "-Wno-undef" - ] + anyTargetArch ["powerpc"] ? arg "-Wno-undef" ] mconcat [ builder (Cc FindCDependencies) ? cArgs From git at git.haskell.org Sat Feb 24 15:11:26 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 24 Feb 2018 15:11:26 +0000 (UTC) Subject: [commit: hadrian] master: Merge pull request #500 from snowleopard/runtime-deps (8ffd5bd) Message-ID: <20180224151126.8FE443A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hadrian On branch : master Link : http://git.haskell.org/hadrian.git/commitdiff/8ffd5bd970646998967306a708ac6c7ea0f0dc4a >--------------------------------------------------------------- commit 8ffd5bd970646998967306a708ac6c7ea0f0dc4a Merge: fd51234 81f180a Author: Andrey Mokhov Date: Fri Feb 9 11:22:05 2018 +0000 Merge pull request #500 from snowleopard/runtime-deps Add support for runtime dependencies >--------------------------------------------------------------- 8ffd5bd970646998967306a708ac6c7ea0f0dc4a src/Base.hs | 54 +++++++++++++++++++++++++--------------- src/Builder.hs | 38 +++++++++++++++++++++------- src/GHC.hs | 20 +-------------- src/Hadrian/Builder.hs | 22 ++++++++++------ src/Rules/Documentation.hs | 8 +----- src/Rules/Install.hs | 15 ++++++++++- src/Rules/Test.hs | 7 ++---- src/Settings/Builders/Ghc.hs | 13 +--------- src/Settings/Builders/Hsc2Hs.hs | 1 - src/Settings/Builders/RunTest.hs | 12 ++++----- 10 files changed, 102 insertions(+), 88 deletions(-) From git at git.haskell.org Sat Feb 24 15:11:28 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 24 Feb 2018 15:11:28 +0000 (UTC) Subject: [commit: hadrian] master: Relax Cabal constraint (5029444) Message-ID: <20180224151128.952E03A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hadrian On branch : master Link : http://git.haskell.org/hadrian.git/commitdiff/502944442d00a4dd592a28bcf72b7681f6ad6bde >--------------------------------------------------------------- commit 502944442d00a4dd592a28bcf72b7681f6ad6bde Author: Moritz Angermann Date: Thu Feb 15 18:29:19 2018 +0800 Relax Cabal constraint As the Cabal 2.2 release branch has been cut, we need to relax the constraint on Cabal in hadrian. >--------------------------------------------------------------- 502944442d00a4dd592a28bcf72b7681f6ad6bde hadrian.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/hadrian.cabal b/hadrian.cabal index 0405601..3eeaf71 100644 --- a/hadrian.cabal +++ b/hadrian.cabal @@ -118,7 +118,7 @@ executable hadrian other-extensions: MultiParamTypeClasses , TypeFamilies build-depends: base >= 4.8 && < 5 - , Cabal >= 2.1.0.0 && < 2.2 + , Cabal >= 2.1.0.0 && < 2.3 , containers == 0.5.* , directory >= 1.2 && < 1.4 , extra >= 1.4.7 From git at git.haskell.org Sat Feb 24 15:11:22 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 24 Feb 2018 15:11:22 +0000 (UTC) Subject: [commit: hadrian] master: Minor revision (63b9d5f) Message-ID: <20180224151122.851723A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hadrian On branch : master Link : http://git.haskell.org/hadrian.git/commitdiff/63b9d5f0676f5accad2032b1853722dde51d5ee6 >--------------------------------------------------------------- commit 63b9d5f0676f5accad2032b1853722dde51d5ee6 Author: Andrey Mokhov Date: Fri Feb 9 02:23:44 2018 +0000 Minor revision >--------------------------------------------------------------- 63b9d5f0676f5accad2032b1853722dde51d5ee6 src/Base.hs | 32 ++++++++++++++++---------------- src/Rules/Test.hs | 4 +--- src/Settings/Builders/Hsc2Hs.hs | 1 - src/Settings/Builders/RunTest.hs | 12 ++++++------ 4 files changed, 23 insertions(+), 26 deletions(-) diff --git a/src/Base.hs b/src/Base.hs index 6bfa460..c3cb353 100644 --- a/src/Base.hs +++ b/src/Base.hs @@ -70,6 +70,18 @@ configH = "mk/config.h" shakeFilesDir :: FilePath shakeFilesDir = "hadrian" +-- | Directory for binaries that are built "in place". +inplaceBinPath :: FilePath +inplaceBinPath = "inplace/bin" + +-- | Directory for libraries that are built "in place". +inplaceLibPath :: FilePath +inplaceLibPath = "inplace/lib" + +-- | Directory for binary wrappers, and auxiliary binaries such as @touchy at . +inplaceLibBinPath :: FilePath +inplaceLibBinPath = inplaceLibPath -/- "bin" + -- | The directory in 'buildRoot' containing generated source files that are not -- package-specific, e.g. @ghcplatform.h at . generatedDir :: FilePath @@ -81,7 +93,7 @@ stage0PackageDbDir = "stage0/bootstrapping.conf" -- | Path to the inplace package database used in 'Stage1' and later. inplacePackageDbPath :: FilePath -inplacePackageDbPath = "inplace/lib/package.conf.d" +inplacePackageDbPath = inplaceLibPath -/- "package.conf.d" -- | Path to the package database used in a given 'Stage'. packageDbPath :: Stage -> Action FilePath @@ -92,21 +104,8 @@ packageDbPath _ = return inplacePackageDbPath packageDbStamp :: FilePath packageDbStamp = ".stamp" --- | Directory for binaries that are built "in place". -inplaceBinPath :: FilePath -inplaceBinPath = "inplace/bin" - --- | Directory for libraries that are built "in place". -inplaceLibPath :: FilePath -inplaceLibPath = "inplace/lib" - --- | Directory for binary wrappers, and auxiliary binaries such as @touchy at . -inplaceLibBinPath :: FilePath -inplaceLibBinPath = inplaceLibPath -/- "bin" - --- ref: ghc/ghc.mk:142 --- ref: driver/ghc.mk --- ref: utils/hsc2hs/ghc.mk:35 +-- ref: GHC_DEPENDENCIES in ghc/ghc.mk +-- ref: INSTALL_LIBS in driver/ghc.mk -- TODO: Derive this from Builder.runtimeDependencies -- | Files that need to be copied over to 'inplaceLibPath'. inplaceLibCopyTargets :: [FilePath] @@ -125,6 +124,7 @@ inplaceLibCopyTargets = map (inplaceLibPath -/-) haddockHtmlResourcesStamp :: FilePath haddockHtmlResourcesStamp = inplaceLibPath -/- "html/README.md" +-- ref: utils/hsc2hs/ghc.mk -- | Path to 'hsc2hs' template. templateHscPath :: FilePath templateHscPath = inplaceLibPath -/- "template-hsc.h" diff --git a/src/Rules/Test.hs b/src/Rules/Test.hs index 0fedd70..1205051 100644 --- a/src/Rules/Test.hs +++ b/src/Rules/Test.hs @@ -35,11 +35,9 @@ testRules = do "validate" ~> do needBuilder $ Ghc CompileHs Stage2 needBuilder $ GhcPkg Update Stage1 + needBuilder Hp2Ps needBuilder Hpc needBuilder Hsc2Hs - -- TODO: Eliminate explicit filepaths. - -- See https://github.com/snowleopard/hadrian/issues/376. - need ["inplace/bin/hp2ps"] build $ target (vanillaContext Stage2 compiler) (Make "testsuite/tests") [] [] "test" ~> do diff --git a/src/Settings/Builders/Hsc2Hs.hs b/src/Settings/Builders/Hsc2Hs.hs index 6185f6b..80e80db 100644 --- a/src/Settings/Builders/Hsc2Hs.hs +++ b/src/Settings/Builders/Hsc2Hs.hs @@ -28,7 +28,6 @@ hsc2hsBuilderArgs = builder Hsc2Hs ? do , notStage0 ? arg ("--cflag=-D" ++ tOs ++ "_HOST_OS=1" ) , arg $ "--cflag=-D__GLASGOW_HASKELL__=" ++ version , arg $ "--template=" ++ top -/- templateHscPath - , arg $ "-I" ++ top -/- "inplace/lib/include/" , arg =<< getInput , arg "-o", arg =<< getOutput ] diff --git a/src/Settings/Builders/RunTest.hs b/src/Settings/Builders/RunTest.hs index 3094e8d..c348bf1 100644 --- a/src/Settings/Builders/RunTest.hs +++ b/src/Settings/Builders/RunTest.hs @@ -2,10 +2,10 @@ module Settings.Builders.RunTest (runTestBuilderArgs) where import Hadrian.Utilities +import CommandLine (TestArgs(..), defaultTestArgs) import Flavour import Rules.Test import Settings.Builders.Common -import CommandLine ( TestArgs(..), defaultTestArgs ) -- Arguments to send to the runtest.py script. runTestBuilderArgs :: Args @@ -29,11 +29,11 @@ runTestBuilderArgs = builder RunTest ? do verbose <- shakeVerbosity <$> expr getShakeOptions top <- expr topDirectory - compiler <- expr $ builderPath $ Ghc CompileHs Stage2 - ghcPkg <- expr $ builderPath $ GhcPkg Update Stage1 - haddock <- expr $ builderPath $ Haddock BuildPackage - hp2ps <- expr $ builderPath $ Hp2Ps - hpc <- expr $ builderPath $ Hpc + compiler <- getBuilderPath $ Ghc CompileHs Stage2 + ghcPkg <- getBuilderPath $ GhcPkg Update Stage1 + haddock <- getBuilderPath $ Haddock BuildPackage + hp2ps <- getBuilderPath $ Hp2Ps + hpc <- getBuilderPath $ Hpc ghcFlags <- expr runTestGhcFlags timeoutProg <- expr buildRoot <&> (-/- timeoutProgPath) From git at git.haskell.org Sat Feb 24 15:11:30 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 24 Feb 2018 15:11:30 +0000 (UTC) Subject: [commit: hadrian] master: Merge pull request #503 from snowleopard/angerman-patch-1 (7805b98) Message-ID: <20180224151130.9AC3C3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hadrian On branch : master Link : http://git.haskell.org/hadrian.git/commitdiff/7805b98a95710e4a5b0b7d4fd528825cd903998c >--------------------------------------------------------------- commit 7805b98a95710e4a5b0b7d4fd528825cd903998c Merge: 8ffd5bd 5029444 Author: Andrey Mokhov Date: Thu Feb 15 11:48:57 2018 +0000 Merge pull request #503 from snowleopard/angerman-patch-1 Relax Cabal constraint >--------------------------------------------------------------- 7805b98a95710e4a5b0b7d4fd528825cd903998c hadrian.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) From git at git.haskell.org Sat Feb 24 15:11:32 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 24 Feb 2018 15:11:32 +0000 (UTC) Subject: [commit: hadrian] master: Add iserv library (#504) (386cd49) Message-ID: <20180224151132.A012F3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hadrian On branch : master Link : http://git.haskell.org/hadrian.git/commitdiff/386cd490356daabea2d9fd4bd09c929517d7acb4 >--------------------------------------------------------------- commit 386cd490356daabea2d9fd4bd09c929517d7acb4 Author: Andrey Mokhov Date: Sat Feb 17 00:18:01 2018 +0000 Add iserv library (#504) See https://phabricator.haskell.org/D4377 >--------------------------------------------------------------- 386cd490356daabea2d9fd4bd09c929517d7acb4 src/GHC.hs | 20 +++++++++++--------- 1 file changed, 11 insertions(+), 9 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index 771d37e..e14cdb6 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -5,9 +5,9 @@ module GHC ( deepseq, deriveConstants, directory, filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghcCompact, ghci, ghcPkg, ghcPrim, ghcTags, ghcSplit, haddock, haskeline, hsc2hs, hp2ps, hpc, hpcBin, integerGmp, - integerSimple, iservBin, libffi, mtl, parsec, parallel, pretty, primitive, - process, rts, runGhc, stm, templateHaskell, terminfo, text, time, touchy, - transformers, unlit, unix, win32, xhtml, ghcPackages, isGhcPackage, + integerSimple, iservBin, iservLib, libffi, mtl, parsec, parallel, pretty, + primitive, process, rts, runGhc, stm, templateHaskell, terminfo, text, time, + touchy, transformers, unlit, unix, win32, xhtml, ghcPackages, isGhcPackage, defaultPackages, -- * Package information @@ -34,9 +34,9 @@ ghcPackages = , deepseq, deriveConstants, directory, filepath, genapply, genprimopcode , ghc, ghcBoot, ghcBootTh, ghcCabal, ghcCompact, ghci, ghcPkg, ghcPrim , ghcTags, haddock, haskeline, hsc2hs, hp2ps, hpc, hpcBin, integerGmp - , integerSimple, iservBin, libffi, mtl, parsec, parallel, pretty, primitive - , process, rts, runGhc, stm, templateHaskell, terminfo, text, time, touchy - , transformers, unlit, unix, win32, xhtml ] + , integerSimple, iservBin, iservLib, libffi, mtl, parsec, parallel, pretty + , primitive, process, rts, runGhc, stm, templateHaskell, terminfo, text + , time, touchy, transformers, unlit, unix, win32, xhtml ] -- TODO: Optimise by switching to sets of packages. isGhcPackage :: Package -> Bool @@ -75,7 +75,8 @@ hpc = hsLib "hpc" hpcBin = hsUtil "hpc-bin" `setPath` "utils/hpc" integerGmp = hsLib "integer-gmp" integerSimple = hsLib "integer-simple" -iservBin = hsPrg "iserv-bin" `setPath` "iserv" +iservBin = hsUtil "iserv" +iservLib = hsLib "libiserv" libffi = cTop "libffi" mtl = hsLib "mtl" parsec = hsLib "parsec" @@ -159,9 +160,9 @@ stage0Packages = do , templateHaskell , text , transformers - , unlit ] + , unlit ] ++ [ terminfo | not win, not ios, not cross ] - ++ [ touchy | win ] + ++ [ touchy | win ] stage1Packages :: Action [Package] stage1Packages = do @@ -192,6 +193,7 @@ stage1Packages = do , time , xhtml ] ++ [ iservBin | not win ] + ++ [ iservLib | not win ] ++ [ unix | not win ] ++ [ win32 | win ] From git at git.haskell.org Sat Feb 24 15:11:34 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 24 Feb 2018 15:11:34 +0000 (UTC) Subject: [commit: hadrian] master: Add --quickjump to Haddock (#505) (2e0e8ae) Message-ID: <20180224151134.A40E83A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hadrian On branch : master Link : http://git.haskell.org/hadrian.git/commitdiff/2e0e8aeb27ac9ac7a1746350c2ef782d29bf7c89 >--------------------------------------------------------------- commit 2e0e8aeb27ac9ac7a1746350c2ef782d29bf7c89 Author: Andrey Mokhov Date: Sun Feb 18 20:17:11 2018 +0000 Add --quickjump to Haddock (#505) Also reorder other flags as in the Make build system See https://phabricator.haskell.org/D4365 >--------------------------------------------------------------- 2e0e8aeb27ac9ac7a1746350c2ef782d29bf7c89 src/Settings/Builders/Haddock.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/src/Settings/Builders/Haddock.hs b/src/Settings/Builders/Haddock.hs index b381047..ed29012 100644 --- a/src/Settings/Builders/Haddock.hs +++ b/src/Settings/Builders/Haddock.hs @@ -39,13 +39,14 @@ haddockBuilderArgs = withHsPackage $ \cabalFile -> mconcat hVersion <- expr $ pkgVersion (unsafePkgCabalFile haddock) -- TODO: improve ghcOpts <- haddockGhcArgs mconcat - [ arg $ "--odir=" ++ takeDirectory output - , arg "--verbosity=0" + [ arg "--verbosity=0" + , arg $ "--odir=" ++ takeDirectory output , arg "--no-tmp-comp-dir" , arg $ "--dump-interface=" ++ output , arg "--html" , arg "--hyperlinked-source" , arg "--hoogle" + , arg "--quickjump" , arg $ "--title=" ++ pkgName pkg ++ "-" ++ version ++ ": " ++ synopsis , arg $ "--prologue=" ++ path -/- "haddock-prologue.txt" From git at git.haskell.org Sat Feb 24 15:11:36 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 24 Feb 2018 15:11:36 +0000 (UTC) Subject: [commit: hadrian] master: Move a bunch of types into dedicated modules (#502) (cc8f62c) Message-ID: <20180224151136.B030E3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hadrian On branch : master Link : http://git.haskell.org/hadrian.git/commitdiff/cc8f62c0f6438bc342d9f49bf38629591c793ff1 >--------------------------------------------------------------- commit cc8f62c0f6438bc342d9f49bf38629591c793ff1 Author: Alp Mestanogullari Date: Mon Feb 19 21:23:10 2018 +0100 Move a bunch of types into dedicated modules (#502) * move a bunch of types into dedicated modules * address review feedback * do away with Hadrian.Builder.Mode for now >--------------------------------------------------------------- cc8f62c0f6438bc342d9f49bf38629591c793ff1 hadrian.cabal | 5 +++ src/Context.hs | 14 +------ src/Context/Type.hs | 20 +++++++++ src/Expression.hs | 18 ++------ src/Expression/Type.hs | 17 ++++++++ src/Hadrian/Builder/Tar.hs | 1 + src/Hadrian/Haskell/Cabal/Parse.hs | 22 +--------- src/Hadrian/Haskell/Cabal/Type.hs | 23 +++++++++++ src/Hadrian/Package.hs | 44 +------------------- src/Hadrian/Package/Type.hs | 45 ++++++++++++++++++++ src/Way.hs | 83 +------------------------------------ src/Way/Type.hs | 84 ++++++++++++++++++++++++++++++++++++++ 12 files changed, 202 insertions(+), 174 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc cc8f62c0f6438bc342d9f49bf38629591c793ff1 From git at git.haskell.org Sat Feb 24 15:11:38 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 24 Feb 2018 15:11:38 +0000 (UTC) Subject: [commit: hadrian] master: Fix ghc-cabal: Parsec modules are now found in libraries/parsec/src (#506) (7fa577c) Message-ID: <20180224151138.B572B3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hadrian On branch : master Link : http://git.haskell.org/hadrian.git/commitdiff/7fa577c2322e0efc147a007a4edcf5849802e8b2 >--------------------------------------------------------------- commit 7fa577c2322e0efc147a007a4edcf5849802e8b2 Author: Ben Gamari Date: Tue Feb 20 09:05:55 2018 -0500 Fix ghc-cabal: Parsec modules are now found in libraries/parsec/src (#506) This has been the case since haskell/parsec at 89d4541. >--------------------------------------------------------------- 7fa577c2322e0efc147a007a4edcf5849802e8b2 src/Settings/Packages/GhcCabal.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Settings/Packages/GhcCabal.hs b/src/Settings/Packages/GhcCabal.hs index c88617b..70f2449 100644 --- a/src/Settings/Packages/GhcCabal.hs +++ b/src/Settings/Packages/GhcCabal.hs @@ -28,5 +28,5 @@ ghcCabalPackageArgs = stage0 ? package ghcCabal ? builder Ghc ? do , arg "-ilibraries/mtl" , arg "-ilibraries/text" , arg "-Ilibraries/text/include" - , arg "-ilibraries/parsec" ] + , arg "-ilibraries/parsec/src" ] From git at git.haskell.org Sat Feb 24 15:11:40 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 24 Feb 2018 15:11:40 +0000 (UTC) Subject: [commit: hadrian] master: Undo iserv changes (#507) (5edcca7) Message-ID: <20180224151140.BA4313A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hadrian On branch : master Link : http://git.haskell.org/hadrian.git/commitdiff/5edcca746578c798bed34c3bf84ede39fc91c265 >--------------------------------------------------------------- commit 5edcca746578c798bed34c3bf84ede39fc91c265 Author: Andrey Mokhov Date: Tue Feb 20 21:05:09 2018 +0000 Undo iserv changes (#507) * Undo iserv changes See #504 and https://phabricator.haskell.org/D4377 * Update comments >--------------------------------------------------------------- 5edcca746578c798bed34c3bf84ede39fc91c265 src/GHC.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/src/GHC.hs b/src/GHC.hs index e14cdb6..2a87d68 100644 --- a/src/GHC.hs +++ b/src/GHC.hs @@ -75,7 +75,8 @@ hpc = hsLib "hpc" hpcBin = hsUtil "hpc-bin" `setPath` "utils/hpc" integerGmp = hsLib "integer-gmp" integerSimple = hsLib "integer-simple" -iservBin = hsUtil "iserv" +-- iservBin = hsUtil "iserv" -- FIXME: See #507 +iservBin = hsPrg "iserv-bin" `setPath` "iserv" iservLib = hsLib "libiserv" libffi = cTop "libffi" mtl = hsLib "mtl" @@ -193,7 +194,7 @@ stage1Packages = do , time , xhtml ] ++ [ iservBin | not win ] - ++ [ iservLib | not win ] + -- ++ [ iservLib | not win ] -- FIXME: See #507 ++ [ unix | not win ] ++ [ win32 | win ] From git at git.haskell.org Sat Feb 24 15:11:42 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 24 Feb 2018 15:11:42 +0000 (UTC) Subject: [commit: hadrian] master: Add --configure flag to the script (b6d83c4) Message-ID: <20180224151142.BDF6C3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hadrian On branch : master Link : http://git.haskell.org/hadrian.git/commitdiff/b6d83c4b12abfaa416f62e95bd8f3d610e4adeac >--------------------------------------------------------------- commit b6d83c4b12abfaa416f62e95bd8f3d610e4adeac Author: Andrey Mokhov Date: Thu Feb 22 18:55:36 2018 +0000 Add --configure flag to the script See #508 >--------------------------------------------------------------- b6d83c4b12abfaa416f62e95bd8f3d610e4adeac doc/windows.md | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/doc/windows.md b/doc/windows.md index b374074..0ad2086 100644 --- a/doc/windows.md +++ b/doc/windows.md @@ -22,7 +22,8 @@ stack exec -- pacman -S autoconf automake-wrapper make patch python tar --noconf stack build # Build GHC -stack exec hadrian -- --directory ".." -j --flavour=quickest +# Note that the --configure flag is required only for the first build +stack exec hadrian -- --directory ".." -j --flavour=quickest --configure # Test GHC cd .. From git at git.haskell.org Sat Feb 24 15:11:44 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 24 Feb 2018 15:11:44 +0000 (UTC) Subject: [commit: hadrian] master: Make shell.nix less broken (#510) (da39729) Message-ID: <20180224151144.C2BE13A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/hadrian On branch : master Link : http://git.haskell.org/hadrian.git/commitdiff/da397291a9052387862c27c87ec29b6fce2c7d77 >--------------------------------------------------------------- commit da397291a9052387862c27c87ec29b6fce2c7d77 Author: Sebastian Graf Date: Fri Feb 23 16:50:23 2018 +0100 Make shell.nix less broken (#510) * shell.nix: Use ghc822 (ghc821 is no longer available) * shell.nix: It's nativeBuildInputs now * shell.nix: ./validate needs sphinx to be available >--------------------------------------------------------------- da397291a9052387862c27c87ec29b6fce2c7d77 shell.nix | 13 +++++++------ 1 file changed, 7 insertions(+), 6 deletions(-) diff --git a/shell.nix b/shell.nix index f15f72b..d8767cd 100644 --- a/shell.nix +++ b/shell.nix @@ -5,7 +5,7 @@ { nixpkgs ? import {} }: let - haskellPackages = nixpkgs.haskell.packages.ghc821; + haskellPackages = nixpkgs.haskell.packages.ghc822; removeBuild = path: type: let baseName = baseNameOf (toString path); @@ -23,7 +23,7 @@ let filterSrc = path: builtins.filterSource removeBuild path; - hadrianPackages = nixpkgs.haskell.packages.ghc821.override { + hadrianPackages = nixpkgs.haskell.packages.ghc822.override { overrides = self: super: let localPackage = name: path: self.callCabal2nix name (filterSrc path) {}; in { @@ -43,9 +43,10 @@ in nixpkgs.lib.overrideDerivation nixpkgs.haskell.packages.ghcHEAD.ghc (drv: { name = "ghc-dev"; - buildInputs = drv.buildInputs ++ [ - hadrianPackages.hadrian - nixpkgs.arcanist - ]; + nativeBuildInputs = drv.nativeBuildInputs ++ + [ hadrianPackages.hadrian + nixpkgs.arcanist + nixpkgs.python3Packages.sphinx + ]; }) From git at git.haskell.org Sat Feb 24 15:12:28 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 24 Feb 2018 15:12:28 +0000 (UTC) Subject: [commit: ghc] master: Update Hadrian submodule (bf3f0a6) Message-ID: <20180224151228.DE1FC3A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bf3f0a6808b89504a993dc9f2839daff9eaf6f2a/ghc >--------------------------------------------------------------- commit bf3f0a6808b89504a993dc9f2839daff9eaf6f2a Author: Andrey Mokhov Date: Sat Feb 24 15:00:22 2018 +0000 Update Hadrian submodule * Make shell.nix less broken (hadrian/510) * Add --configure flag to the script * Undo iserv changes (hadrian/507) * Fix ghc-cabal: Parsec modules are now found in libraries/parsec/src (hadrian/506) * Move a bunch of types into dedicated modules (hadrian/502) * Add --quickjump to Haddock (hadrian/505) * Add iserv library (hadrian/504) * Merge pull request hadrian/503 from snowleopard/angerman-patch-1 * Merge pull request hadrian/500 from snowleopard/runtime-deps * Fix Hadrian after Cabal changes (hadrian/498) * Drop custom logic for Scav_thr and Evac_thr (hadrian/497) * Fix Haddock (hadrian/496) >--------------------------------------------------------------- bf3f0a6808b89504a993dc9f2839daff9eaf6f2a hadrian | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/hadrian b/hadrian index 63a5563..da39729 160000 --- a/hadrian +++ b/hadrian @@ -1 +1 @@ -Subproject commit 63a556382f4b3154ed2ce3a6c8a36f79d9b8e3b1 +Subproject commit da397291a9052387862c27c87ec29b6fce2c7d77 From git at git.haskell.org Sat Feb 24 17:23:14 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 24 Feb 2018 17:23:14 +0000 (UTC) Subject: [commit: ghc] ghc-8.4: Bump unix submodule back to 2.7 (a1e15c8) Message-ID: <20180224172314.309C23A5EE@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.4 Link : http://ghc.haskell.org/trac/ghc/changeset/a1e15c8f59092ef2d11be7966bd20688d8dc01e6/ghc >--------------------------------------------------------------- commit a1e15c8f59092ef2d11be7966bd20688d8dc01e6 Author: Ben Gamari Date: Fri Feb 23 16:57:33 2018 -0500 Bump unix submodule back to 2.7 >--------------------------------------------------------------- a1e15c8f59092ef2d11be7966bd20688d8dc01e6 libraries/unix | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/unix b/libraries/unix index 41c5776..3172ec8 160000 --- a/libraries/unix +++ b/libraries/unix @@ -1 +1 @@ -Subproject commit 41c5776162b60e0739a7559ceab03b9c3a444516 +Subproject commit 3172ec893026869d1a458cf067790fce3b1e3eef From git at git.haskell.org Sun Feb 25 21:57:36 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 25 Feb 2018 21:57:36 +0000 (UTC) Subject: [commit: ghc] master: Introduce the flag -dsuppress-timestamps to avoid timestamps in dumps. (3d43fd5) Message-ID: <20180225215736.C24AF3A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3d43fd5b816a980d650d98f5822831dfce38f658/ghc >--------------------------------------------------------------- commit 3d43fd5b816a980d650d98f5822831dfce38f658 Author: Andreas Klebinger Date: Tue Feb 20 13:19:19 2018 -0500 Introduce the flag -dsuppress-timestamps to avoid timestamps in dumps. This makes it easier to diff dumps which are otherwise identical. Also updated the description of -dsuppress-all as parts of these also apply to stages other than core. Test Plan: Looking at dump result. Reviewers: bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4429 >--------------------------------------------------------------- 3d43fd5b816a980d650d98f5822831dfce38f658 compiler/main/DynFlags.hs | 8 ++++++-- compiler/main/ErrUtils.hs | 9 ++++++--- docs/users_guide/debugging.rst | 9 ++++++++- 3 files changed, 20 insertions(+), 6 deletions(-) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 01432b6..b7720dd 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -583,6 +583,7 @@ data GeneralFlag | Opt_SuppressUniques | Opt_SuppressStgFreeVars | Opt_SuppressTicks -- Replaces Opt_PprShowTicks + | Opt_SuppressTimestamps -- ^ Suppress timestamps in dumps -- temporary flags | Opt_AutoLinkPackages @@ -3040,7 +3041,8 @@ dynamic_flags_deps = [ setGeneralFlag Opt_SuppressIdInfo setGeneralFlag Opt_SuppressTicks setGeneralFlag Opt_SuppressStgFreeVars - setGeneralFlag Opt_SuppressTypeSignatures) + setGeneralFlag Opt_SuppressTypeSignatures + setGeneralFlag Opt_SuppressTimestamps) ------ Debugging ---------------------------------------------------- , make_ord_flag defGhcFlag "dstg-stats" @@ -3835,10 +3837,12 @@ dFlagsDeps = [ flagSpec "suppress-idinfo" Opt_SuppressIdInfo, flagSpec "suppress-unfoldings" Opt_SuppressUnfoldings, flagSpec "suppress-module-prefixes" Opt_SuppressModulePrefixes, + flagSpec "suppress-timestamps" Opt_SuppressTimestamps, flagSpec "suppress-type-applications" Opt_SuppressTypeApplications, flagSpec "suppress-type-signatures" Opt_SuppressTypeSignatures, flagSpec "suppress-uniques" Opt_SuppressUniques, - flagSpec "suppress-var-kinds" Opt_SuppressVarKinds] + flagSpec "suppress-var-kinds" Opt_SuppressVarKinds + ] -- | These @-f\@ flags can all be reversed with @-fno-\@ fFlags :: [FlagSpec GeneralFlag] diff --git a/compiler/main/ErrUtils.hs b/compiler/main/ErrUtils.hs index 13ff017..c7fb8ba 100644 --- a/compiler/main/ErrUtils.hs +++ b/compiler/main/ErrUtils.hs @@ -500,9 +500,12 @@ dumpSDoc dflags print_unqual flag hdr doc = doc' <- if null hdr then return doc else do t <- getCurrentTime - let d = text (show t) - $$ blankLine - $$ doc + let timeStamp = if (gopt Opt_SuppressTimestamps dflags) + then empty + else text (show t) + let d = timeStamp + $$ blankLine + $$ doc return $ mkDumpDoc hdr d defaultLogActionHPrintDoc dflags handle doc' dump_style diff --git a/docs/users_guide/debugging.rst b/docs/users_guide/debugging.rst index cf92634..d11cc04 100644 --- a/docs/users_guide/debugging.rst +++ b/docs/users_guide/debugging.rst @@ -612,7 +612,7 @@ are doing, not all of it will be useful. Use these flags to suppress the parts that you are not interested in. .. ghc-flag:: -dsuppress-all - :shortdesc: In core dumps, suppress everything (except for uniques) that is + :shortdesc: In dumps, suppress everything (except for uniques) that is suppressible. :type: dynamic @@ -663,6 +663,13 @@ parts that you are not interested in. Suppress the printing of module qualification prefixes. This is the ``Data.List`` in ``Data.List.length``. +.. ghc-flag:: -dsuppress-timestamps + :shortdesc: Suppress timestamps in dumps + :type: dynamic + + Suppress the printing of timestamps. + This makes it easier to diff dumps. + .. ghc-flag:: -dsuppress-type-signatures :shortdesc: Suppress type signatures :type: dynamic From git at git.haskell.org Sun Feb 25 21:57:39 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 25 Feb 2018 21:57:39 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Bump allocations for T9630 (f57c305) Message-ID: <20180225215739.916993A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f57c3059d7c8b8e00bd3a9f9153c3520f6db14d4/ghc >--------------------------------------------------------------- commit f57c3059d7c8b8e00bd3a9f9153c3520f6db14d4 Author: Ben Gamari Date: Sun Feb 25 16:23:39 2018 -0500 testsuite: Bump allocations for T9630 >--------------------------------------------------------------- f57c3059d7c8b8e00bd3a9f9153c3520f6db14d4 testsuite/tests/perf/compiler/all.T | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index 1ae69e7..1a2413a 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -1228,9 +1228,10 @@ test ('T9630', [ compiler_stats_num_field('max_bytes_used', # Note [residency] [(platform('x86_64-unknown-mingw32'), 39867088, 15), # 2017-12-24: 34171816 (x64/Windows) - (wordsize(64), 41568168, 15) + (wordsize(64), 35324712, 15) # initial: 56955240 # 2017-06-07: 41568168 Stop the specialiser generating loopy code + # 2018-02-25: 35324712 It's not entirely clear ]), extra_clean(['T9630a.hi', 'T9630a.o']) ], From git at git.haskell.org Sun Feb 25 21:57:42 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 25 Feb 2018 21:57:42 +0000 (UTC) Subject: [commit: ghc] master: driver/utils/dynwrapper.c: Remove unused variable (c969c98) Message-ID: <20180225215742.6202E3A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c969c987ab63db29f305f9a0fd2047bc8156f309/ghc >--------------------------------------------------------------- commit c969c987ab63db29f305f9a0fd2047bc8156f309 Author: Simon Jakobi Date: Tue Feb 20 13:17:27 2018 -0500 driver/utils/dynwrapper.c: Remove unused variable The variable was already unused when the file was introduced in b35a6ce0e34255d200ddcf341ffc645fd237ea32. Reviewers: bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #11777 Differential Revision: https://phabricator.haskell.org/D4426 >--------------------------------------------------------------- c969c987ab63db29f305f9a0fd2047bc8156f309 driver/utils/dynwrapper.c | 1 - 1 file changed, 1 deletion(-) diff --git a/driver/utils/dynwrapper.c b/driver/utils/dynwrapper.c index a9250f5..7fb06e5 100644 --- a/driver/utils/dynwrapper.c +++ b/driver/utils/dynwrapper.c @@ -155,7 +155,6 @@ HINSTANCE GetNonNullModuleHandle(LPTSTR dll) { typedef int (*hs_main_t)(int , char **, StgClosure *, RtsConfig); int main(int argc, char *argv[]) { - void *p; HINSTANCE hRtsDll, hProgDll; LPTSTR oldPath; From git at git.haskell.org Sun Feb 25 21:57:45 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 25 Feb 2018 21:57:45 +0000 (UTC) Subject: [commit: ghc] master: RTS: Remember to free some pointers (be498a2) Message-ID: <20180225215745.44F673A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/be498a24250f637471426989b3bdf5f1b18e47bb/ghc >--------------------------------------------------------------- commit be498a24250f637471426989b3bdf5f1b18e47bb Author: Simon Jakobi Date: Tue Feb 20 13:17:50 2018 -0500 RTS: Remember to free some pointers Reviewers: bgamari, erikd, simonmar Reviewed By: bgamari, simonmar Subscribers: Phyx, rwbarton, thomie, carter GHC Trac Issues: #11777 Differential Revision: https://phabricator.haskell.org/D4428 >--------------------------------------------------------------- be498a24250f637471426989b3bdf5f1b18e47bb rts/win32/IOManager.c | 15 ++++++++++++--- 1 file changed, 12 insertions(+), 3 deletions(-) diff --git a/rts/win32/IOManager.c b/rts/win32/IOManager.c index c5cae75..216e725 100644 --- a/rts/win32/IOManager.c +++ b/rts/win32/IOManager.c @@ -437,7 +437,10 @@ AddIORequest ( int fd, { WorkItem* wItem = (WorkItem*)malloc(sizeof(WorkItem)); unsigned int reqID; - if (!ioMan || !wItem) return 0; + if (!ioMan || !wItem) { + free(wItem); + return 0; + } reqID = ioMan->requestID++; /* Fill in the blanks */ @@ -466,7 +469,10 @@ AddDelayRequest ( HsInt usecs, { WorkItem* wItem = (WorkItem*)malloc(sizeof(WorkItem)); unsigned int reqID; - if (!ioMan || !wItem) return false; + if (!ioMan || !wItem) { + free(wItem); + return false; + } reqID = ioMan->requestID++; /* Fill in the blanks */ @@ -491,7 +497,10 @@ AddProcRequest ( void* proc, { WorkItem* wItem = (WorkItem*)malloc(sizeof(WorkItem)); unsigned int reqID; - if (!ioMan || !wItem) return false; + if (!ioMan || !wItem) { + free(wItem); + return false; + } reqID = ioMan->requestID++; /* Fill in the blanks */ From git at git.haskell.org Sun Feb 25 21:57:48 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 25 Feb 2018 21:57:48 +0000 (UTC) Subject: [commit: ghc] master: boot: Create GNUmakefiles for libraries (5e5e60d) Message-ID: <20180225215748.1FA7C3A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5e5e60dd2553549d7b00f6bb0a66064f8fe13bc2/ghc >--------------------------------------------------------------- commit 5e5e60dd2553549d7b00f6bb0a66064f8fe13bc2 Author: Ben Gamari Date: Wed Feb 21 09:58:19 2018 -0500 boot: Create GNUmakefiles for libraries D3918 neglected to implement this when it rewrote boot in python. >--------------------------------------------------------------- 5e5e60dd2553549d7b00f6bb0a66064f8fe13bc2 boot | 11 +++++++++++ 1 file changed, 11 insertions(+) diff --git a/boot b/boot index 7dc2983..f913724 100755 --- a/boot +++ b/boot @@ -132,6 +132,17 @@ def boot_pkgs(): pkg = pkg, dir = dir_))) + makefile = os.path.join(package, 'GNUmakefile') + with open(makefile, 'w') as f: + f.write(dedent( + """\ + dir = {package} + TOP = {top} + include $(TOP)/mk/sub-makefile.mk + FAST_MAKE_OPTS += stage=0 + """.format(package = package, top = top) + )) + def autoreconf(): # Run autoreconf on everything that needs it. From git at git.haskell.org Sun Feb 25 21:57:50 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 25 Feb 2018 21:57:50 +0000 (UTC) Subject: [commit: ghc] master: RTS: Remove unused retainer schemes (cb89ba8) Message-ID: <20180225215750.DC9C43A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cb89ba88d42ab77f9e20d722ec1ab40ec6f8e703/ghc >--------------------------------------------------------------- commit cb89ba88d42ab77f9e20d722ec1ab40ec6f8e703 Author: Simon Jakobi Date: Tue Feb 20 13:18:52 2018 -0500 RTS: Remove unused retainer schemes Reviewers: bgamari, erikd, simonmar Reviewed By: simonmar Subscribers: rwbarton, thomie, carter GHC Trac Issues: #11777 Differential Revision: https://phabricator.haskell.org/D4427 >--------------------------------------------------------------- cb89ba88d42ab77f9e20d722ec1ab40ec6f8e703 rts/RetainerProfile.c | 9 ---- rts/RetainerSet.c | 141 -------------------------------------------------- rts/RetainerSet.h | 23 +------- 3 files changed, 1 insertion(+), 172 deletions(-) diff --git a/rts/RetainerProfile.c b/rts/RetainerProfile.c index 4badbfe..cad3bb4 100644 --- a/rts/RetainerProfile.c +++ b/rts/RetainerProfile.c @@ -1143,16 +1143,7 @@ getRetainerFrom( StgClosure *c ) { ASSERT(isRetainer(c)); -#if defined(RETAINER_SCHEME_INFO) - // Retainer scheme 1: retainer = info table - return get_itbl(c); -#elif defined(RETAINER_SCHEME_CCS) - // Retainer scheme 2: retainer = cost centre stack return c->header.prof.ccs; -#elif defined(RETAINER_SCHEME_CC) - // Retainer scheme 3: retainer = cost centre - return c->header.prof.ccs->cc; -#endif } /* ----------------------------------------------------------------------------- diff --git a/rts/RetainerSet.c b/rts/RetainerSet.c index 5808097..59103dd 100644 --- a/rts/RetainerSet.c +++ b/rts/RetainerSet.c @@ -218,82 +218,17 @@ addElement(retainer r, RetainerSet *rs) * printRetainer() prints the full information on a given retainer, * not a retainer set. * -------------------------------------------------------------------------- */ -#if defined(RETAINER_SCHEME_INFO) -// Retainer scheme 1: retainer = info table -static void -printRetainer(FILE *f, retainer itbl) -{ - fprintf(f, "%s[%s]", GET_PROF_DESC(itbl), itbl->prof.closure_type); -} -#elif defined(RETAINER_SCHEME_CCS) -// Retainer scheme 2: retainer = cost centre stack static void printRetainer(FILE *f, retainer ccs) { fprintCCS(f, ccs); } -#elif defined(RETAINER_SCHEME_CC) -// Retainer scheme 3: retainer = cost centre -static void -printRetainer(FILE *f, retainer cc) -{ - fprintf(f,"%s.%s", cc->module, cc->label); -} -#endif /* ----------------------------------------------------------------------------- * printRetainerSetShort() should always display the same output for * a given retainer set regardless of the time of invocation. * -------------------------------------------------------------------------- */ #if defined(SECOND_APPROACH) -#if defined(RETAINER_SCHEME_INFO) -// Retainer scheme 1: retainer = info table -void -printRetainerSetShort(FILE *f, RetainerSet *rs, uint32_t max_length) -{ - char tmp[max_length + 1]; - int size; - uint32_t j; - - ASSERT(rs->id < 0); - - tmp[max_length] = '\0'; - - // No blank characters are allowed. - sprintf(tmp + 0, "(%d)", -(rs->id)); - size = strlen(tmp); - ASSERT(size < max_length); - - for (j = 0; j < rs->num; j++) { - if (j < rs->num - 1) { - strncpy(tmp + size, GET_PROF_DESC(rs->element[j]), max_length - size); - size = strlen(tmp); - if (size == max_length) - break; - strncpy(tmp + size, ",", max_length - size); - size = strlen(tmp); - if (size == max_length) - break; - } - else { - strncpy(tmp + size, GET_PROF_DESC(rs->element[j]), max_length - size); - // size = strlen(tmp); - } - } - fprintf(f, tmp); -} -#elif defined(RETAINER_SCHEME_CC) -// Retainer scheme 3: retainer = cost centre -void -printRetainerSetShort(FILE *f, RetainerSet *rs, uint32_t max_length) -{ - char tmp[max_length + 1]; - int size; - uint32_t j; - -} -#elif defined(RETAINER_SCHEME_CCS) -// Retainer scheme 2: retainer = cost centre stack void printRetainerSetShort(FILE *f, RetainerSet *rs, uint32_t max_length) { @@ -328,82 +263,6 @@ printRetainerSetShort(FILE *f, RetainerSet *rs, uint32_t max_length) } fputs(tmp, f); } -#elif defined(RETAINER_SCHEME_CC) -// Retainer scheme 3: retainer = cost centre -static void -printRetainerSetShort(FILE *f, retainerSet *rs, uint32_t max_length) -{ - char tmp[max_length + 1]; - int size; - uint32_t j; - - ASSERT(rs->id < 0); - - tmp[max_length] = '\0'; - - // No blank characters are allowed. - sprintf(tmp + 0, "(%d)", -(rs->id)); - size = strlen(tmp); - ASSERT(size < max_length); - - for (j = 0; j < rs->num; j++) { - if (j < rs->num - 1) { - strncpy(tmp + size, rs->element[j]->label, - max_length - size); - size = strlen(tmp); - if (size == max_length) - break; - strncpy(tmp + size, ",", max_length - size); - size = strlen(tmp); - if (size == max_length) - break; - } - else { - strncpy(tmp + size, rs->element[j]->label, - max_length - size); - // size = strlen(tmp); - } - } - fprintf(f, tmp); -/* - #define DOT_NUMBER 3 - // 1. 32 > max_length + 1 (1 for '\0') - // 2. (max_length - DOT_NUMBER ) characters should be enough for - // printing one natural number (plus '(' and ')'). - char tmp[32]; - int size, ts; - uint32_t j; - - ASSERT(rs->id < 0); - - // No blank characters are allowed. - sprintf(tmp + 0, "(%d)", -(rs->id)); - size = strlen(tmp); - ASSERT(size < max_length - DOT_NUMBER); - - for (j = 0; j < rs->num; j++) { - ts = strlen(rs->element[j]->label); - if (j < rs->num - 1) { - if (size + ts + 1 > max_length - DOT_NUMBER) { - sprintf(tmp + size, "..."); - break; - } - sprintf(tmp + size, "%s,", rs->element[j]->label); - size += ts + 1; - } - else { - if (size + ts > max_length - DOT_NUMBER) { - sprintf(tmp + size, "..."); - break; - } - sprintf(tmp + size, "%s", rs->element[j]->label); - size += ts; - } - } - fprintf(f, tmp); -*/ -} -#endif /* RETAINER_SCHEME_CC */ #endif /* SECOND_APPROACH */ /* ----------------------------------------------------------------------------- diff --git a/rts/RetainerSet.h b/rts/RetainerSet.h index 1b4dec0..2f9aeea 100644 --- a/rts/RetainerSet.h +++ b/rts/RetainerSet.h @@ -25,34 +25,13 @@ its retainer identity because its location may change during garbage collections. 2. Type 'retainer' must come with comparison operations as well as - an equality operation. That it, <, >, and == must be supported - + an equality operation. That is, <, >, and == must be supported - this is necessary to store retainers in a sorted order in retainer sets. Therefore, you cannot use a huge structure type as 'retainer', for instance. - - We illustrate three possibilities of defining 'retainer identity'. - Choose one of the following three compiler directives: - - Retainer scheme 1 (RETAINER_SCHEME_INFO) : retainer = info table - Retainer scheme 2 (RETAINER_SCHEME_CCS) : retainer = cost centre stack - Retainer scheme 3 (RETAINER_SCHEME_CC) : retainer = cost centre */ -// #define RETAINER_SCHEME_INFO -#define RETAINER_SCHEME_CCS -// #define RETAINER_SCHEME_CC - -#if defined(RETAINER_SCHEME_INFO) -struct _StgInfoTable; -typedef struct _StgInfoTable *retainer; -#endif -#if defined(RETAINER_SCHEME_CCS) typedef CostCentreStack *retainer; -#endif - -#if defined(RETAINER_SCHEME_CC) -typedef CostCentre *retainer; -#endif /* Type 'retainerSet' defines an abstract datatype for sets of retainers. From git at git.haskell.org Mon Feb 26 06:04:58 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Feb 2018 06:04:58 +0000 (UTC) Subject: [commit: ghc] master: Update .gitignore (ffdb110) Message-ID: <20180226060458.879E53A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ffdb110a7f71b29f30adab7fea794b9f070a8e75/ghc >--------------------------------------------------------------- commit ffdb110a7f71b29f30adab7fea794b9f070a8e75 Author: Ömer Sinan Ağacan Date: Mon Feb 26 09:04:13 2018 +0300 Update .gitignore Reviewers: bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4446 >--------------------------------------------------------------- ffdb110a7f71b29f30adab7fea794b9f070a8e75 .gitignore | 2 ++ 1 file changed, 2 insertions(+) diff --git a/.gitignore b/.gitignore index 67eea8a..460cb68 100644 --- a/.gitignore +++ b/.gitignore @@ -112,6 +112,8 @@ _darcs/ /docs/users_guide/build-man /docs/users_guide/.doctrees-* /docs/users_guide/.doctrees/ +/docs/users_guide/ghc_packages.pyc +/docs/users_guide/utils.pyc /driver/ghci/ghc-pkg-inplace /driver/ghci/ghci-inplace /driver/ghci/ghci.res From git at git.haskell.org Mon Feb 26 06:12:43 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Feb 2018 06:12:43 +0000 (UTC) Subject: [commit: ghc] branch 'wip/angerman/win32-cross' created Message-ID: <20180226061243.AE8AF3A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/angerman/win32-cross Referencing: c5c8363cc2261b3595a4efe89a2fc011c38e84e1 From git at git.haskell.org Mon Feb 26 06:12:47 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Feb 2018 06:12:47 +0000 (UTC) Subject: [commit: ghc] wip/angerman/win32-cross: Move `iserv` into `utils` and change package name from `iserv-bin` to `iserv` (81f449c) Message-ID: <20180226061247.C18323A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/win32-cross Link : http://ghc.haskell.org/trac/ghc/changeset/81f449cab0523c028a8ea2774a55ae7ebed1e802/ghc >--------------------------------------------------------------- commit 81f449cab0523c028a8ea2774a55ae7ebed1e802 Author: Moritz Angermann Date: Sat Nov 25 15:10:52 2017 +0800 Move `iserv` into `utils` and change package name from `iserv-bin` to `iserv` This is done for consistency. We usually call the package file the same name the folder has. The move into `utils` is done so that we can move the library into `libraries/iserv` and the proxy into `utils/iserv-proxy` and then break the `iserv.cabal` apart. This will make building the cross compiler with TH simpler, because we can build the library and proxy as separate packages. # Conflicts: # utils/iserv-proxy/iserv-proxy.cabal >--------------------------------------------------------------- 81f449cab0523c028a8ea2774a55ae7ebed1e802 ghc.mk | 13 +-- {iserv => libraries/libiserv}/Makefile | 0 {iserv => libraries/libiserv}/cbits/iservmain.c | 0 libraries/libiserv/ghc.mk | 5 + libraries/libiserv/libiserv.cabal | 39 +++++++ {iserv => libraries/libiserv}/proxy-src/Remote.hs | 0 {iserv => libraries/libiserv}/src/GHCi/Utils.hsc | 0 {iserv => libraries/libiserv}/src/Lib.hs | 0 {iserv => libraries/libiserv}/src/Main.hs | 0 .../libiserv}/src/Remote/Message.hs | 0 {iserv => libraries/libiserv}/src/Remote/Slave.hs | 0 {iserv => utils/iserv-proxy}/Makefile | 0 utils/iserv-proxy/ghc.mk | 113 +++++++++++++++++++++ .../iserv-proxy/iserv-proxy.cabal | 72 +------------ .../Remote.hs => utils/iserv-proxy/src/Main.hs | 0 {iserv => utils/iserv}/Makefile | 0 {iserv => utils/iserv}/cbits/iservmain.c | 0 {iserv => utils/iserv}/ghc.mk | 66 ++++++------ utils/iserv/iserv.cabal | 44 ++++++++ {iserv => utils/iserv}/src/Main.hs | 0 20 files changed, 246 insertions(+), 106 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 81f449cab0523c028a8ea2774a55ae7ebed1e802 From git at git.haskell.org Mon Feb 26 06:12:50 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Feb 2018 06:12:50 +0000 (UTC) Subject: [commit: ghc] wip/angerman/win32-cross: adds .gitignore (a203bc6) Message-ID: <20180226061250.99D6D3A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/win32-cross Link : http://ghc.haskell.org/trac/ghc/changeset/a203bc6b3a55818592857cb987a2d766ed14edff/ghc >--------------------------------------------------------------- commit a203bc6b3a55818592857cb987a2d766ed14edff Author: Moritz Angermann Date: Thu Feb 15 13:54:55 2018 +0800 adds .gitignore >--------------------------------------------------------------- a203bc6b3a55818592857cb987a2d766ed14edff .gitignore | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/.gitignore b/.gitignore index 67eea8a..0d3a3a2 100644 --- a/.gitignore +++ b/.gitignore @@ -81,8 +81,7 @@ _darcs/ /ghc/stage1/ /ghc/stage2/ /ghc/stage3/ -/iserv/stage2*/ -/iserv/dist/ +/utils/iserv/stage2*/ # ----------------------------------------------------------------------------- # specific generated files From git at git.haskell.org Mon Feb 26 06:12:53 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Feb 2018 06:12:53 +0000 (UTC) Subject: [commit: ghc] wip/angerman/win32-cross: temp fix Makefile (9aa2173) Message-ID: <20180226061253.5E7F43A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/win32-cross Link : http://ghc.haskell.org/trac/ghc/changeset/9aa21739da05bddae992d718d01022f0036d1251/ghc >--------------------------------------------------------------- commit 9aa21739da05bddae992d718d01022f0036d1251 Author: Moritz Angermann Date: Thu Feb 15 12:29:14 2018 +0800 temp fix Makefile >--------------------------------------------------------------- 9aa21739da05bddae992d718d01022f0036d1251 utils/iserv/Makefile | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/utils/iserv/Makefile b/utils/iserv/Makefile index f160978..3619858 100644 --- a/utils/iserv/Makefile +++ b/utils/iserv/Makefile @@ -10,6 +10,6 @@ # # ----------------------------------------------------------------------------- -dir = iserv -TOP = .. +dir = utils/iserv +TOP = ../.. include $(TOP)/mk/sub-makefile.mk From git at git.haskell.org Mon Feb 26 06:12:56 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Feb 2018 06:12:56 +0000 (UTC) Subject: [commit: ghc] wip/angerman/win32-cross: Move `iserv` into `utils` and change package name from `iserv-bin` to `iserv` (e135e8c) Message-ID: <20180226061256.2BE1E3A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/win32-cross Link : http://ghc.haskell.org/trac/ghc/changeset/e135e8c958fd57c4a027a74a2e13895af7a0910e/ghc >--------------------------------------------------------------- commit e135e8c958fd57c4a027a74a2e13895af7a0910e Author: Moritz Angermann Date: Thu Feb 22 16:53:35 2018 +0800 Move `iserv` into `utils` and change package name from `iserv-bin` to `iserv` Summary: This is done for consistency. We usually call the package file the same name the folder has. The move into `utils` is done so that we can move the library into `libraries/iserv` and the proxy into `utils/iserv-proxy` and then break the `iserv.cabal` apart. This will make building the cross compiler with TH simpler, because we can build the library and proxy as separate packages. Test Plan: ./validate Reviewers: bgamari, goldfire, erikd Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4436 >--------------------------------------------------------------- e135e8c958fd57c4a027a74a2e13895af7a0910e libraries/libiserv/src/Main.hs | 63 ------------------------------------------ 1 file changed, 63 deletions(-) diff --git a/libraries/libiserv/src/Main.hs b/libraries/libiserv/src/Main.hs deleted file mode 100644 index 858cee8..0000000 --- a/libraries/libiserv/src/Main.hs +++ /dev/null @@ -1,63 +0,0 @@ -{-# LANGUAGE CPP, GADTs #-} - --- | --- The Remote GHCi server. --- --- For details on Remote GHCi, see Note [Remote GHCi] in --- compiler/ghci/GHCi.hs. --- -module Main (main) where - -import Lib (serv) - -import GHCi.Message -import GHCi.Signals -import GHCi.Utils - -import Control.Exception -import Control.Monad -import Data.IORef -import System.Environment -import System.Exit -import Text.Printf - -dieWithUsage :: IO a -dieWithUsage = do - prog <- getProgName - die $ prog ++ ": " ++ msg - where -#ifdef WINDOWS - msg = "usage: iserv [-v]" -#else - msg = "usage: iserv [-v]" -#endif - -main :: IO () -main = do - args <- getArgs - (wfd1, rfd2, rest) <- - case args of - arg0:arg1:rest -> do - let wfd1 = read arg0 - rfd2 = read arg1 - return (wfd1, rfd2, rest) - _ -> dieWithUsage - - verbose <- case rest of - ["-v"] -> return True - [] -> return False - _ -> dieWithUsage - when verbose $ - printf "GHC iserv starting (in: %d; out: %d)\n" - (fromIntegral rfd2 :: Int) (fromIntegral wfd1 :: Int) - inh <- getGhcHandle rfd2 - outh <- getGhcHandle wfd1 - installSignalHandlers - lo_ref <- newIORef Nothing - let pipe = Pipe{pipeRead = inh, pipeWrite = outh, pipeLeftovers = lo_ref} - uninterruptibleMask $ serv verbose hook pipe - - where hook = return -- empty hook - -- we cannot allow any async exceptions while communicating, because - -- we will lose sync in the protocol, hence uninterruptibleMask. - From git at git.haskell.org Mon Feb 26 06:13:02 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Feb 2018 06:13:02 +0000 (UTC) Subject: [commit: ghc] wip/angerman/win32-cross: Lookup windres, dllwrap and objdump (2247393) Message-ID: <20180226061302.49BE43A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/win32-cross Link : http://ghc.haskell.org/trac/ghc/changeset/22473933ab63ad4f27e6fb8e7cf8de8e47d5f9c2/ghc >--------------------------------------------------------------- commit 22473933ab63ad4f27e6fb8e7cf8de8e47d5f9c2 Author: Moritz Angermann Date: Wed Feb 21 16:42:32 2018 +0800 Lookup windres, dllwrap and objdump >--------------------------------------------------------------- 22473933ab63ad4f27e6fb8e7cf8de8e47d5f9c2 configure.ac | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/configure.ac b/configure.ac index 216f43f..1d3effb 100644 --- a/configure.ac +++ b/configure.ac @@ -418,6 +418,10 @@ then AC_PATH_PROG([DllWrap],[dllwrap]) AC_PATH_PROG([Windres],[windres]) AC_PATH_PROG([Genlib],[genlib]) +else + AC_CHECK_TARGET_TOOL([Windres],[windres]) + AC_CHECK_TARGET_TOOL([DllWrap],[dllwrap]) + AC_CHECK_TARGET_TOOL([OBJDUMP],[objdump]) fi DllWrapCmd="$DllWrap" From git at git.haskell.org Mon Feb 26 06:12:59 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Feb 2018 06:12:59 +0000 (UTC) Subject: [commit: ghc] wip/angerman/win32-cross: Adds quick-cross-ncg flavour. (8ba60b4) Message-ID: <20180226061259.7A7DB3A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/win32-cross Link : http://ghc.haskell.org/trac/ghc/changeset/8ba60b4f1832ef9314c2845ee02984300232082c/ghc >--------------------------------------------------------------- commit 8ba60b4f1832ef9314c2845ee02984300232082c Author: Moritz Angermann Date: Wed Feb 21 16:41:26 2018 +0800 Adds quick-cross-ncg flavour. >--------------------------------------------------------------- 8ba60b4f1832ef9314c2845ee02984300232082c mk/build.mk.sample | 7 +++++-- mk/flavours/{quick-cross.mk => quick-cross-ncg.mk} | 4 ++-- 2 files changed, 7 insertions(+), 4 deletions(-) diff --git a/mk/build.mk.sample b/mk/build.mk.sample index 958cea7..100cd07 100644 --- a/mk/build.mk.sample +++ b/mk/build.mk.sample @@ -22,8 +22,11 @@ # Fast build with optimised libraries, no profiling, with LLVM: #BuildFlavour = quick-llvm -# Fast build configured for a cross compiler -#BuildFlavour = quick-cross +# Fast build configured for a cross compiler (using the LLVM backend) +#BuildFlavour = quick-cross + +# Fast build configured for a cross compiler (using the NCG backend) +#BuildFlavour = quick-cross-ncg # Even faster build. NOT RECOMMENDED: the libraries will be # completely unoptimised, so any code built with this compiler diff --git a/mk/flavours/quick-cross.mk b/mk/flavours/quick-cross-ncg.mk similarity index 85% copy from mk/flavours/quick-cross.mk copy to mk/flavours/quick-cross-ncg.mk index f0f00d2..97352cc 100644 --- a/mk/flavours/quick-cross.mk +++ b/mk/flavours/quick-cross-ncg.mk @@ -1,7 +1,7 @@ SRC_HC_OPTS = -O0 -H64m GhcStage1HcOpts = -O -GhcStage2HcOpts = -O0 -fllvm -GhcLibHcOpts = -O -fllvm +GhcStage2HcOpts = -O0 +GhcLibHcOpts = -O BUILD_PROF_LIBS = NO SplitObjs = NO SplitSections = NO From git at git.haskell.org Mon Feb 26 06:13:05 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Feb 2018 06:13:05 +0000 (UTC) Subject: [commit: ghc] wip/angerman/win32-cross: Fix windows wchar with `_s` for mingw (9facc31) Message-ID: <20180226061305.1B30D3A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/win32-cross Link : http://ghc.haskell.org/trac/ghc/changeset/9facc3152cbacd972a6ff6f43335efc0a3ae7074/ghc >--------------------------------------------------------------- commit 9facc3152cbacd972a6ff6f43335efc0a3ae7074 Author: Moritz Angermann Date: Wed Feb 21 16:42:12 2018 +0800 Fix windows wchar with `_s` for mingw >--------------------------------------------------------------- 9facc3152cbacd972a6ff6f43335efc0a3ae7074 libraries/base/cbits/Win32Utils.c | 2 ++ rts/PathUtils.c | 5 +++++ 2 files changed, 7 insertions(+) diff --git a/libraries/base/cbits/Win32Utils.c b/libraries/base/cbits/Win32Utils.c index ce7ce97..b33db04 100644 --- a/libraries/base/cbits/Win32Utils.c +++ b/libraries/base/cbits/Win32Utils.c @@ -9,6 +9,8 @@ #include "HsBase.h" #include #include +/* Using Secure APIs */ +#define MINGW_HAS_SECURE_API 1 #include #include diff --git a/rts/PathUtils.c b/rts/PathUtils.c index 1b0b729..def3f7e 100644 --- a/rts/PathUtils.c +++ b/rts/PathUtils.c @@ -7,6 +7,11 @@ #include #include +#if defined(mingw32_HOST_OS) +/* Using Secure APIs */ +#define MINGW_HAS_SECURE_API 1 +#include +#endif pathchar* pathdup(pathchar *path) { From git at git.haskell.org Mon Feb 26 06:13:10 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Feb 2018 06:13:10 +0000 (UTC) Subject: [commit: ghc] wip/angerman/win32-cross: bump hsc2hs (674c7c3) Message-ID: <20180226061310.BDAC33A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/win32-cross Link : http://ghc.haskell.org/trac/ghc/changeset/674c7c3f0c34c1a991ea5eb6b72b7a1b6db448a9/ghc >--------------------------------------------------------------- commit 674c7c3f0c34c1a991ea5eb6b72b7a1b6db448a9 Author: Moritz Angermann Date: Wed Feb 21 16:44:39 2018 +0800 bump hsc2hs >--------------------------------------------------------------- 674c7c3f0c34c1a991ea5eb6b72b7a1b6db448a9 utils/hsc2hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/hsc2hs b/utils/hsc2hs index 738f366..c8f29af 160000 --- a/utils/hsc2hs +++ b/utils/hsc2hs @@ -1 +1 @@ -Subproject commit 738f3666c878ee9e79c3d5e819ef8b3460288edf +Subproject commit c8f29af1f63d4b6fcbc179d448d0e20571e46b8c From git at git.haskell.org Mon Feb 26 06:13:07 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Feb 2018 06:13:07 +0000 (UTC) Subject: [commit: ghc] wip/angerman/win32-cross: Fix type. (6c5fdd9) Message-ID: <20180226061307.D74AC3A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/win32-cross Link : http://ghc.haskell.org/trac/ghc/changeset/6c5fdd96e35ad90bb6c4083ef3969b2a39b46528/ghc >--------------------------------------------------------------- commit 6c5fdd96e35ad90bb6c4083ef3969b2a39b46528 Author: Moritz Angermann Date: Wed Feb 21 16:42:45 2018 +0800 Fix type. >--------------------------------------------------------------- 6c5fdd96e35ad90bb6c4083ef3969b2a39b46528 rts/win32/OSMem.c | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/rts/win32/OSMem.c b/rts/win32/OSMem.c index c67b95b..534cd15 100644 --- a/rts/win32/OSMem.c +++ b/rts/win32/OSMem.c @@ -458,7 +458,7 @@ void *osReserveHeapMemory (void *startAddress, W_ *len) sysErrorBelch( "osReserveHeapMemory: VirtualAlloc MEM_RESERVE %llu bytes \ at address %p bytes failed", - len + MBLOCK_SIZE, startAddress); + *len + MBLOCK_SIZE, startAddress); } stg_exit(EXIT_FAILURE); } From git at git.haskell.org Mon Feb 26 06:13:13 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Feb 2018 06:13:13 +0000 (UTC) Subject: [commit: ghc] wip/angerman/win32-cross: Compile with `--via-asm` when cross compiling. (bd2484a) Message-ID: <20180226061313.99D283A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/win32-cross Link : http://ghc.haskell.org/trac/ghc/changeset/bd2484a99296d19b945acf9d16a0a290460f8e5b/ghc >--------------------------------------------------------------- commit bd2484a99296d19b945acf9d16a0a290460f8e5b Author: Moritz Angermann Date: Wed Feb 21 16:43:16 2018 +0800 Compile with `--via-asm` when cross compiling. This requires a bumped hsc2hs. >--------------------------------------------------------------- bd2484a99296d19b945acf9d16a0a290460f8e5b mk/config.mk.in | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/mk/config.mk.in b/mk/config.mk.in index e5ec04a..26b07f3 100644 --- a/mk/config.mk.in +++ b/mk/config.mk.in @@ -649,8 +649,12 @@ $(eval $(call set_stage_HSC2HS_OPTS,0)) $(eval $(call set_stage_HSC2HS_OPTS,1)) $(eval $(call set_stage_HSC2HS_OPTS,2)) ifeq "$(CrossCompiling)" "YES" -SRC_HSC2HS_OPTS_STAGE1 += --cross-compile -SRC_HSC2HS_OPTS_STAGE2 += --cross-compile +# We'll assume we compile with gcc or clang, and both support `-S` and can as such use the +# --via-asm pass, which should be faster and is required for cross compiling to windows, as +# the c compiler complains about non-constant expressions even though they are constant and +# end up as constants in the assembly. +SRC_HSC2HS_OPTS_STAGE1 += --cross-compile --via-asm +SRC_HSC2HS_OPTS_STAGE2 += --cross-compile --via-asm endif SRC_HSC2HS_OPTS_STAGE0 += --cflag=-D$(HostArch_CPP)_HOST_ARCH --cflag=-D$(HostOS_CPP)_HOST_OS SRC_HSC2HS_OPTS_STAGE1 += --cflag=-D$(TargetArch_CPP)_HOST_ARCH --cflag=-D$(TargetOS_CPP)_HOST_OS From git at git.haskell.org Mon Feb 26 06:13:25 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Feb 2018 06:13:25 +0000 (UTC) Subject: [commit: ghc] wip/angerman/win32-cross: bump hsc2hs (c5c8363) Message-ID: <20180226061325.8680C3A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/win32-cross Link : http://ghc.haskell.org/trac/ghc/changeset/c5c8363cc2261b3595a4efe89a2fc011c38e84e1/ghc >--------------------------------------------------------------- commit c5c8363cc2261b3595a4efe89a2fc011c38e84e1 Author: Moritz Angermann Date: Fri Feb 23 10:49:55 2018 +0800 bump hsc2hs >--------------------------------------------------------------- c5c8363cc2261b3595a4efe89a2fc011c38e84e1 utils/hsc2hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/hsc2hs b/utils/hsc2hs index 738f366..12162e6 160000 --- a/utils/hsc2hs +++ b/utils/hsc2hs @@ -1 +1 @@ -Subproject commit 738f3666c878ee9e79c3d5e819ef8b3460288edf +Subproject commit 12162e6e7436fc194572bd7ab913611293b67f11 From git at git.haskell.org Mon Feb 26 06:13:22 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Feb 2018 06:13:22 +0000 (UTC) Subject: [commit: ghc] wip/angerman/win32-cross: Merge branches 'feature/D4430-win32-fixes', 'feature/D4436-iserv-split-8.6' and 'feature/D4439-win32-bump-hsc2hs' into work (d300e59) Message-ID: <20180226061322.9E46E3A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/win32-cross Link : http://ghc.haskell.org/trac/ghc/changeset/d300e59b2dac9e84e58ca0126382ea77f55a80f7/ghc >--------------------------------------------------------------- commit d300e59b2dac9e84e58ca0126382ea77f55a80f7 Merge: 3483423 6c5fdd9 e135e8c a49fff5 Author: Moritz Angermann Date: Fri Feb 23 09:38:28 2018 +0800 Merge branches 'feature/D4430-win32-fixes', 'feature/D4436-iserv-split-8.6' and 'feature/D4439-win32-bump-hsc2hs' into work >--------------------------------------------------------------- d300e59b2dac9e84e58ca0126382ea77f55a80f7 .gitignore | 3 +- configure.ac | 4 + ghc.mk | 13 +-- libraries/base/cbits/Win32Utils.c | 2 + {iserv => libraries/libiserv}/Makefile | 0 {iserv => libraries/libiserv}/cbits/iservmain.c | 0 libraries/libiserv/ghc.mk | 5 + libraries/libiserv/libiserv.cabal | 39 +++++++ {iserv => libraries/libiserv}/proxy-src/Remote.hs | 0 {iserv => libraries/libiserv}/src/GHCi/Utils.hsc | 0 {iserv => libraries/libiserv}/src/Lib.hs | 0 .../libiserv}/src/Remote/Message.hs | 0 {iserv => libraries/libiserv}/src/Remote/Slave.hs | 0 mk/build.mk.sample | 7 +- mk/config.mk.in | 8 +- mk/flavours/{quick-cross.mk => quick-cross-ncg.mk} | 4 +- rts/PathUtils.c | 5 + rts/win32/OSMem.c | 2 +- {iserv => utils/iserv-proxy}/Makefile | 0 utils/iserv-proxy/ghc.mk | 113 +++++++++++++++++++++ .../iserv-proxy/iserv-proxy.cabal | 72 +------------ .../Remote.hs => utils/iserv-proxy/src/Main.hs | 0 utils/{hp2ps => iserv}/Makefile | 2 +- {iserv => utils/iserv}/cbits/iservmain.c | 0 {iserv => utils/iserv}/ghc.mk | 66 ++++++------ utils/iserv/iserv.cabal | 44 ++++++++ {iserv => utils/iserv}/src/Main.hs | 0 27 files changed, 273 insertions(+), 116 deletions(-) From git at git.haskell.org Mon Feb 26 06:13:16 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Feb 2018 06:13:16 +0000 (UTC) Subject: [commit: ghc] wip/angerman/win32-cross: Compile with `--via-asm` when cross compiling. (a49fff5) Message-ID: <20180226061316.684B63A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/win32-cross Link : http://ghc.haskell.org/trac/ghc/changeset/a49fff54771356bc2d048052f420a2e233320ca7/ghc >--------------------------------------------------------------- commit a49fff54771356bc2d048052f420a2e233320ca7 Author: Moritz Angermann Date: Thu Feb 22 22:03:22 2018 +0800 Compile with `--via-asm` when cross compiling. Summary: This bumps `hsc2hs` and adds the new `--via-asm` flag, which allows to successfully cross compile the win32 lirbary. Test Plan: ./validate Reviewers: bgamari Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4439 >--------------------------------------------------------------- a49fff54771356bc2d048052f420a2e233320ca7 utils/hsc2hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/hsc2hs b/utils/hsc2hs index c8f29af..738f366 160000 --- a/utils/hsc2hs +++ b/utils/hsc2hs @@ -1 +1 @@ -Subproject commit c8f29af1f63d4b6fcbc179d448d0e20571e46b8c +Subproject commit 738f3666c878ee9e79c3d5e819ef8b3460288edf From git at git.haskell.org Mon Feb 26 06:33:56 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Feb 2018 06:33:56 +0000 (UTC) Subject: [commit: ghc] wip/angerman/win32-cross: fix gitmodules remote for the time being (9b6bf0f) Message-ID: <20180226063356.4DD7A3A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/angerman/win32-cross Link : http://ghc.haskell.org/trac/ghc/changeset/9b6bf0f10629d8e1fb1861bd7d5c213856885917/ghc >--------------------------------------------------------------- commit 9b6bf0f10629d8e1fb1861bd7d5c213856885917 Author: Moritz Angermann Date: Mon Feb 26 14:33:29 2018 +0800 fix gitmodules remote for the time being >--------------------------------------------------------------- 9b6bf0f10629d8e1fb1861bd7d5c213856885917 .gitmodules | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.gitmodules b/.gitmodules index 2125a92..72d7385 100644 --- a/.gitmodules +++ b/.gitmodules @@ -117,7 +117,7 @@ ignore = untracked [submodule "utils/hsc2hs"] path = utils/hsc2hs - url = ../hsc2hs.git + url = https://github.com/angerman/hsc2hs.git ignore = untracked [submodule "libffi-tarballs"] path = libffi-tarballs From git at git.haskell.org Mon Feb 26 15:33:17 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Feb 2018 15:33:17 +0000 (UTC) Subject: [commit: ghc] tag 'ghc-8.5-start' created Message-ID: <20180226153317.7153E3A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New tag : ghc-8.5-start Referencing: 2dde6e9a1d8618f754bd3cd35817bfa46a610cf0 From git at git.haskell.org Mon Feb 26 19:41:33 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Feb 2018 19:41:33 +0000 (UTC) Subject: [commit: ghc] master: circleci: Simplify Hadrian build (da4766c) Message-ID: <20180226194133.48B1B3A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/da4766c313bf33e5f0790583af204935f62699a0/ghc >--------------------------------------------------------------- commit da4766c313bf33e5f0790583af204935f62699a0 Author: Ben Gamari Date: Mon Feb 26 11:37:44 2018 -0500 circleci: Simplify Hadrian build This uses the build.sh script included in the Hadrian tree, ensuring that we will build Cabal from git if necessary. >--------------------------------------------------------------- da4766c313bf33e5f0790583af204935f62699a0 .circleci/config.yml | 11 ++--------- 1 file changed, 2 insertions(+), 9 deletions(-) diff --git a/.circleci/config.yml b/.circleci/config.yml index e4f09a3..295d803 100644 --- a/.circleci/config.yml +++ b/.circleci/config.yml @@ -55,16 +55,10 @@ aliases: command: "make -j$THREADS" - &build_hadrian run: - name: Build Hadrian - command: | - cd hadrian - cabal update - cabal install - - &build_ghc_hadrian - run: name: Build GHC using Hadrian command: | - $HOME/.cabal/bin/hadrian -j$THREADS + cabal update + hadrian/build.sh -j$THREADS - &test run: name: Test @@ -169,7 +163,6 @@ jobs: - *boot - *configure_unix - *build_hadrian - - *build_ghc_hadrian "validate-x86_64-linux-unreg": resource_class: xlarge From git at git.haskell.org Tue Feb 27 00:01:13 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Feb 2018 00:01:13 +0000 (UTC) Subject: [commit: ghc] wip/docker-ghcci: Move apt-get up so we have root (b15742e) Message-ID: <20180227000113.1E3203A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/docker-ghcci Link : http://ghc.haskell.org/trac/ghc/changeset/b15742e71d0e2b4a285507e3bfe513ad9e737c6d/ghc >--------------------------------------------------------------- commit b15742e71d0e2b4a285507e3bfe513ad9e737c6d Author: David Feuer Date: Mon Feb 26 19:00:44 2018 -0500 Move apt-get up so we have root >--------------------------------------------------------------- b15742e71d0e2b4a285507e3bfe513ad9e737c6d .circleci/config.yml | 19 ++++--------------- .circleci/images/x86_64-linux/Dockerfile | 6 ++++++ 2 files changed, 10 insertions(+), 15 deletions(-) diff --git a/.circleci/config.yml b/.circleci/config.yml index bc318c6..5e14f52 100644 --- a/.circleci/config.yml +++ b/.circleci/config.yml @@ -7,12 +7,6 @@ aliases: # Make sure we have proper openssh before checkout: CircleCI git # does not check the repository out properly without it and also # takes 20 times longer than it should be. - - &precheckout - run: - name: Install OpenSSH client - command: | - apt-get update -qq - apt-get install -qy openssh-client - &prepare run: name: prepare-system @@ -98,11 +92,10 @@ jobs: "validate-x86_64-linux": resource_class: xlarge docker: - - image: dfeuer/ghcci:x86_64-linux-0.0.1 + - image: dfeuer/ghcci:x86_64-linux-0.0.2 environment: <<: *buildenv steps: - - *precheckout - checkout - *prepare - *submodules @@ -122,7 +115,6 @@ jobs: TARGET: FreeBSD <<: *buildenv steps: - - *precheckout - checkout - *prepare - *submodules @@ -158,11 +150,10 @@ jobs: "validate-hadrian-x86_64-linux": resource_class: xlarge docker: - - image: dfeuer/ghcci:x86_64-linux-0.0.1 + - image: dfeuer/ghcci:x86_64-linux-0.0.2 environment: <<: *buildenv steps: - - *precheckout - checkout - *prepare - *submodules @@ -174,11 +165,10 @@ jobs: "validate-x86_64-linux-unreg": resource_class: xlarge docker: - - image: dfeuer/ghcci:x86_64-linux-0.0.1 + - image: dfeuer/ghcci:x86_64-linux-0.0.2 environment: <<: *buildenv steps: - - *precheckout - checkout - *prepare - *submodules @@ -190,7 +180,7 @@ jobs: "validate-x86_64-linux-llvm": resource_class: xlarge docker: - - image: dfeuer/ghcci:x86_64-linux-0.0.1 + - image: dfeuer/ghcci:x86_64-linux-0.0.2 environment: <<: *buildenv BUILD_FLAVOUR: perf-llvm @@ -206,7 +196,6 @@ jobs: - run: name: Verify that llc works command: llc - - *precheckout - checkout - *prepare - *submodules diff --git a/.circleci/images/x86_64-linux/Dockerfile b/.circleci/images/x86_64-linux/Dockerfile index aa8813f..c3219c9 100644 --- a/.circleci/images/x86_64-linux/Dockerfile +++ b/.circleci/images/x86_64-linux/Dockerfile @@ -1,3 +1,9 @@ FROM haskell:8.2 +RUN echo 'Set up ghc user' RUN adduser ghc --gecos 'GHC builds' --disabled-password + +RUN echo 'Install OpenSSH client' +RUN apt-get update -qq +RUN apt-get install -qy openssh-client + USER ghc From git at git.haskell.org Tue Feb 27 04:51:51 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Feb 2018 04:51:51 +0000 (UTC) Subject: [commit: ghc] wip/docker-ghcci: Let's try again (1edd30e) Message-ID: <20180227045151.A2AB43A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/docker-ghcci Link : http://ghc.haskell.org/trac/ghc/changeset/1edd30e301a11492438352cf88c8c32254322489/ghc >--------------------------------------------------------------- commit 1edd30e301a11492438352cf88c8c32254322489 Author: David Feuer Date: Mon Feb 26 23:51:34 2018 -0500 Let's try again >--------------------------------------------------------------- 1edd30e301a11492438352cf88c8c32254322489 .circleci/images/x86_64-linux/Dockerfile | 2 ++ .circleci/prepare-system.sh | 1 - 2 files changed, 2 insertions(+), 1 deletion(-) diff --git a/.circleci/images/x86_64-linux/Dockerfile b/.circleci/images/x86_64-linux/Dockerfile index c3219c9..bfc4a8c 100644 --- a/.circleci/images/x86_64-linux/Dockerfile +++ b/.circleci/images/x86_64-linux/Dockerfile @@ -6,4 +6,6 @@ RUN echo 'Install OpenSSH client' RUN apt-get update -qq RUN apt-get install -qy openssh-client +RUN apt-get install -qy git make automake autoconf gcc perl python3 texinfo xz-utils lbzip2 patch + USER ghc diff --git a/.circleci/prepare-system.sh b/.circleci/prepare-system.sh index 193fac9..c61c09a 100755 --- a/.circleci/prepare-system.sh +++ b/.circleci/prepare-system.sh @@ -43,7 +43,6 @@ case "$(uname)" in fi else # assuming Ubuntu - apt-get install -qy git make automake autoconf gcc perl python3 texinfo xz-utils lbzip2 patch cabal update cabal install --reinstall hscolour --index-state=$hackage_index_state fi From git at git.haskell.org Tue Feb 27 08:45:02 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Feb 2018 08:45:02 +0000 (UTC) Subject: [commit: ghc] master: Comments only (40fa420) Message-ID: <20180227084502.A8C9B3A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/40fa420ce97125724eff9001a8cdef29a96e789c/ghc >--------------------------------------------------------------- commit 40fa420ce97125724eff9001a8cdef29a96e789c Author: Simon Peyton Jones Date: Tue Feb 20 11:34:45 2018 +0000 Comments only >--------------------------------------------------------------- 40fa420ce97125724eff9001a8cdef29a96e789c compiler/coreSyn/CoreUtils.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/compiler/coreSyn/CoreUtils.hs b/compiler/coreSyn/CoreUtils.hs index 3d5f4bc..644c0f8 100644 --- a/compiler/coreSyn/CoreUtils.hs +++ b/compiler/coreSyn/CoreUtils.hs @@ -1723,6 +1723,8 @@ don't want to discard a seq on it. exprIsTopLevelBindable :: CoreExpr -> Type -> Bool -- See Note [CoreSyn top-level string literals] -- Precondition: exprType expr = ty +-- Top-level literal strings can't even be wrapped in ticks +-- see Note [CoreSyn top-level string literals] in CoreSyn exprIsTopLevelBindable expr ty = exprIsLiteralString expr || not (isUnliftedType ty) From git at git.haskell.org Tue Feb 27 08:45:06 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Feb 2018 08:45:06 +0000 (UTC) Subject: [commit: ghc] master: Fix a nasty bug in the pure unifier (e99fdf7) Message-ID: <20180227084506.288D63A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e99fdf775540440c1c58dc5ade3c5984dc49246f/ghc >--------------------------------------------------------------- commit e99fdf775540440c1c58dc5ade3c5984dc49246f Author: Simon Peyton Jones Date: Mon Feb 26 17:44:55 2018 +0000 Fix a nasty bug in the pure unifier The pure unifier was building an infinite type, through a defective occurs check. So GHC went into an infinite loop. Reason: we were neglecting the 'kco' part of the type, which 'unify_ty' maintains. Yikes. The fix is easy. I refactored a bit to make it harder to go wrong in future. >--------------------------------------------------------------- e99fdf775540440c1c58dc5ade3c5984dc49246f compiler/types/Unify.hs | 59 ++++++++++++++++++--------------- testsuite/tests/polykinds/T14846.hs | 39 ++++++++++++++++++++++ testsuite/tests/polykinds/T14846.stderr | 43 ++++++++++++++++++++++++ testsuite/tests/polykinds/all.T | 1 + 4 files changed, 116 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 e99fdf775540440c1c58dc5ade3c5984dc49246f From git at git.haskell.org Tue Feb 27 08:45:08 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Feb 2018 08:45:08 +0000 (UTC) Subject: [commit: ghc] master: Better stats for T5837 (d675a35) Message-ID: <20180227084509.007263A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d675a354e8db67d87d1f257c3d1d2bf2d58c2b3f/ghc >--------------------------------------------------------------- commit d675a354e8db67d87d1f257c3d1d2bf2d58c2b3f Author: Simon Peyton Jones Date: Tue Feb 27 08:43:51 2018 +0000 Better stats for T5837 I'm not sure why. It's an odd test, mind you; a weird type-function recursion thing. So I'm not inclined to investigate. Anyway, good! >--------------------------------------------------------------- d675a354e8db67d87d1f257c3d1d2bf2d58c2b3f testsuite/tests/perf/compiler/all.T | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index 1a2413a..4c2462c 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -665,7 +665,7 @@ test('T5837', # 2017-04-21 54985248 (x64/Windows) - Unknown # 2017-12-24 54793816 (x64/Windows) - Unknown - (wordsize(64), 55813608, 7)]) + (wordsize(64), 51294232, 7)]) # sample: 3926235424 (amd64/Linux, 15/2/2012) # 2012-10-02 81879216 # 2012-09-20 87254264 amd64/Linux @@ -704,6 +704,7 @@ test('T5837', # 2017-09-06 56782344 amd64/Linux Drift manifest in unrelated LLVM patch # 2017-10-24 52089424 amd64/linux Fix space leak in BinIface.getSymbolTable # 2018-02-19 55813608 amd64/Linux Unknown + # 2018-02-27 51294232 amd64/Linux Better still, I'm not sure why ], compile, ['-freduction-depth=50']) From git at git.haskell.org Tue Feb 27 08:45:11 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Feb 2018 08:45:11 +0000 (UTC) Subject: [commit: ghc] master: Tiny refactor in Core Lint (8c1d6b7) Message-ID: <20180227084511.D25453A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8c1d6b7d196f41669f052f16151423f7ce9842f8/ghc >--------------------------------------------------------------- commit 8c1d6b7d196f41669f052f16151423f7ce9842f8 Author: Simon Peyton Jones Date: Tue Feb 20 10:45:21 2018 +0000 Tiny refactor in Core Lint >--------------------------------------------------------------- 8c1d6b7d196f41669f052f16151423f7ce9842f8 compiler/coreSyn/CoreLint.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/compiler/coreSyn/CoreLint.hs b/compiler/coreSyn/CoreLint.hs index b0d2ac3..4fa3425 100644 --- a/compiler/coreSyn/CoreLint.hs +++ b/compiler/coreSyn/CoreLint.hs @@ -1457,7 +1457,7 @@ lintCoreRule _ _ (BuiltinRule {}) lintCoreRule fun fun_ty rule@(Rule { ru_name = name, ru_bndrs = bndrs , ru_args = args, ru_rhs = rhs }) = lintBinders LambdaBind bndrs $ \ _ -> - do { lhs_ty <- foldM lintCoreArg fun_ty args + do { lhs_ty <- lintCoreArgs fun_ty args ; rhs_ty <- case isJoinId_maybe fun of Just join_arity -> do { checkL (args `lengthIs` join_arity) $ @@ -1467,7 +1467,8 @@ lintCoreRule fun fun_ty rule@(Rule { ru_name = name, ru_bndrs = bndrs _ -> markAllJoinsBad $ lintCoreExpr rhs ; ensureEqTys lhs_ty rhs_ty $ (rule_doc <+> vcat [ text "lhs type:" <+> ppr lhs_ty - , text "rhs type:" <+> ppr rhs_ty ]) + , text "rhs type:" <+> ppr rhs_ty + , text "fun_ty:" <+> ppr fun_ty ]) ; let bad_bndrs = filter is_bad_bndr bndrs ; checkL (null bad_bndrs) From git at git.haskell.org Tue Feb 27 08:47:36 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Feb 2018 08:47:36 +0000 (UTC) Subject: [commit: ghc] master: Test for Trac #13075 is working now (3dec923) Message-ID: <20180227084736.16ED23A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3dec9236a80299cd3e3b9b21a42f91628db1a3d7/ghc >--------------------------------------------------------------- commit 3dec9236a80299cd3e3b9b21a42f91628db1a3d7 Author: Simon Peyton Jones Date: Tue Feb 27 08:46:50 2018 +0000 Test for Trac #13075 is working now >--------------------------------------------------------------- 3dec9236a80299cd3e3b9b21a42f91628db1a3d7 .../should_run/T5472.stdout => typecheck/should_fail/T13075.stderr} | 0 testsuite/tests/typecheck/should_fail/all.T | 2 +- 2 files changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/deSugar/should_run/T5472.stdout b/testsuite/tests/typecheck/should_fail/T13075.stderr similarity index 100% copy from testsuite/tests/deSugar/should_run/T5472.stdout copy to testsuite/tests/typecheck/should_fail/T13075.stderr diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index 20ed5a4..5377fef 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -429,7 +429,7 @@ test('T12947', normal, compile_fail, ['']) test('T12973', normal, compile_fail, ['']) test('StrictBinds', normal, compile_fail, ['']) test('T13068', [extra_files(['T13068.hs', 'T13068a.hs', 'T13068.hs-boot', 'T13068m.hs'])], multimod_compile_fail, ['T13068m', '']) -test('T13075', expect_broken(13075), compile_fail, ['']) +test('T13075', normal, compile_fail, ['']) test('T13105', normal, compile_fail, ['']) test('LevPolyBounded', normal, compile_fail, ['']) test('T13487', normal, compile, ['']) From git at git.haskell.org Tue Feb 27 08:54:29 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Feb 2018 08:54:29 +0000 (UTC) Subject: [commit: ghc] master: Comments only (51e0a38) Message-ID: <20180227085429.0A4E93A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/51e0a382a96e4c2e911738aeaac20f36b621fbbc/ghc >--------------------------------------------------------------- commit 51e0a382a96e4c2e911738aeaac20f36b621fbbc Author: Simon Peyton Jones Date: Tue Feb 27 08:51:06 2018 +0000 Comments only >--------------------------------------------------------------- 51e0a382a96e4c2e911738aeaac20f36b621fbbc compiler/types/Unify.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/compiler/types/Unify.hs b/compiler/types/Unify.hs index e59c4ce..9166544 100644 --- a/compiler/types/Unify.hs +++ b/compiler/types/Unify.hs @@ -1075,6 +1075,7 @@ bindTv env tv1 ty2 ; checkRnEnvR env free_tvs2 -- Occurs check, see Note [Fine-grained unification] + -- Make sure you include 'kco' (which ty2 does) Trac #14846 ; occurs <- occursCheck env tv1 free_tvs2 ; if occurs then maybeApart From git at git.haskell.org Tue Feb 27 08:54:31 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Feb 2018 08:54:31 +0000 (UTC) Subject: [commit: ghc] master: Fix test for Trac #13075 (b2996f1) Message-ID: <20180227085431.E96BA3A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b2996f1b81c6c51eedc7ece93de0a6bc0426da5c/ghc >--------------------------------------------------------------- commit b2996f1b81c6c51eedc7ece93de0a6bc0426da5c Author: Simon Peyton Jones Date: Tue Feb 27 08:53:10 2018 +0000 Fix test for Trac #13075 I'd put the stderr file in my link tree, not in the source tree, so my original push had the wrong file, even though my tree validated. Sorry! >--------------------------------------------------------------- b2996f1b81c6c51eedc7ece93de0a6bc0426da5c testsuite/tests/typecheck/should_fail/T13075.stderr | 2 ++ 1 file changed, 2 insertions(+) diff --git a/testsuite/tests/typecheck/should_fail/T13075.stderr b/testsuite/tests/typecheck/should_fail/T13075.stderr index 0519ecb..89abb9a 100644 --- a/testsuite/tests/typecheck/should_fail/T13075.stderr +++ b/testsuite/tests/typecheck/should_fail/T13075.stderr @@ -1 +1,3 @@ +T13075.hs:5:1: error: + Top-level strict bindings aren't allowed: !(Just x) = Nothing From git at git.haskell.org Tue Feb 27 09:25:37 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Feb 2018 09:25:37 +0000 (UTC) Subject: [commit: ghc] wip/docker-ghcci: Attempt freebsd (ad9b64d) Message-ID: <20180227092537.30A903A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/docker-ghcci Link : http://ghc.haskell.org/trac/ghc/changeset/ad9b64d453307ae9958da993f831d6f4b4dede3e/ghc >--------------------------------------------------------------- commit ad9b64d453307ae9958da993f831d6f4b4dede3e Author: David Feuer Date: Tue Feb 27 04:25:03 2018 -0500 Attempt freebsd >--------------------------------------------------------------- ad9b64d453307ae9958da993f831d6f4b4dede3e .circleci/config.yml | 10 +++++----- .circleci/images/x86_64-freebsd/Dockerfile | 17 +++++++++++++++-- .circleci/prepare-system.sh | 6 ------ 3 files changed, 20 insertions(+), 13 deletions(-) diff --git a/.circleci/config.yml b/.circleci/config.yml index 5e14f52..571de55 100644 --- a/.circleci/config.yml +++ b/.circleci/config.yml @@ -92,7 +92,7 @@ jobs: "validate-x86_64-linux": resource_class: xlarge docker: - - image: dfeuer/ghcci:x86_64-linux-0.0.2 + - image: dfeuer/ghcci:x86_64-linux-0.0.3 environment: <<: *buildenv steps: @@ -110,7 +110,7 @@ jobs: "validate-x86_64-freebsd": resource_class: xlarge docker: - - image: ghcci:x86_64-freebsd + - image: dfeuer/ghcci:x86_64-freebsd-0.0.1 environment: TARGET: FreeBSD <<: *buildenv @@ -150,7 +150,7 @@ jobs: "validate-hadrian-x86_64-linux": resource_class: xlarge docker: - - image: dfeuer/ghcci:x86_64-linux-0.0.2 + - image: dfeuer/ghcci:x86_64-linux-0.0.3 environment: <<: *buildenv steps: @@ -165,7 +165,7 @@ jobs: "validate-x86_64-linux-unreg": resource_class: xlarge docker: - - image: dfeuer/ghcci:x86_64-linux-0.0.2 + - image: dfeuer/ghcci:x86_64-linux-0.0.3 environment: <<: *buildenv steps: @@ -180,7 +180,7 @@ jobs: "validate-x86_64-linux-llvm": resource_class: xlarge docker: - - image: dfeuer/ghcci:x86_64-linux-0.0.2 + - image: dfeuer/ghcci:x86_64-linux-0.0.3 environment: <<: *buildenv BUILD_FLAVOUR: perf-llvm diff --git a/.circleci/images/x86_64-freebsd/Dockerfile b/.circleci/images/x86_64-freebsd/Dockerfile index 9c51cc0..1c9916d 100644 --- a/.circleci/images/x86_64-freebsd/Dockerfile +++ b/.circleci/images/x86_64-freebsd/Dockerfile @@ -1,6 +1,10 @@ FROM ubuntu:16.04 -RUN apt-get update && apt-get install -y --no-install-recommends \ +RUN apt-get update -qq +RUN apt-get install -y --no-install-recommends software-properties-common +RUN add-apt-repository -y ppa:hvr/ghc +RUN apt-get update -qq +RUN apt-get install -y --no-install-recommends \ autoconf \ automake \ bzip2 \ @@ -18,7 +22,16 @@ RUN apt-get update && apt-get install -y --no-install-recommends \ software-properties-common \ sudo \ wget \ - xz-utils + xz-utils \ + ghc-8.0.2 \ + cabal-install-1.24 \ + alex \ + happy \ + ncurses-dev \ + gcc \ + texinfo \ + lbzip2 +RUN ln -s $HOME/.cabal/bin/HsColour /usr/local/bin/HsColour COPY build-toolchain.sh /tmp/ RUN /tmp/build-toolchain.sh x86_64 diff --git a/.circleci/prepare-system.sh b/.circleci/prepare-system.sh index c61c09a..6365c29 100755 --- a/.circleci/prepare-system.sh +++ b/.circleci/prepare-system.sh @@ -25,14 +25,8 @@ case "$(uname)" in if [[ -n ${TARGET:-} ]]; then if [[ $TARGET = FreeBSD ]]; then # cross-compiling to FreeBSD - add-apt-repository -y ppa:hvr/ghc - apt-get update -qq - apt-get install -qy ghc-8.0.2 cabal-install-1.24 alex happy \ - ncurses-dev git make automake autoconf gcc perl \ - python3 texinfo xz-utils lbzip2 patch cabal update cabal install --reinstall hscolour --index-state=$hackage_index_state - ln -s $HOME/.cabal/bin/HsColour /usr/local/bin/HsColour echo 'HADDOCK_DOCS = NO' >> mk/build.mk echo 'WERROR=' >> mk/build.mk From git at git.haskell.org Tue Feb 27 13:44:23 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Feb 2018 13:44:23 +0000 (UTC) Subject: [commit: ghc] wip/T2893: Fix a bunch of buglets in QuantifiedConstraints (60f6824) Message-ID: <20180227134423.D932C3A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T2893 Link : http://ghc.haskell.org/trac/ghc/changeset/60f682407eefdb7884d12ba43d00add0c1ca9245/ghc >--------------------------------------------------------------- commit 60f682407eefdb7884d12ba43d00add0c1ca9245 Author: Simon Peyton Jones Date: Tue Feb 27 13:43:26 2018 +0000 Fix a bunch of buglets in QuantifiedConstraints * Freshen tyvars in Inst.instDFunType * Freshen tyvars in TcCanonical.solveForAll * Define TcSMonad.mightMatchLater, and use it (fixes Trac #14833) * Add testsuite directry tests/quantified-constraints/, and start to populate it >--------------------------------------------------------------- 60f682407eefdb7884d12ba43d00add0c1ca9245 compiler/typecheck/Inst.hs | 8 ++++-- compiler/typecheck/TcCanonical.hs | 18 ++++++++----- compiler/typecheck/TcEvidence.hs | 2 -- compiler/typecheck/TcInteract.hs | 30 ++++++++++------------ compiler/typecheck/TcSMonad.hs | 19 +++++++------- compiler/typecheck/TcValidity.hs | 3 ++- compiler/types/Type.hs | 0 testsuite/tests/quantified-constraints/T14833.hs | 28 ++++++++++++++++++++ .../T2893.hs | 0 .../T2893a.hs | 0 testsuite/tests/quantified-constraints/T2893b.hs | 24 +++++++++++++++++ testsuite/tests/quantified-constraints/all.T | 4 +++ testsuite/tests/typecheck/should_compile/all.T | 2 -- 13 files changed, 100 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 60f682407eefdb7884d12ba43d00add0c1ca9245 From git at git.haskell.org Tue Feb 27 13:49:59 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Feb 2018 13:49:59 +0000 (UTC) Subject: [commit: ghc] wip/T2893: Add test for Trac #14835 (36bae41) Message-ID: <20180227134959.6D2A83A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T2893 Link : http://ghc.haskell.org/trac/ghc/changeset/36bae41c5e7abf8895e515e295aabac22a6d67df/ghc >--------------------------------------------------------------- commit 36bae41c5e7abf8895e515e295aabac22a6d67df Author: Simon Peyton Jones Date: Tue Feb 27 13:49:37 2018 +0000 Add test for Trac #14835 >--------------------------------------------------------------- 36bae41c5e7abf8895e515e295aabac22a6d67df .../tests/{ado => quantified-constraints}/Makefile | 0 .../quantified-constraints/{T14833.hs => T14835.hs} | 18 +++++------------- testsuite/tests/quantified-constraints/all.T | 1 + 3 files changed, 6 insertions(+), 13 deletions(-) diff --git a/testsuite/tests/ado/Makefile b/testsuite/tests/quantified-constraints/Makefile similarity index 100% copy from testsuite/tests/ado/Makefile copy to testsuite/tests/quantified-constraints/Makefile diff --git a/testsuite/tests/quantified-constraints/T14833.hs b/testsuite/tests/quantified-constraints/T14835.hs similarity index 65% copy from testsuite/tests/quantified-constraints/T14833.hs copy to testsuite/tests/quantified-constraints/T14835.hs index 6e70196..de9b450 100644 --- a/testsuite/tests/quantified-constraints/T14833.hs +++ b/testsuite/tests/quantified-constraints/T14835.hs @@ -5,7 +5,7 @@ {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE QuantifiedConstraints #-} {-# LANGUAGE UndecidableInstances #-} -module T14833 where +module Bug where data Dict c where Dict :: c => Dict c @@ -13,16 +13,8 @@ data Dict c where class (a => b) => Implies a b instance (a => b) => Implies a b --- Works ok -iota1 :: (() => a) => Dict a -iota1 = Dict +curryC1 :: ((a, b) => c) => Dict (Implies a (Implies b c)) +curryC1 = Dict -iota2 :: Implies () a => Dict a -iota2 = Dict - -{- -[G] Implies () a -[G] (() => a) -- By superclass - -[W] a --} \ No newline at end of file +curryC2 :: Implies (a, b) c => Dict (Implies a (Implies b c)) +curryC2 = Dict diff --git a/testsuite/tests/quantified-constraints/all.T b/testsuite/tests/quantified-constraints/all.T index 9e69942..b67ec99 100644 --- a/testsuite/tests/quantified-constraints/all.T +++ b/testsuite/tests/quantified-constraints/all.T @@ -1,4 +1,5 @@ test('T14833', normal, compile, ['']) +test('T14835', normal, compile, ['']) test('T2893', normal, compile, ['']) test('T2893a', normal, compile, ['']) From git at git.haskell.org Tue Feb 27 15:27:52 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Feb 2018 15:27:52 +0000 (UTC) Subject: [commit: ghc] wip/docker-ghcci: Merge branch 'master' of git://git.haskell.org/ghc into wip/docker-ghcci (3650f09) Message-ID: <20180227152752.B0D7F3A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/docker-ghcci Link : http://ghc.haskell.org/trac/ghc/changeset/3650f0983e4c2b5f97d669fcb16b06bca1045429/ghc >--------------------------------------------------------------- commit 3650f0983e4c2b5f97d669fcb16b06bca1045429 Merge: ad9b64d b2996f1 Author: David Feuer Date: Tue Feb 27 10:27:28 2018 -0500 Merge branch 'master' of git://git.haskell.org/ghc into wip/docker-ghcci >--------------------------------------------------------------- 3650f0983e4c2b5f97d669fcb16b06bca1045429 .circleci/config.yml | 36 +- .gitignore | 2 + aclocal.m4 | 13 +- boot | 11 + compiler/cmm/CmmCommonBlockElim.hs | 11 +- compiler/cmm/CmmExpr.hs | 13 +- compiler/cmm/CmmLayoutStack.hs | 16 +- compiler/cmm/CmmSink.hs | 2 +- compiler/cmm/CmmUtils.hs | 18 + compiler/codeGen/CgUtils.hs | 2 +- compiler/codeGen/StgCmmBind.hs | 11 +- compiler/codeGen/StgCmmCon.hs | 4 +- compiler/codeGen/StgCmmForeign.hs | 47 +-- compiler/codeGen/StgCmmHeap.hs | 9 +- compiler/codeGen/StgCmmLayout.hs | 3 +- compiler/codeGen/StgCmmPrim.hs | 21 +- compiler/codeGen/StgCmmProf.hs | 15 +- compiler/codeGen/StgCmmUtils.hs | 2 +- compiler/coreSyn/CoreLint.hs | 5 +- compiler/coreSyn/CoreUtils.hs | 2 + compiler/deSugar/DsForeign.hs | 3 +- compiler/iface/FlagChecker.hs | 3 +- compiler/main/DriverPipeline.hs | 26 +- compiler/main/DynFlags.hs | 74 +++- compiler/main/ErrUtils.hs | 9 +- compiler/prelude/PrelRules.hs | 13 + compiler/prelude/primops.txt.pp | 1 - compiler/rename/RnSource.hs | 5 +- compiler/simplStg/SimplStg.hs | 12 +- compiler/simplStg/UnariseStg.hs | 60 ++- compiler/stgSyn/StgLint.hs | 459 +++++++-------------- compiler/stgSyn/StgSyn.hs | 1 + compiler/typecheck/TcDeriv.hs | 59 ++- compiler/typecheck/TcDerivUtils.hs | 10 +- compiler/typecheck/TcErrors.hs | 290 +++++++++---- compiler/typecheck/TcHsType.hs | 13 +- compiler/typecheck/TcRnTypes.hs | 16 +- compiler/typecheck/TcTypeable.hs | 5 +- compiler/types/Unify.hs | 106 +++-- configure.ac | 2 + docs/users_guide/8.2.1-notes.rst | 2 +- docs/users_guide/8.6.1-notes.rst | 3 + docs/users_guide/debugging.rst | 11 +- docs/users_guide/glasgow_exts.rst | 116 +++++- docs/users_guide/phases.rst | 5 +- driver/utils/dynwrapper.c | 1 - hadrian | 2 +- libraries/base/Data/Typeable/Internal.hs | 14 +- libraries/base/changelog.md | 5 +- libraries/filepath | 2 +- libraries/ghc-prim/.gitignore | 1 + libraries/haskeline | 2 +- libraries/parsec | 2 +- libraries/pretty | 2 +- libraries/primitive | 2 +- libraries/process | 2 +- libraries/stm | 2 +- libraries/text | 2 +- mk/config.mk.in | 1 + rts/PrimOps.cmm | 5 - rts/RetainerProfile.c | 9 - rts/RetainerSet.c | 141 ------- rts/RetainerSet.h | 23 +- rts/RtsSymbols.c | 1 - rts/win32/IOManager.c | 15 +- rules/build-package-way.mk | 7 +- rules/haddock.mk | 1 + .../concurrent/should_run/setnumcapabilities001.hs | 2 +- testsuite/tests/deriving/should_fail/T14728a.hs | 20 + .../tests/deriving/should_fail/T14728a.stderr | 7 + testsuite/tests/deriving/should_fail/T14728b.hs | 16 + .../tests/deriving/should_fail/T14728b.stderr | 7 + testsuite/tests/deriving/should_fail/all.T | 2 + testsuite/tests/gadt/T14808.hs | 12 + testsuite/tests/gadt/all.T | 1 + testsuite/tests/perf/compiler/all.T | 10 +- testsuite/tests/polykinds/T14846.hs | 39 ++ testsuite/tests/polykinds/T14846.stderr | 43 ++ testsuite/tests/polykinds/all.T | 1 + testsuite/tests/th/T13123.hs | 2 - testsuite/tests/typecheck/should_compile/T14811.hs | 5 + .../abstract_refinement_substitutions.hs | 7 + .../abstract_refinement_substitutions.stderr | 290 +++++++++++++ testsuite/tests/typecheck/should_compile/all.T | 3 + .../should_compile/refinement_substitutions.hs | 7 + .../should_compile/refinement_substitutions.stderr | 188 +++++++++ .../tests/typecheck/should_fail/T13075.stderr | 3 + testsuite/tests/typecheck/should_fail/T14761a.hs | 3 + .../tests/typecheck/should_fail/T14761a.stderr | 7 + testsuite/tests/typecheck/should_fail/T14761b.hs | 5 + .../tests/typecheck/should_fail/T14761b.stderr | 7 + testsuite/tests/typecheck/should_fail/T7210.stderr | 1 + testsuite/tests/typecheck/should_fail/all.T | 4 +- utils/ghc-cabal/ghc.mk | 2 +- utils/haddock | 2 +- 95 files changed, 1683 insertions(+), 802 deletions(-) From git at git.haskell.org Tue Feb 27 15:27:55 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Feb 2018 15:27:55 +0000 (UTC) Subject: [commit: ghc] wip/docker-ghcci's head updated: Merge branch 'master' of git://git.haskell.org/ghc into wip/docker-ghcci (3650f09) Message-ID: <20180227152755.241AB3A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/docker-ghcci' now includes: 8529fbb Get eqTypeRep to inline 7c173b9 Move `iserv` into `utils` and change package name from `iserv-bin` to `iserv` d5ac582 Fix #14811 by wiring in $tcUnit# a644dff circleci: Add nightly build using devel2 flavour 9080466 base: Fix changelog entry for openTempFile 1ede46d Implement stopgap solution for #14728 918c0b3 Add valid refinement substitution suggestions for typed holes 9ff4cce Build Haddocks with --quickjump bfb90bc Remove doubled words ccda486 Tidy up and consolidate canned CmmReg and CmmGlobals c05529c myThreadId# is trivial; make it an inline primop 4e513bf CBE: re-introduce bgamari's fixes d924c17 testsuite: Add newline to test output fc33f8b Improve error message for UNPACK/strictness annotations. 7f389a5 StgLint overhaul 043466b Rename the types in a GADT constructor in toposorted order 5b63240 Increase the amount of parallelism in circleci. 9fc4608 Bump haddock submodule again 2382bbf Bump process submodule fc04a8f Bump filepath submodule d20524e Bump pretty submodule 9ad3fa1 Bump stm submodule to 2.4.5.0 bd0af2a Bump primitive submodule to 0.6.3.0 e26d774 Bump parsec submodule to 0.3.13.0 1ee5abc Bump haskeline submodule to 0.7.4.2 2cb19b4 Bump text submodule to 1.2.3.0 71294f3 testsuite: Bump allocations for T1969 and T5837 eb2daa2 Change how includes for input file directory works 517c194 Document missing dataToTag# . tagToEnum# rule 81a5e05 circleci: Skip performance tests f511bb5 Add ghc-prim.buildinfo to .gitignore f433659 Slight refactor of stock deriving internals abfe104 Revert "Move `iserv` into `utils` and change package name a032ff7 Add references to #6087 0a3629a Don't use ld.gold when building libraries for GHCi 3483423 Comments in Unify, fixing #12442 bf3f0a6 Update Hadrian submodule c969c98 driver/utils/dynwrapper.c: Remove unused variable be498a2 RTS: Remember to free some pointers cb89ba8 RTS: Remove unused retainer schemes 3d43fd5 Introduce the flag -dsuppress-timestamps to avoid timestamps in dumps. 5e5e60d boot: Create GNUmakefiles for libraries f57c305 testsuite: Bump allocations for T9630 ffdb110 Update .gitignore da4766c circleci: Simplify Hadrian build 8c1d6b7 Tiny refactor in Core Lint 40fa420 Comments only e99fdf7 Fix a nasty bug in the pure unifier d675a35 Better stats for T5837 3dec923 Test for Trac #13075 is working now 51e0a38 Comments only b2996f1 Fix test for Trac #13075 3650f09 Merge branch 'master' of git://git.haskell.org/ghc into wip/docker-ghcci From git at git.haskell.org Tue Feb 27 16:44:39 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Feb 2018 16:44:39 +0000 (UTC) Subject: [commit: ghc] master: Build quick flavor and run some tests on Windows (df2c3b3) Message-ID: <20180227164439.14D813A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/df2c3b3364834d2fd038192c89348fc50a2e0475/ghc >--------------------------------------------------------------- commit df2c3b3364834d2fd038192c89348fc50a2e0475 Author: mrkkrp Date: Fri Feb 16 18:53:31 2018 +0700 Build quick flavor and run some tests on Windows This build fits into the 90 minutes window. >--------------------------------------------------------------- df2c3b3364834d2fd038192c89348fc50a2e0475 .appveyor.sh | 15 +++++++++++++-- appveyor.yml | 2 +- 2 files changed, 14 insertions(+), 3 deletions(-) diff --git a/.appveyor.sh b/.appveyor.sh index 436e54b..b7fde23 100644 --- a/.appveyor.sh +++ b/.appveyor.sh @@ -1,5 +1,8 @@ # Configure the environment MSYSTEM=MINGW64 +THREADS=3 +SKIP_PERF_TESTS=YES +BUILD_FLAVOUR=quick source /etc/profile || true # a terrible, terrible workaround for msys2 brokenness # Don't set -e until after /etc/profile is sourced @@ -35,11 +38,19 @@ case "$1" in # Build the compiler ./boot ./configure --enable-tarballs-autodownload - make -j2 + cat <> mk/build.mk + BuildFlavour=$BUILD_FLAVOUR + ifneq "\$(BuildFlavour)" "" + include mk/flavours/\$(BuildFlavour).mk + endif +EOF + make -j$THREADS ;; "test") - make binary_dist + # This does not finish in time. + # make fasttest THREADS=$THREADS + make binary-dist 7z a ghc-windows.zip *.tar.xz ;; diff --git a/appveyor.yml b/appveyor.yml index 7ccf2e0..bcf35a0 100644 --- a/appveyor.yml +++ b/appveyor.yml @@ -25,6 +25,6 @@ build_script: - bash .appveyor.sh test artifacts: - - path: C:\projects\ghc\ghc-windows.zip + - path: ghc-windows.zip name: GHC Windows bindist type: zip From git at git.haskell.org Tue Feb 27 22:40:51 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Feb 2018 22:40:51 +0000 (UTC) Subject: [commit: ghc] wip/docker-ghcci: Remove nonexistent thingy (74d6e47) Message-ID: <20180227224051.D51233A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/docker-ghcci Link : http://ghc.haskell.org/trac/ghc/changeset/74d6e47073ea271adc766987340f242c2b4cf4e8/ghc >--------------------------------------------------------------- commit 74d6e47073ea271adc766987340f242c2b4cf4e8 Author: David Feuer Date: Tue Feb 27 17:40:23 2018 -0500 Remove nonexistent thingy >--------------------------------------------------------------- 74d6e47073ea271adc766987340f242c2b4cf4e8 .circleci/config.yml | 1 - hadrian | 2 +- libraries/filepath | 2 +- libraries/haskeline | 2 +- libraries/parsec | 2 +- libraries/pretty | 2 +- libraries/primitive | 2 +- libraries/process | 2 +- libraries/stm | 2 +- libraries/text | 2 +- utils/haddock | 2 +- 11 files changed, 10 insertions(+), 11 deletions(-) diff --git a/.circleci/config.yml b/.circleci/config.yml index d632145..a26ef1c 100644 --- a/.circleci/config.yml +++ b/.circleci/config.yml @@ -206,7 +206,6 @@ jobs: BUILD_FLAVOUR: devel2 <<: *buildenv steps: - - *precheckout - checkout - *prepare - *submodules diff --git a/hadrian b/hadrian index da39729..63a5563 160000 --- a/hadrian +++ b/hadrian @@ -1 +1 @@ -Subproject commit da397291a9052387862c27c87ec29b6fce2c7d77 +Subproject commit 63a556382f4b3154ed2ce3a6c8a36f79d9b8e3b1 diff --git a/libraries/filepath b/libraries/filepath index 0991bf3..9c64a63 160000 --- a/libraries/filepath +++ b/libraries/filepath @@ -1 +1 @@ -Subproject commit 0991bf392dbd56b5db9f155ee64fb122ca55017c +Subproject commit 9c64a634c144392f36cdad5c8c067824093a64d6 diff --git a/libraries/haskeline b/libraries/haskeline index 019e08f..1436a8c 160000 --- a/libraries/haskeline +++ b/libraries/haskeline @@ -1 +1 @@ -Subproject commit 019e08f2c91b7cc45e5fb98189193a9f5c2d2d57 +Subproject commit 1436a8c7c8ee5076c99e09fe20943bf6101237af diff --git a/libraries/parsec b/libraries/parsec index 00dd731..1c56e08 160000 --- a/libraries/parsec +++ b/libraries/parsec @@ -1 +1 @@ -Subproject commit 00dd731bc12746ac7d4341348abe733c5373cdb7 +Subproject commit 1c56e0885173accbd3296aa5591a3e0c18084e7a diff --git a/libraries/pretty b/libraries/pretty index c3a1469..445e92d 160000 --- a/libraries/pretty +++ b/libraries/pretty @@ -1 +1 @@ -Subproject commit c3a1469306b35fa5d023dc570554f97f1a90435d +Subproject commit 445e92dd7508978caba5563c1e79b2758dff4767 diff --git a/libraries/primitive b/libraries/primitive index 53f72ce..260cc97 160000 --- a/libraries/primitive +++ b/libraries/primitive @@ -1 +1 @@ -Subproject commit 53f72ce69a4dfde5345cf5809a8b4a1993523367 +Subproject commit 260cc9755ee6928876e5174998425cd5863c34a2 diff --git a/libraries/process b/libraries/process index 7c0b581..2364a36 160000 --- a/libraries/process +++ b/libraries/process @@ -1 +1 @@ -Subproject commit 7c0b58141290b50a338bf391adc0a8c43513165b +Subproject commit 2364a36549d461adc4886ef33f259638336a87d2 diff --git a/libraries/stm b/libraries/stm index 5ea70d4..8194700 160000 --- a/libraries/stm +++ b/libraries/stm @@ -1 +1 @@ -Subproject commit 5ea70d4e15d461888866796a164bf9c177a1e8b8 +Subproject commit 819470093eccb81d058408076df8903e781f551c diff --git a/libraries/text b/libraries/text index a02c2da..2d88a0a 160000 --- a/libraries/text +++ b/libraries/text @@ -1 +1 @@ -Subproject commit a02c2dafafa425bd5f36c8629e98b98daf1cfa1e +Subproject commit 2d88a0a3e8e3bb79260e5c8f61dd6c447f61c5f5 diff --git a/utils/haddock b/utils/haddock index 4804e39..dd80ae1 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit 4804e39144dc0ded9b38dbb3442b6016ac719a1a +Subproject commit dd80ae1773ea6aae48c3c5a899d510699783d6ee From git at git.haskell.org Tue Feb 27 22:50:59 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Feb 2018 22:50:59 +0000 (UTC) Subject: [commit: ghc] wip/docker-ghcci: Silly whoops (107bb36) Message-ID: <20180227225059.65FB93A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/docker-ghcci Link : http://ghc.haskell.org/trac/ghc/changeset/107bb36cdbf5939f2aba4b16227553692afad353/ghc >--------------------------------------------------------------- commit 107bb36cdbf5939f2aba4b16227553692afad353 Author: David Feuer Date: Tue Feb 27 17:50:38 2018 -0500 Silly whoops >--------------------------------------------------------------- 107bb36cdbf5939f2aba4b16227553692afad353 .circleci/images/x86_64-freebsd/Dockerfile | 1 - .circleci/prepare-system.sh | 9 ++++----- 2 files changed, 4 insertions(+), 6 deletions(-) diff --git a/.circleci/images/x86_64-freebsd/Dockerfile b/.circleci/images/x86_64-freebsd/Dockerfile index 1c9916d..5ab8f58 100644 --- a/.circleci/images/x86_64-freebsd/Dockerfile +++ b/.circleci/images/x86_64-freebsd/Dockerfile @@ -32,6 +32,5 @@ RUN apt-get install -y --no-install-recommends \ texinfo \ lbzip2 -RUN ln -s $HOME/.cabal/bin/HsColour /usr/local/bin/HsColour COPY build-toolchain.sh /tmp/ RUN /tmp/build-toolchain.sh x86_64 diff --git a/.circleci/prepare-system.sh b/.circleci/prepare-system.sh index 6365c29..ed01658 100755 --- a/.circleci/prepare-system.sh +++ b/.circleci/prepare-system.sh @@ -22,12 +22,13 @@ EOF case "$(uname)" in Linux) + cabal update + cabal install --reinstall hscolour --index-state=$hackage_index_state + ln -s $HOME/.cabal/bin/HsColour /usr/local/bin/HsColour + if [[ -n ${TARGET:-} ]]; then if [[ $TARGET = FreeBSD ]]; then # cross-compiling to FreeBSD - cabal update - cabal install --reinstall hscolour --index-state=$hackage_index_state - echo 'HADDOCK_DOCS = NO' >> mk/build.mk echo 'WERROR=' >> mk/build.mk # https://circleci.com/docs/2.0/env-vars/#interpolating-environment-variables-to-set-other-environment-variables @@ -37,8 +38,6 @@ case "$(uname)" in fi else # assuming Ubuntu - cabal update - cabal install --reinstall hscolour --index-state=$hackage_index_state fi ;; Darwin) From git at git.haskell.org Tue Feb 27 23:00:02 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Feb 2018 23:00:02 +0000 (UTC) Subject: [commit: ghc] wip/docker-ghcci: Shell syntax (e55310c) Message-ID: <20180227230002.2FBFC3A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/docker-ghcci Link : http://ghc.haskell.org/trac/ghc/changeset/e55310c81e27bccacbe52f849271e0a10c62a2af/ghc >--------------------------------------------------------------- commit e55310c81e27bccacbe52f849271e0a10c62a2af Author: David Feuer Date: Tue Feb 27 17:59:46 2018 -0500 Shell syntax >--------------------------------------------------------------- e55310c81e27bccacbe52f849271e0a10c62a2af .circleci/prepare-system.sh | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.circleci/prepare-system.sh b/.circleci/prepare-system.sh index ed01658..47fbcb1 100755 --- a/.circleci/prepare-system.sh +++ b/.circleci/prepare-system.sh @@ -36,7 +36,7 @@ case "$(uname)" in else fail "TARGET=$target not supported" fi - else +# else # assuming Ubuntu fi ;; From git at git.haskell.org Tue Feb 27 23:08:45 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Feb 2018 23:08:45 +0000 (UTC) Subject: [commit: ghc] wip/docker-ghcci: Perm error (0d8c020) Message-ID: <20180227230845.9D8883A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/docker-ghcci Link : http://ghc.haskell.org/trac/ghc/changeset/0d8c020aba9ed5c817e553f0dbbb436245afa0e0/ghc >--------------------------------------------------------------- commit 0d8c020aba9ed5c817e553f0dbbb436245afa0e0 Author: David Feuer Date: Tue Feb 27 18:08:22 2018 -0500 Perm error >--------------------------------------------------------------- 0d8c020aba9ed5c817e553f0dbbb436245afa0e0 .circleci/config.yml | 8 ++++---- .circleci/images/x86_64-freebsd/Dockerfile | 1 + .circleci/images/x86_64-linux/Dockerfile | 2 ++ .circleci/prepare-system.sh | 1 - 4 files changed, 7 insertions(+), 5 deletions(-) diff --git a/.circleci/config.yml b/.circleci/config.yml index a26ef1c..8507e23 100644 --- a/.circleci/config.yml +++ b/.circleci/config.yml @@ -86,7 +86,7 @@ jobs: "validate-x86_64-linux": resource_class: xlarge docker: - - image: dfeuer/ghcci:x86_64-linux-0.0.3 + - image: dfeuer/ghcci:x86_64-linux-0.0.4 environment: <<: *buildenv steps: @@ -144,7 +144,7 @@ jobs: "validate-hadrian-x86_64-linux": resource_class: xlarge docker: - - image: dfeuer/ghcci:x86_64-linux-0.0.3 + - image: dfeuer/ghcci:x86_64-linux-0.0.4 environment: <<: *buildenv steps: @@ -158,7 +158,7 @@ jobs: "validate-x86_64-linux-unreg": resource_class: xlarge docker: - - image: dfeuer/ghcci:x86_64-linux-0.0.3 + - image: dfeuer/ghcci:x86_64-linux-0.0.4 environment: <<: *buildenv steps: @@ -173,7 +173,7 @@ jobs: "validate-x86_64-linux-llvm": resource_class: xlarge docker: - - image: dfeuer/ghcci:x86_64-linux-0.0.3 + - image: dfeuer/ghcci:x86_64-linux-0.0.4 environment: <<: *buildenv BUILD_FLAVOUR: perf-llvm diff --git a/.circleci/images/x86_64-freebsd/Dockerfile b/.circleci/images/x86_64-freebsd/Dockerfile index 5ab8f58..9a661c1 100644 --- a/.circleci/images/x86_64-freebsd/Dockerfile +++ b/.circleci/images/x86_64-freebsd/Dockerfile @@ -34,3 +34,4 @@ RUN apt-get install -y --no-install-recommends \ COPY build-toolchain.sh /tmp/ RUN /tmp/build-toolchain.sh x86_64 +RUN ln -s $HOME/.cabal/bin/HsColour /usr/local/bin/HsColour diff --git a/.circleci/images/x86_64-linux/Dockerfile b/.circleci/images/x86_64-linux/Dockerfile index bfc4a8c..4630ba2 100644 --- a/.circleci/images/x86_64-linux/Dockerfile +++ b/.circleci/images/x86_64-linux/Dockerfile @@ -8,4 +8,6 @@ RUN apt-get install -qy openssh-client RUN apt-get install -qy git make automake autoconf gcc perl python3 texinfo xz-utils lbzip2 patch +RUN ln -s $HOME/.cabal/bin/HsColour /usr/local/bin/HsColour + USER ghc diff --git a/.circleci/prepare-system.sh b/.circleci/prepare-system.sh index 47fbcb1..506df63 100755 --- a/.circleci/prepare-system.sh +++ b/.circleci/prepare-system.sh @@ -24,7 +24,6 @@ case "$(uname)" in Linux) cabal update cabal install --reinstall hscolour --index-state=$hackage_index_state - ln -s $HOME/.cabal/bin/HsColour /usr/local/bin/HsColour if [[ -n ${TARGET:-} ]]; then if [[ $TARGET = FreeBSD ]]; then From git at git.haskell.org Tue Feb 27 23:21:10 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Feb 2018 23:21:10 +0000 (UTC) Subject: [commit: ghc] wip/docker-ghcci: Try hscolour again? (47caf33) Message-ID: <20180227232110.A2D173A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/docker-ghcci Link : http://ghc.haskell.org/trac/ghc/changeset/47caf33120f4153dd90e00771747fc466daf4833/ghc >--------------------------------------------------------------- commit 47caf33120f4153dd90e00771747fc466daf4833 Author: David Feuer Date: Tue Feb 27 18:20:49 2018 -0500 Try hscolour again? >--------------------------------------------------------------- 47caf33120f4153dd90e00771747fc466daf4833 .circleci/prepare-system.sh | 1 + 1 file changed, 1 insertion(+) diff --git a/.circleci/prepare-system.sh b/.circleci/prepare-system.sh index 506df63..84fd513 100755 --- a/.circleci/prepare-system.sh +++ b/.circleci/prepare-system.sh @@ -16,6 +16,7 @@ V=1 HADDOCK_DOCS=YES LATEX_DOCS=YES HSCOLOUR_SRCS=YES +HSCOLOUR_CMD=/usr/local/bin/HsColour BUILD_DOCBOOK_HTML=YES BeConservative=YES EOF From git at git.haskell.org Wed Feb 28 00:50:46 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 28 Feb 2018 00:50:46 +0000 (UTC) Subject: [commit: ghc] wip/docker-ghcci: How'd we lose parsec? (860f0d6) Message-ID: <20180228005046.4F9A53A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/docker-ghcci Link : http://ghc.haskell.org/trac/ghc/changeset/860f0d645908ee8fa4777f750e41022b7ba09159/ghc >--------------------------------------------------------------- commit 860f0d645908ee8fa4777f750e41022b7ba09159 Author: David Feuer Date: Tue Feb 27 19:50:09 2018 -0500 How'd we lose parsec? >--------------------------------------------------------------- 860f0d645908ee8fa4777f750e41022b7ba09159 .circleci/prepare-system.sh | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.circleci/prepare-system.sh b/.circleci/prepare-system.sh index 84fd513..6ab53f0 100755 --- a/.circleci/prepare-system.sh +++ b/.circleci/prepare-system.sh @@ -24,7 +24,7 @@ EOF case "$(uname)" in Linux) cabal update - cabal install --reinstall hscolour --index-state=$hackage_index_state + cabal install --reinstall hscolour parsec --index-state=$hackage_index_state if [[ -n ${TARGET:-} ]]; then if [[ $TARGET = FreeBSD ]]; then From git at git.haskell.org Wed Feb 28 01:25:20 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 28 Feb 2018 01:25:20 +0000 (UTC) Subject: [commit: ghc] wip/docker-ghcci: Revert "How'd we lose parsec?" (edbf8bb) Message-ID: <20180228012520.4A7133A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/docker-ghcci Link : http://ghc.haskell.org/trac/ghc/changeset/edbf8bba5e195f6efffd9f432294d1c9b3649c64/ghc >--------------------------------------------------------------- commit edbf8bba5e195f6efffd9f432294d1c9b3649c64 Author: David Feuer Date: Tue Feb 27 20:04:21 2018 -0500 Revert "How'd we lose parsec?" This reverts commit 860f0d645908ee8fa4777f750e41022b7ba09159. >--------------------------------------------------------------- edbf8bba5e195f6efffd9f432294d1c9b3649c64 .circleci/prepare-system.sh | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.circleci/prepare-system.sh b/.circleci/prepare-system.sh index 6ab53f0..84fd513 100755 --- a/.circleci/prepare-system.sh +++ b/.circleci/prepare-system.sh @@ -24,7 +24,7 @@ EOF case "$(uname)" in Linux) cabal update - cabal install --reinstall hscolour parsec --index-state=$hackage_index_state + cabal install --reinstall hscolour --index-state=$hackage_index_state if [[ -n ${TARGET:-} ]]; then if [[ $TARGET = FreeBSD ]]; then From git at git.haskell.org Wed Feb 28 01:25:26 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 28 Feb 2018 01:25:26 +0000 (UTC) Subject: [commit: ghc] wip/docker-ghcci: Put the submodules back. (2af6ad2) Message-ID: <20180228012526.19B223A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/docker-ghcci Link : http://ghc.haskell.org/trac/ghc/changeset/2af6ad2418f140399cbe4582cc230c1a5b3ff29f/ghc >--------------------------------------------------------------- commit 2af6ad2418f140399cbe4582cc230c1a5b3ff29f Author: David Feuer Date: Tue Feb 27 20:21:38 2018 -0500 Put the submodules back. >--------------------------------------------------------------- 2af6ad2418f140399cbe4582cc230c1a5b3ff29f .circleci/config.yml | 1 - 1 file changed, 1 deletion(-) diff --git a/.circleci/config.yml b/.circleci/config.yml index 89c6537..8507e23 100644 --- a/.circleci/config.yml +++ b/.circleci/config.yml @@ -206,7 +206,6 @@ jobs: BUILD_FLAVOUR: devel2 <<: *buildenv steps: - - *precheckout - checkout - *prepare - *submodules From git at git.haskell.org Wed Feb 28 01:25:23 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 28 Feb 2018 01:25:23 +0000 (UTC) Subject: [commit: ghc] wip/docker-ghcci: Revert "Remove nonexistent thingy" (80598cd) Message-ID: <20180228012523.4340B3A5F6@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/docker-ghcci Link : http://ghc.haskell.org/trac/ghc/changeset/80598cd553be99612174e38b9c06c2500a919dfa/ghc >--------------------------------------------------------------- commit 80598cd553be99612174e38b9c06c2500a919dfa Author: David Feuer Date: Tue Feb 27 20:20:38 2018 -0500 Revert "Remove nonexistent thingy" This reverts commit 74d6e47073ea271adc766987340f242c2b4cf4e8. >--------------------------------------------------------------- 80598cd553be99612174e38b9c06c2500a919dfa .circleci/config.yml | 1 + hadrian | 2 +- libraries/filepath | 2 +- libraries/haskeline | 2 +- libraries/parsec | 2 +- libraries/pretty | 2 +- libraries/primitive | 2 +- libraries/process | 2 +- libraries/stm | 2 +- libraries/text | 2 +- utils/haddock | 2 +- 11 files changed, 11 insertions(+), 10 deletions(-) diff --git a/.circleci/config.yml b/.circleci/config.yml index 8507e23..89c6537 100644 --- a/.circleci/config.yml +++ b/.circleci/config.yml @@ -206,6 +206,7 @@ jobs: BUILD_FLAVOUR: devel2 <<: *buildenv steps: + - *precheckout - checkout - *prepare - *submodules diff --git a/hadrian b/hadrian index 63a5563..da39729 160000 --- a/hadrian +++ b/hadrian @@ -1 +1 @@ -Subproject commit 63a556382f4b3154ed2ce3a6c8a36f79d9b8e3b1 +Subproject commit da397291a9052387862c27c87ec29b6fce2c7d77 diff --git a/libraries/filepath b/libraries/filepath index 9c64a63..0991bf3 160000 --- a/libraries/filepath +++ b/libraries/filepath @@ -1 +1 @@ -Subproject commit 9c64a634c144392f36cdad5c8c067824093a64d6 +Subproject commit 0991bf392dbd56b5db9f155ee64fb122ca55017c diff --git a/libraries/haskeline b/libraries/haskeline index 1436a8c..019e08f 160000 --- a/libraries/haskeline +++ b/libraries/haskeline @@ -1 +1 @@ -Subproject commit 1436a8c7c8ee5076c99e09fe20943bf6101237af +Subproject commit 019e08f2c91b7cc45e5fb98189193a9f5c2d2d57 diff --git a/libraries/parsec b/libraries/parsec index 1c56e08..00dd731 160000 --- a/libraries/parsec +++ b/libraries/parsec @@ -1 +1 @@ -Subproject commit 1c56e0885173accbd3296aa5591a3e0c18084e7a +Subproject commit 00dd731bc12746ac7d4341348abe733c5373cdb7 diff --git a/libraries/pretty b/libraries/pretty index 445e92d..c3a1469 160000 --- a/libraries/pretty +++ b/libraries/pretty @@ -1 +1 @@ -Subproject commit 445e92dd7508978caba5563c1e79b2758dff4767 +Subproject commit c3a1469306b35fa5d023dc570554f97f1a90435d diff --git a/libraries/primitive b/libraries/primitive index 260cc97..53f72ce 160000 --- a/libraries/primitive +++ b/libraries/primitive @@ -1 +1 @@ -Subproject commit 260cc9755ee6928876e5174998425cd5863c34a2 +Subproject commit 53f72ce69a4dfde5345cf5809a8b4a1993523367 diff --git a/libraries/process b/libraries/process index 2364a36..7c0b581 160000 --- a/libraries/process +++ b/libraries/process @@ -1 +1 @@ -Subproject commit 2364a36549d461adc4886ef33f259638336a87d2 +Subproject commit 7c0b58141290b50a338bf391adc0a8c43513165b diff --git a/libraries/stm b/libraries/stm index 8194700..5ea70d4 160000 --- a/libraries/stm +++ b/libraries/stm @@ -1 +1 @@ -Subproject commit 819470093eccb81d058408076df8903e781f551c +Subproject commit 5ea70d4e15d461888866796a164bf9c177a1e8b8 diff --git a/libraries/text b/libraries/text index 2d88a0a..a02c2da 160000 --- a/libraries/text +++ b/libraries/text @@ -1 +1 @@ -Subproject commit 2d88a0a3e8e3bb79260e5c8f61dd6c447f61c5f5 +Subproject commit a02c2dafafa425bd5f36c8629e98b98daf1cfa1e diff --git a/utils/haddock b/utils/haddock index dd80ae1..4804e39 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit dd80ae1773ea6aae48c3c5a899d510699783d6ee +Subproject commit 4804e39144dc0ded9b38dbb3442b6016ac719a1a