[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 6 commits: base: Mark CPUTime001 as fragile
Marge Bot
gitlab at gitlab.haskell.org
Mon Jun 10 14:31:53 UTC 2019
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
1a3420ca by Ben Gamari at 2019-06-10T11:59:41Z
base: Mark CPUTime001 as fragile
As noted in #16224, CPUTime001 has been quite problematic, reporting
non-monotonic timestamps in CI. Unfortunately I've been unable to
reproduce this locally.
- - - - -
9bc10993 by Vladislav Zavialov at 2019-06-10T12:00:16Z
Print role annotations in TemplateHaskell brackets (#16718)
- - - - -
ec2bc8dd by Richard Eisenberg at 2019-06-10T14:31:46Z
Comments only: document newtypes' DataConWrapId
- - - - -
75f146af by David Eichmann at 2019-06-10T14:31:48Z
Refactor the rules for .hi and .o into a single rule using `&%>` #16764
Currently the rule for .hi files just triggers (via need) the rule
for the .o file, and .o rule generates both the .o and .hi file.
Likewise for .o-boot and .hi-boot files. This is a bit of an abuse
of Shake, and in fact shake supports rules with multiple output
with the &%> function. This exact use case appears in Neil
Mitchell's paper *Shake Before Building* section 6.3.
- - - - -
2d4855d8 by Ben Gamari at 2019-06-10T14:31:48Z
testsuite: Fix and extend closure_size test
This was previously broken in several ways. This is fixed and it also
now tests arrays. Unfortunately I was unable to find a way to continue
testing PAP and FUN sizes; these simply depend too much upon the
behavior of the simplifier.
I also tried to extend this to test non-empty arrays as well but
unfortunately this was non-trivial as the array card size constant isn't
readily available from haskell.
Fixes #16531.
- - - - -
21f1960d by Ben Gamari at 2019-06-10T14:31:48Z
ghc-heap: Add closure_size_noopt test
This adds a new test, only run in the `normal` way, to verify the size
of FUNs and PAPs.
- - - - -
12 changed files:
- compiler/basicTypes/MkId.hs
- compiler/hsSyn/HsDecls.hs
- hadrian/src/Rules/Compile.hs
- libraries/base/tests/all.T
- + libraries/ghc-heap/tests/ClosureSizeUtils.hs
- libraries/ghc-heap/tests/all.T
- libraries/ghc-heap/tests/closure_size.hs
- + libraries/ghc-heap/tests/closure_size_noopt.hs
- + testsuite/tests/roles/should_compile/T16718.hs
- + testsuite/tests/roles/should_compile/T16718.stderr
- testsuite/tests/roles/should_compile/all.T
- testsuite/tests/th/T15365.stderr
Changes:
=====================================
compiler/basicTypes/MkId.hs
=====================================
@@ -298,6 +298,24 @@ so the data constructor for T:C had a single argument, namely the
predicate (C a). But now we treat that as an ordinary argument, not
part of the theta-type, so all is well.
+Note [Newtype workers]
+~~~~~~~~~~~~~~~~~~~~~~
+A newtype does not really have a worker. Instead, newtype constructors
+just unfold into a cast. But we need *something* for, say, MkAge to refer
+to. So, we do this:
+
+* The Id used as the newtype worker will have a compulsory unfolding to
+ a cast. See Note [Compulsory newtype unfolding]
+
+* This Id is labeled as a DataConWrapId. We don't want to use a DataConWorkId,
+ as those have special treatment in the back end.
+
+* There is no top-level binding, because the compulsory unfolding
+ means that it will be inlined (to a cast) at every call site.
+
+We probably should have a NewtypeWorkId, but these Ids disappear as soon as
+we desugar anyway, so it seems a step too far.
+
Note [Compulsory newtype unfolding]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Newtype wrappers, just like workers, have compulsory unfoldings.
@@ -447,6 +465,8 @@ mkDataConWorkId :: Name -> DataCon -> Id
mkDataConWorkId wkr_name data_con
| isNewTyCon tycon
= mkGlobalId (DataConWrapId data_con) wkr_name wkr_ty nt_work_info
+ -- See Note [Newtype workers]
+
| otherwise
= mkGlobalId (DataConWorkId data_con) wkr_name wkr_ty alg_wkr_info
=====================================
compiler/hsSyn/HsDecls.hs
=====================================
@@ -302,6 +302,7 @@ instance (p ~ GhcPass pass, OutputableBndrId p) => Outputable (HsGroup p) where
if isEmptyValBinds val_decls
then Nothing
else Just (ppr val_decls),
+ ppr_ds (tyClGroupRoleDecls tycl_decls),
ppr_ds (tyClGroupTyClDecls tycl_decls),
ppr_ds (tyClGroupInstDecls tycl_decls),
ppr_ds deriv_decls,
=====================================
hadrian/src/Rules/Compile.hs
=====================================
@@ -4,7 +4,7 @@ import Hadrian.BuildPath
import Hadrian.Oracles.TextFile
import Base
-import Context
+import Context as C
import Expression
import Rules.Generate
import Settings
@@ -30,16 +30,29 @@ compilePackage rs = do
--
-- and parse the information we need (stage, package path, ...) from
-- the path and figure out the suitable way to produce that object file.
- objectFilesUnder root |%> \path -> do
- obj <- parsePath (parseBuildObject root) "<object file path parser>" path
- compileObject rs path obj
+ alternatives $ do
+ -- Language is identified by subdirectory under /build.
+ -- These are non-haskell files so only have a .o or .<way>_o suffix.
+ [ root -/- "**/build/c/**/*." ++ wayPat ++ "o"
+ | wayPat <- wayPats] |%> compileNonHsObject rs C
+
+ [ root -/- "**/build/cmm/**/*." ++ wayPat ++ "o"
+ | wayPat <- wayPats] |%> compileNonHsObject rs Cmm
+
+ [ root -/- "**/build/s/**/*." ++ wayPat ++ "o"
+ | wayPat <- wayPats] |%> compileNonHsObject rs Asm
+
+ -- All else is haskell.
+ -- This comes last as it overlaps with the above rules' file patterns.
+ forM_ ((,) <$> hsExts <*> wayPats) $ \ ((oExt, hiExt), wayPat) ->
+ [ root -/- "**/build/**/*." ++ wayPat ++ oExt
+ , root -/- "**/build/**/*." ++ wayPat ++ hiExt ]
+ &%> \ [o, _hi] -> compileHsObjectAndHi rs o
where
- objectFilesUnder r = [ r -/- ("**/build/**/*" ++ pat)
- | pat <- extensionPats ]
-
- exts = [ "o", "hi", "o-boot", "hi-boot" ]
- patternsFor e = [ "." ++ e, ".*_" ++ e ]
- extensionPats = concatMap patternsFor exts
+ hsExts = [ ("o", "hi")
+ , ("o-boot", "hi-boot")
+ ]
+ wayPats = [ "", "*_" ]
-- * Object file paths types and parsers
@@ -153,67 +166,47 @@ objectContext (BuildPath _ stage pkgPath obj) =
-- * Building an object
-compileHsObject
- :: [(Resource, Int)] -> FilePath -> BuildPath Object -> HsObject -> Action ()
-compileHsObject rs objpath b@(BuildPath _root stage _path _o) hsobj =
- case hsobj of
- HsObject _basename (Extension way Hi ) -> need [objpath -<.> osuf way]
- HsObject _basename (Extension way HiBoot) -> need [objpath -<.> obootsuf way]
- HsObject _basename (Extension way suf) -> do
- let ctx = objectContext b
- ctxPath <- contextPath ctx
- (src, deps) <- lookupDependencies (ctxPath -/- ".dependencies") objpath
- need (src:deps)
- needLibrary =<< contextDependencies ctx
-
- -- The .dependencies files only lists shallow dependencies. ghc will
- -- generally read more *.hi and *.hi-boot files (deep dependencies).
- -- Allow such reads (see https://gitlab.haskell.org/ghc/ghc/wikis/Developing-Hadrian#cloud-shared-cache-build)
- -- Note that this may allow too many *.hi and *.hi-boot files, but
- -- calculating the exact set of deep dependencies is not feasible.
- trackAllow [ "//*." ++ hisuf way
- , "//*." ++ hibootsuf way
- ]
-
- buildWithResources rs $ target ctx (Ghc CompileHs stage) [src] [objpath]
- -- Andrey: It appears that the previous refactoring has broken
- -- multiple-output build rules. Ideally, we should bring multiple-output
- -- rules back, see: https://github.com/snowleopard/hadrian/issues/216.
- -- As a temporary solution, I'm using Shake's new 'produces' feature to
- -- record that this rule also produces a corresponding interface file.
- let hi | suf == O = objpath -<.> hisuf way
- | suf == OBoot = objpath -<.> hibootsuf way
- | otherwise = error "Internal error: unknown Haskell object extension"
- produces [hi]
-
-compileNonHsObject
- :: [(Resource, Int)] -> FilePath -> BuildPath Object -> NonHsObject
- -> Action ()
-compileNonHsObject rs objpath b@(BuildPath _root stage _path _o) nonhsobj =
- case nonhsobj of
- NonHsObject lang _basename _way ->
- go (builderFor lang) (toSrcFor lang)
-
- where builderFor C = Ghc CompileCWithGhc
- builderFor _ = Ghc CompileHs
-
- toSrcFor Asm = obj2src "S" (const False)
- toSrcFor C = obj2src "c" (const False)
- toSrcFor Cmm = obj2src "cmm" isGeneratedCmmFile
-
- go builder tosrc = do
- let ctx = objectContext b
- src <- tosrc ctx objpath
- need [src]
- needDependencies ctx src (objpath <.> "d")
- buildWithResources rs $ target ctx (builder stage) [src] [objpath]
-
-compileObject
- :: [(Resource, Int)] -> FilePath -> BuildPath Object -> Action ()
-compileObject rs objpath b@(BuildPath _root _stage _path (Hs o)) =
- compileHsObject rs objpath b o
-compileObject rs objpath b@(BuildPath _root _stage _path (NonHs o)) =
- compileNonHsObject rs objpath b o
+compileHsObjectAndHi
+ :: [(Resource, Int)] -> FilePath -> Action ()
+compileHsObjectAndHi rs objpath = do
+ root <- buildRoot
+ b@(BuildPath _root stage _path _o)
+ <- parsePath (parseBuildObject root) "<object file path parser>" objpath
+ let ctx = objectContext b
+ way = C.way ctx
+ ctxPath <- contextPath ctx
+ (src, deps) <- lookupDependencies (ctxPath -/- ".dependencies") objpath
+ need (src:deps)
+ needLibrary =<< contextDependencies ctx
+
+ -- The .dependencies file lists indicating inputs. ghc will
+ -- generally read more *.hi and *.hi-boot files (direct inputs).
+ -- Allow such reads (see https://gitlab.haskell.org/ghc/ghc/wikis/Developing-Hadrian#haskell-object-files-and-hi-inputs)
+ -- Note that this may allow too many *.hi and *.hi-boot files, but
+ -- calculating the exact set of direct inputs is not feasible.
+ trackAllow [ "//*." ++ hisuf way
+ , "//*." ++ hibootsuf way
+ ]
+
+ buildWithResources rs $ target ctx (Ghc CompileHs stage) [src] [objpath]
+
+compileNonHsObject :: [(Resource, Int)] -> SourceLang -> FilePath -> Action ()
+compileNonHsObject rs lang path = do
+ root <- buildRoot
+ b@(BuildPath _root stage _path _o)
+ <- parsePath (parseBuildObject root) "<object file path parser>" path
+ let
+ ctx = objectContext b
+ builder = case lang of
+ C -> Ghc CompileCWithGhc
+ _ -> Ghc CompileHs
+ src <- case lang of
+ Asm -> obj2src "S" (const False) ctx path
+ C -> obj2src "c" (const False) ctx path
+ Cmm -> obj2src "cmm" isGeneratedCmmFile ctx path
+ need [src]
+ needDependencies ctx src (path <.> "d")
+ buildWithResources rs $ target ctx (builder stage) [src] [path]
-- * Helpers
=====================================
libraries/base/tests/all.T
=====================================
@@ -20,7 +20,7 @@ test('tempfiles', normal, compile_and_run, [''])
test('fixed', normal, compile_and_run, [''])
test('quotOverflow', normal, compile_and_run, [''])
test('assert', exit_code(1), compile_and_run, ['-fno-ignore-asserts'])
-test('CPUTime001', normal, compile_and_run, [''])
+test('CPUTime001', fragile(16224), compile_and_run, [''])
test('readLitChar', normal, compile_and_run, [''])
test('unicode001',
when(platform('i386-unknown-openbsd'), expect_fail),
=====================================
libraries/ghc-heap/tests/ClosureSizeUtils.hs
=====================================
@@ -0,0 +1,52 @@
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE BangPatterns #-}
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE TypeApplications #-}
+{-# LANGUAGE TypeInType #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+
+-- | Utilities for the @closure_size@ tests
+module ClosureSizeUtils (assertSize, assertSizeUnlifted) where
+
+import Control.Monad
+import GHC.Exts
+import GHC.Exts.Heap.Closures
+import GHC.Stack
+import Type.Reflection
+
+profHeaderSize :: Int
+#if PROFILING
+profHeaderSize = 2
+#else
+profHeaderSize = 0
+#endif
+
+assertSize
+ :: forall a. (HasCallStack, Typeable a)
+ => a -- ^ closure
+ -> Int -- ^ expected size in words
+ -> IO ()
+assertSize x =
+ assertSizeBox (asBox x) (typeRep @a)
+
+assertSizeUnlifted
+ :: forall (a :: TYPE 'UnliftedRep). (HasCallStack, Typeable a)
+ => a -- ^ closure
+ -> Int -- ^ expected size in words
+ -> IO ()
+assertSizeUnlifted x =
+ assertSizeBox (Box (unsafeCoerce# x)) (typeRep @a)
+
+assertSizeBox
+ :: forall a. (HasCallStack)
+ => Box -- ^ closure
+ -> TypeRep a
+ -> Int -- ^ expected size in words
+ -> IO ()
+assertSizeBox x ty expected = do
+ let !size = closureSize x
+ when (size /= expected') $ do
+ putStrLn $ "closureSize ("++show ty++") == "++show size++", expected "++show expected'
+ putStrLn $ prettyCallStack callStack
+ where expected' = expected + profHeaderSize
+{-# NOINLINE assertSize #-}
=====================================
libraries/ghc-heap/tests/all.T
=====================================
@@ -1,11 +1,26 @@
test('heap_all',
- [when(have_profiling(),
- extra_ways(['prof'])),
+ [when(have_profiling(), extra_ways(['prof'])),
# These ways produce slightly different heap representations.
# Currently we don't test them.
omit_ways(['ghci', 'hpc'])
],
compile_and_run, [''])
+
+# Test everything except FUNs and PAPs in all ways.
test('closure_size',
- omit_ways(['ghci', 'hpc', 'prof']),
+ [extra_files(['ClosureSizeUtils.hs']),
+ when(have_profiling(), extra_ways(['prof'])),
+ # These ways produce slightly different heap representations.
+ # Currently we don't test them.
+ omit_ways(['hpc'])
+ ],
+ compile_and_run, [''])
+
+# Test PAPs and FUNs only in normal way (e.g. with -O0)
+# since otherwise the simplifier interferes.
+test('closure_size_noopt',
+ [extra_files(['ClosureSizeUtils.hs']),
+ only_ways(['normal'])
+ ],
compile_and_run, [''])
+
=====================================
libraries/ghc-heap/tests/closure_size.hs
=====================================
@@ -1,25 +1,20 @@
-{-# LANGUAGE BangPatterns #-}
-{-# LANGUAGE TypeApplications #-}
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE KindSignatures #-}
+{-# LANGUAGE UnboxedTuples #-}
+{-# LANGUAGE TypeInType #-}
{-# LANGUAGE ScopedTypeVariables #-}
-import Control.Monad
-import Type.Reflection
-import GHC.Stack
+import GHC.Exts
+import GHC.IO
+import ClosureSizeUtils
-import GHC.Exts.Heap.Closures
+data A = A (Array# Int)
+data MA = MA (MutableArray# RealWorld Int)
+data BA = BA ByteArray#
+data MBA = MBA (MutableByteArray# RealWorld)
+data B = B BCO#
+data APC a = APC a
-assertSize :: forall a. (HasCallStack, Typeable a)
- => a -> Int -> IO ()
-assertSize !x expected = do
- let !size = closureSize (asBox x)
- when (size /= expected) $ do
- putStrLn $ "closureSize ("++show (typeRep @a)++") == "++show size++", expected "++show expected
- putStrLn $ prettyCallStack callStack
-{-# NOINLINE assertSize #-}
-
-pap :: Int -> Char -> Int
-pap x _ = x
-{-# NOINLINE pap #-}
main :: IO ()
main = do
@@ -28,7 +23,26 @@ main = do
assertSize (Nothing :: Maybe ()) 2
assertSize ((1,2) :: (Int,Int)) 3
assertSize ((1,2,3) :: (Int,Int,Int)) 4
- assertSize (id :: Int -> Int) 1
- assertSize (fst :: (Int,Int) -> Int) 1
- assertSize (pap 1) 2
+ MA ma <- IO $ \s ->
+ case newArray# 0# 0 s of
+ (# s1, x #) -> (# s1, MA x #)
+
+ A a <- IO $ \s ->
+ case freezeArray# ma 0# 0# s of
+ (# s1, x #) -> (# s1, A x #)
+
+ MBA mba <- IO $ \s ->
+ case newByteArray# 0# s of
+ (# s1, x #) -> (# s1, MBA x #)
+
+ BA ba <- IO $ \s ->
+ case newByteArray# 0# s of
+ (# s1, x #) ->
+ case unsafeFreezeByteArray# x s1 of
+ (# s2, y #) -> (# s2, BA y #)
+
+ assertSizeUnlifted ma 3
+ assertSizeUnlifted a 3
+ assertSizeUnlifted mba 2
+ assertSizeUnlifted ba 2
=====================================
libraries/ghc-heap/tests/closure_size_noopt.hs
=====================================
@@ -0,0 +1,12 @@
+import ClosureSizeUtils
+
+pap :: Int -> Char -> Int
+pap x _ = x
+{-# NOINLINE pap #-}
+
+main :: IO ()
+main = do
+ assertSize (id :: Int -> Int) 1
+ assertSize (fst :: (Int,Int) -> Int) 1
+ assertSize (pap 1) 2
+
=====================================
testsuite/tests/roles/should_compile/T16718.hs
=====================================
@@ -0,0 +1,7 @@
+{-# LANGUAGE RoleAnnotations, TemplateHaskell #-}
+
+module T16718 where
+
+$([d| type role P phantom
+ data P a
+ |])
=====================================
testsuite/tests/roles/should_compile/T16718.stderr
=====================================
@@ -0,0 +1,7 @@
+T16718.hs:(5,3)-(7,6): Splicing declarations
+ [d| type role P phantom
+
+ data P a |]
+ ======>
+ type role P phantom
+ data P a
=====================================
testsuite/tests/roles/should_compile/all.T
=====================================
@@ -10,3 +10,4 @@ test('T8958', [normalise_fun(normalise_errmsg), only_ways('normal')], compile, [
test('T10263', normal, compile, [''])
test('T9204b', [], multimod_compile, ['T9204b', '-v0'])
test('T14101', normal, compile, [''])
+test('T16718', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
=====================================
testsuite/tests/th/T15365.stderr
=====================================
@@ -4,6 +4,8 @@ T15365.hs:(9,3)-(31,6): Splicing declarations
pattern (:!!!) :: Bool
pattern (:!!!) = True
+ type role (***)
+
type (|||) = Either
data (***)
class (???)
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/e19159dba3e59c2fa38d5809c889a1e2eb61775f...21f1960ddafc5b1f7c6bc6bb004ff45d24c74962
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/e19159dba3e59c2fa38d5809c889a1e2eb61775f...21f1960ddafc5b1f7c6bc6bb004ff45d24c74962
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20190610/7fab4663/attachment-0001.html>
More information about the ghc-commits
mailing list