[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 7 commits: Comments only: document newtypes' DataConWrapId
Marge Bot
gitlab at gitlab.haskell.org
Tue Jun 11 04:24:28 UTC 2019
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
0345b1b0 by Richard Eisenberg at 2019-06-11T03:52:10Z
Comments only: document newtypes' DataConWrapId
- - - - -
58a5d728 by David Eichmann at 2019-06-11T03:52:50Z
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.
- - - - -
2f945086 by Ben Gamari at 2019-06-11T03:53:25Z
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.
- - - - -
e5d275f4 by Ben Gamari at 2019-06-11T03:53:25Z
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.
- - - - -
5278d1a8 by Oleg Grenrus at 2019-06-11T04:24:18Z
Add -Winferred-safe-imports warning
This commit partly reverts e69619e923e84ae61a6bb4357f06862264daa94b
commit by reintroducing Sf_SafeInferred SafeHaskellMode.
We preserve whether module was declared or inferred Safe. When
declared-Safe module imports inferred-Safe, we warn. This inferred
status is volatile, often enough it's a happy coincidence, something
which cannot be relied upon. However, explicitly Safe or Trustworthy
packages won't accidentally become Unsafe.
Updates haddock submodule.
- - - - -
a9bd5e24 by Oleg Grenrus at 2019-06-11T04:24:18Z
Add -Wmissing-safe-haskell-mode warning
- - - - -
1d3c656e by Alp Mestanogullari at 2019-06-11T04:24:21Z
testsuite/mk/boilerplate.mk: rename 'ghc-config-mk' to 'ghc_config_mk'
Make/shell variable names which contain dashes can cause problems under
some conditions. The 'ghc-config-mk' variable from testsuite/mk/boilerplate.mk
that I made overridable (by Hadrian) in ba0aed2e was working as expected when
our Hadrian/Linux job was based off the deb8 Docker image, but broke when
I switched the job to use our deb9-based image, in 3d97bad6. The exact
circumstances/tool versions that trigger this problem are unknown, but
changing the variable's name to 'ghc_config_mk' lets us work around the issue.
This fixes the annth_compunits and annth_make test failures that showed up
when we switched the Hadrian/Linux job to use the deb9 environment.
- - - - -
16 changed files:
- compiler/basicTypes/MkId.hs
- compiler/main/DynFlags.hs
- compiler/main/HscMain.hs
- compiler/main/HscTypes.hs
- compiler/typecheck/TcRnMonad.hs
- docs/users_guide/safe_haskell.rst
- hadrian/src/Rules/Compile.hs
- hadrian/src/Rules/Test.hs
- + 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/mk/boilerplate.mk
- testsuite/tests/plugins/T16260.stdout
- testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout
- utils/haddock
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/main/DynFlags.hs
=====================================
@@ -911,6 +911,8 @@ data WarningFlag =
| Opt_WarnSpaceAfterBang
| Opt_WarnMissingDerivingStrategies -- Since 8.8
| Opt_WarnPrepositiveQualifiedModule -- Since TBD
+ | Opt_WarnInferredSafeImports -- Since 8.10
+ | Opt_WarnMissingSafeHaskellMode -- Since 8.10
deriving (Eq, Show, Enum)
data Language = Haskell98 | Haskell2010
@@ -921,11 +923,12 @@ instance Outputable Language where
-- | The various Safe Haskell modes
data SafeHaskellMode
- = Sf_None
- | Sf_Unsafe
- | Sf_Trustworthy
- | Sf_Safe
- | Sf_Ignore
+ = Sf_None -- ^ inferred unsafe
+ | Sf_Unsafe -- ^ declared and checked
+ | Sf_Trustworthy -- ^ declared and checked
+ | Sf_Safe -- ^ declared and checked
+ | Sf_SafeInferred -- ^ inferred as safe
+ | Sf_Ignore -- ^ @-fno-safe-haskell@ state
deriving (Eq)
instance Show SafeHaskellMode where
@@ -933,6 +936,7 @@ instance Show SafeHaskellMode where
show Sf_Unsafe = "Unsafe"
show Sf_Trustworthy = "Trustworthy"
show Sf_Safe = "Safe"
+ show Sf_SafeInferred = "Safe-Inferred"
show Sf_Ignore = "Ignore"
instance Outputable SafeHaskellMode where
@@ -3757,6 +3761,8 @@ dynamic_flags_deps = [
, make_ord_flag defFlag "fno-safe-infer" (noArg (\d ->
d { safeInfer = False }))
, make_ord_flag defFlag "fno-safe-haskell" (NoArg (setSafeHaskell Sf_Ignore))
+
+ ------ position independent flags ----------------------------------
, make_ord_flag defGhcFlag "fPIC" (NoArg (setGeneralFlag Opt_PIC))
, make_ord_flag defGhcFlag "fno-PIC" (NoArg (unSetGeneralFlag Opt_PIC))
, make_ord_flag defGhcFlag "fPIE" (NoArg (setGeneralFlag Opt_PIC))
@@ -4075,6 +4081,8 @@ wWarningFlagsDeps = [
flagSpec "all-missed-specializations" Opt_WarnAllMissedSpecs,
flagSpec' "safe" Opt_WarnSafe setWarnSafe,
flagSpec "trustworthy-safe" Opt_WarnTrustworthySafe,
+ flagSpec "inferred-safe-imports" Opt_WarnInferredSafeImports,
+ flagSpec "missing-safe-haskell-mode" Opt_WarnMissingSafeHaskellMode,
flagSpec "tabs" Opt_WarnTabs,
flagSpec "type-defaults" Opt_WarnTypeDefaults,
flagSpec "typed-holes" Opt_WarnTypedHoles,
=====================================
compiler/main/HscMain.hs
=====================================
@@ -498,6 +498,14 @@ tcRnModule' sum save_rn_syntax mod = do
hsc_env <- getHscEnv
dflags <- getDynFlags
+ -- -Wmissing-safe-haskell-mode
+ when (not (safeHaskellModeEnabled dflags)
+ && wopt Opt_WarnMissingSafeHaskellMode dflags) $
+ logWarnings $ unitBag $
+ makeIntoWarning (Reason Opt_WarnMissingSafeHaskellMode) $
+ mkPlainWarnMsg dflags (getLoc (hpm_module mod)) $
+ warnMissingSafeHaskellMode
+
tcg_res <- {-# SCC "Typecheck-Rename" #-}
ioMsgMaybe $
tcRnModule hsc_env sum
@@ -542,6 +550,8 @@ tcRnModule' sum save_rn_syntax mod = do
errSafe t = quotes (pprMod t) <+> text "has been inferred as safe!"
errTwthySafe t = quotes (pprMod t)
<+> text "is marked as Trustworthy but has been inferred as safe!"
+ warnMissingSafeHaskellMode = ppr (moduleName (ms_mod sum))
+ <+> text "is missing Safe Haskell mode"
-- | Convert a typechecked module to Core
hscDesugar :: HscEnv -> ModSummary -> TcGblEnv -> IO ModGuts
@@ -1107,21 +1117,36 @@ hscCheckSafe' m l = do
let trust = getSafeMode $ mi_trust iface'
trust_own_pkg = mi_trust_pkg iface'
-- check module is trusted
- safeM = trust `elem` [Sf_Safe, Sf_Trustworthy]
+ safeM = trust `elem` [Sf_Safe, Sf_SafeInferred, Sf_Trustworthy]
-- check package is trusted
safeP = packageTrusted dflags trust trust_own_pkg m
-- pkg trust reqs
pkgRs = S.fromList . map fst $ filter snd $ dep_pkgs $ mi_deps iface'
+ -- warn if Safe module imports Safe-Inferred module.
+ warns = if wopt Opt_WarnInferredSafeImports dflags
+ && safeLanguageOn dflags
+ && trust == Sf_SafeInferred
+ then inferredImportWarn
+ else emptyBag
-- General errors we throw but Safe errors we log
errs = case (safeM, safeP) of
(True, True ) -> emptyBag
(True, False) -> pkgTrustErr
(False, _ ) -> modTrustErr
in do
+ logWarnings warns
logWarnings errs
return (trust == Sf_Trustworthy, pkgRs)
where
+ inferredImportWarn = unitBag
+ $ makeIntoWarning (Reason Opt_WarnInferredSafeImports)
+ $ mkErrMsg dflags l (pkgQual dflags)
+ $ sep
+ [ text "Importing Safe-Inferred module "
+ <> ppr (moduleName m)
+ <> text " from explicitly Safe module"
+ ]
pkgTrustErr = unitBag $ mkErrMsg dflags l (pkgQual dflags) $
sep [ ppr (moduleName m)
<> text ": Can't be safely imported!"
@@ -1144,6 +1169,7 @@ hscCheckSafe' m l = do
packageTrusted dflags _ _ _
| not (packageTrustOn dflags) = True
packageTrusted _ Sf_Safe False _ = True
+ packageTrusted _ Sf_SafeInferred False _ = True
packageTrusted dflags _ _ m
| isHomePkg dflags m = True
| otherwise = trusted $ getPackageDetails dflags (moduleUnitId m)
=====================================
compiler/main/HscTypes.hs
=====================================
@@ -2949,6 +2949,7 @@ trustInfoToNum it
Sf_Unsafe -> 1
Sf_Trustworthy -> 2
Sf_Safe -> 3
+ Sf_SafeInferred -> 4
Sf_Ignore -> 0
numToTrustInfo :: Word8 -> IfaceTrustInfo
@@ -2956,9 +2957,7 @@ numToTrustInfo 0 = setSafeMode Sf_None
numToTrustInfo 1 = setSafeMode Sf_Unsafe
numToTrustInfo 2 = setSafeMode Sf_Trustworthy
numToTrustInfo 3 = setSafeMode Sf_Safe
-numToTrustInfo 4 = setSafeMode Sf_Safe -- retained for backwards compat, used
- -- to be Sf_SafeInfered but we no longer
- -- differentiate.
+numToTrustInfo 4 = setSafeMode Sf_SafeInferred
numToTrustInfo n = error $ "numToTrustInfo: bad input number! (" ++ show n ++ ")"
instance Outputable IfaceTrustInfo where
@@ -2967,6 +2966,7 @@ instance Outputable IfaceTrustInfo where
ppr (TrustInfo Sf_Unsafe) = text "unsafe"
ppr (TrustInfo Sf_Trustworthy) = text "trustworthy"
ppr (TrustInfo Sf_Safe) = text "safe"
+ ppr (TrustInfo Sf_SafeInferred) = text "safe-inferred"
instance Binary IfaceTrustInfo where
put_ bh iftrust = putByte bh $ trustInfoToNum iftrust
=====================================
compiler/typecheck/TcRnMonad.hs
=====================================
@@ -1837,13 +1837,13 @@ finalSafeMode :: DynFlags -> TcGblEnv -> IO SafeHaskellMode
finalSafeMode dflags tcg_env = do
safeInf <- fst <$> readIORef (tcg_safeInfer tcg_env)
return $ case safeHaskell dflags of
- Sf_None | safeInferOn dflags && safeInf -> Sf_Safe
+ Sf_None | safeInferOn dflags && safeInf -> Sf_SafeInferred
| otherwise -> Sf_None
s -> s
-- | Switch instances to safe instances if we're in Safe mode.
fixSafeInstances :: SafeHaskellMode -> [ClsInst] -> [ClsInst]
-fixSafeInstances sfMode | sfMode /= Sf_Safe = id
+fixSafeInstances sfMode | sfMode /= Sf_Safe && sfMode /= Sf_SafeInferred = id
fixSafeInstances _ = map fixSafe
where fixSafe inst = let new_flag = (is_flag inst) { isSafeOverlap = True }
in inst { is_flag = new_flag }
=====================================
docs/users_guide/safe_haskell.rst
=====================================
@@ -739,7 +739,7 @@ And one general flag:
requiring the package that ``M`` resides in be considered trusted, for ``M``
to be considered trusted.
-And three warning flags:
+And five warning flags:
.. ghc-flag:: -Wunsafe
:shortdesc: warn if the module being compiled is regarded to be unsafe.
@@ -775,6 +775,55 @@ And three warning flags:
-XSafe , a more informative bound. Can be used to detect once a Safe Haskell
bound can be improved as dependencies are updated.
+.. ghc-flag:: -Winferred-safe-imports
+ :shortdesc: warn when an explicitly Safe Haskell module imports a Safe-Inferred one
+ :type: dynamic
+ :reverse: -Wno-inferred-safe-imports
+ :category:
+
+ :since: 8.10.1
+
+ .. index::
+ single: safe haskell imports, warning
+
+ The module ``A`` below is annotated to be explictly ``Safe``, but it imports
+ ``Safe-Inferred`` module.
+
+ {-# LANGUAGE Safe #-}
+ module A where
+
+ import B (double)
+
+ quad :: Int -> Int
+ quad = double . double
+
+
+ module B where
+
+ double :: Int -> Int
+ double n = n + n
+
+ The inferred status is volatile: if an unsafe import is added to the module
+ ``B``, it will cause compilation error of ``A``. When
+ :ghc-flag:`-Winferred-safe-imports` is enabled, the compiler will emit a
+ warning about this.
+ This option is off by default.
+
+.. ghc-flag:: -Wmissing-safe-haskell-mode
+ :shortdesc: warn when the Safe Haskell mode is not explicitly specified.
+ :type: dynamic
+ :reverse: -Wno-missing-safe-haskell-mode
+ :category:
+
+ :since: 8.10.1
+
+ .. index::
+ single: safe haskell mode, missing
+
+ The compiler will warn when none of :extension:`Safe`,
+ :extension:`Trustworthy` or :extension:`Unsafe` is specified.
+ This option is off by default.
+
.. _safe-compilation:
Safe Compilation
=====================================
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
=====================================
hadrian/src/Rules/Test.hs
=====================================
@@ -122,7 +122,7 @@ testRules = do
-- This lets us bypass the need to generate a config
-- through Make, which happens in testsuite/mk/boilerplate.mk
-- which is in turn included by all test 'Makefile's.
- setEnv "ghc-config-mk" (top -/- root -/- ghcConfigPath)
+ setEnv "ghc_config_mk" (top -/- root -/- ghcConfigPath)
-- Execute the test target.
-- We override the verbosity setting to make sure the user can see
=====================================
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/mk/boilerplate.mk
=====================================
@@ -240,17 +240,17 @@ $(TOP)/mk/ghc-config : $(TOP)/mk/ghc-config.hs
empty=
space=$(empty) $(empty)
-ifeq "$(ghc-config-mk)" ""
-ghc-config-mk = $(TOP)/mk/ghcconfig$(subst $(space),_,$(subst :,_,$(subst /,_,$(subst \,_,$(TEST_HC))))).mk
+ifeq "$(ghc_config_mk)" ""
+ghc_config_mk = $(TOP)/mk/ghcconfig$(subst $(space),_,$(subst :,_,$(subst /,_,$(subst \,_,$(TEST_HC))))).mk
-$(ghc-config-mk) : $(TOP)/mk/ghc-config
+$(ghc_config_mk) : $(TOP)/mk/ghc-config
$(TOP)/mk/ghc-config "$(TEST_HC)" >"$@"; if [ $$? != 0 ]; then $(RM) "$@"; exit 1; fi
# If the ghc-config fails, remove $@, and fail
endif
# Note: $(CLEANING) is not defined in the testsuite.
ifeq "$(findstring clean,$(MAKECMDGOALS))" ""
--include $(ghc-config-mk)
+-include $(ghc_config_mk)
endif
# Note [WayFlags]
=====================================
testsuite/tests/plugins/T16260.stdout
=====================================
@@ -1,4 +1,4 @@
False
None
True
-Safe
+Safe-Inferred
=====================================
testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout
=====================================
@@ -4,42 +4,42 @@ pdb.safePkg01/local.db
trusted: False
M_SafePkg
-package dependencies: base-4.12.0.0* ghc-prim-0.6.1 integer-gmp-1.0.2.0
+package dependencies: base-4.13.0.0* ghc-prim-0.6.1 integer-gmp-1.0.2.0
trusted: safe
require own pkg trusted: False
M_SafePkg2
-package dependencies: base-4.12.0.0 ghc-prim-0.6.1 integer-gmp-1.0.2.0
+package dependencies: base-4.13.0.0 ghc-prim-0.6.1 integer-gmp-1.0.2.0
trusted: trustworthy
require own pkg trusted: False
M_SafePkg3
-package dependencies: base-4.12.0.0* ghc-prim-0.6.1 integer-gmp-1.0.2.0
+package dependencies: base-4.13.0.0* ghc-prim-0.6.1 integer-gmp-1.0.2.0
trusted: safe
require own pkg trusted: True
M_SafePkg4
-package dependencies: base-4.12.0.0* ghc-prim-0.6.1 integer-gmp-1.0.2.0
+package dependencies: base-4.13.0.0* ghc-prim-0.6.1 integer-gmp-1.0.2.0
trusted: safe
require own pkg trusted: True
M_SafePkg5
-package dependencies: base-4.12.0.0* ghc-prim-0.6.1 integer-gmp-1.0.2.0
-trusted: safe
+package dependencies: base-4.13.0.0* ghc-prim-0.6.1 integer-gmp-1.0.2.0
+trusted: safe-inferred
require own pkg trusted: True
M_SafePkg6
-package dependencies: array-0.5.2.0 base-4.12.0.0* bytestring-0.10.8.2* deepseq-1.4.4.0 ghc-prim-0.6.1 integer-gmp-1.0.2.0
+package dependencies: array-0.5.4.0 base-4.13.0.0* bytestring-0.10.9.0* deepseq-1.4.4.0 ghc-prim-0.6.1 integer-gmp-1.0.2.0
trusted: trustworthy
require own pkg trusted: False
M_SafePkg7
-package dependencies: array-0.5.2.0 base-4.12.0.0* bytestring-0.10.8.2* deepseq-1.4.4.0 ghc-prim-0.6.1 integer-gmp-1.0.2.0
+package dependencies: array-0.5.4.0 base-4.13.0.0* bytestring-0.10.9.0* deepseq-1.4.4.0 ghc-prim-0.6.1 integer-gmp-1.0.2.0
trusted: safe
require own pkg trusted: False
M_SafePkg8
-package dependencies: array-0.5.2.0 base-4.12.0.0 bytestring-0.10.8.2* deepseq-1.4.4.0 ghc-prim-0.6.1 integer-gmp-1.0.2.0
+package dependencies: array-0.5.4.0 base-4.13.0.0 bytestring-0.10.9.0* deepseq-1.4.4.0 ghc-prim-0.6.1 integer-gmp-1.0.2.0
trusted: trustworthy
require own pkg trusted: False
=====================================
utils/haddock
=====================================
@@ -1 +1 @@
-Subproject commit 83bb9870a117f9426e6f6cff6fec3bb6e93a7c18
+Subproject commit 5e333bad752b9c048ad5400b7159e32f4d3d65bd
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/21f1960ddafc5b1f7c6bc6bb004ff45d24c74962...1d3c656ef5d3635bac84522e41d4ff59918e3632
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/21f1960ddafc5b1f7c6bc6bb004ff45d24c74962...1d3c656ef5d3635bac84522e41d4ff59918e3632
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/20190611/78ad1852/attachment-0001.html>
More information about the ghc-commits
mailing list