[Git][ghc/ghc][wip/fendor/t23703] 2 commits: Refactor distinct constructor tables map construction

Hannes Siebenhandl pushed to branch wip/fendor/t23703 at Glasgow Haskell Compiler / GHC Commits: 62f51fad by Finley McIlwaine at 2025-09-01T10:56:54+02:00 Refactor distinct constructor tables map construction Adds `GHC.Types.Unique.Map.alterUniqMap_L`, `GHC.Types.Unique.FM.alterUFM_L`, `GHC.Data.Word64Map.alterLookupWithKey` to support fusion of distinct constructor data insertion and lookup during the construction of the data con map in `GHC.Stg.Debug.numberDataCon`. - - - - - 561a1835 by Finley McIlwaine at 2025-09-01T10:57:59+02:00 Allow per constructor refinement of distinct-constructor-tables Introduce `-fno-distinct-constructor-tables`. A distinct constructor table configuration is built from the combination of flags given, in order. For example, to create distinct constructor tables for all constructors except for a specific few named `C1`,..., `CN`, pass `-fdistinct-contructor-tables` followed by `fno-distinct-constructor-tables=C1,...,CN`. To only generate distinct constuctor tables for a few specific constructors and no others, just pass `-fdistinct-constructor-tables=C1,...,CN`. The various configurations of these flags is included in the `DynFlags` fingerprints, which should result in the expected recompilation logic. Adds a test that checks for distinct tables for various given or omitted constructors. Updates CountDepsAst and CountDepsParser tests to account for new dependencies. Fixes #23703 - - - - - 29 changed files: - compiler/GHC/Data/Word64Map/Internal.hs - compiler/GHC/Data/Word64Map/Lazy.hs - compiler/GHC/Driver/Config/Stg/Debug.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Iface/Flags.hs - compiler/GHC/Iface/Recomp/Flags.hs - compiler/GHC/Stg/Debug.hs - + compiler/GHC/Stg/Debug/Types.hs - compiler/GHC/Types/Unique/DFM.hs - compiler/GHC/Types/Unique/FM.hs - compiler/GHC/Types/Unique/Map.hs - compiler/ghc.cabal.in - docs/users_guide/debug-info.rst - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - + testsuite/tests/rts/ipe/distinct-tables/Main.hs - + testsuite/tests/rts/ipe/distinct-tables/Makefile - + testsuite/tests/rts/ipe/distinct-tables/X.hs - + testsuite/tests/rts/ipe/distinct-tables/all.T - + testsuite/tests/rts/ipe/distinct-tables/distinct_tables01.stdout - + testsuite/tests/rts/ipe/distinct-tables/distinct_tables02.stdout - + testsuite/tests/rts/ipe/distinct-tables/distinct_tables03.stdout - + testsuite/tests/rts/ipe/distinct-tables/distinct_tables04.stdout - + testsuite/tests/rts/ipe/distinct-tables/distinct_tables05.stdout - + testsuite/tests/rts/ipe/distinct-tables/distinct_tables06.stdout - + testsuite/tests/rts/ipe/distinct-tables/distinct_tables07.stdout - + testsuite/tests/rts/ipe/distinct-tables/distinct_tables08.stdout Changes: ===================================== compiler/GHC/Data/Word64Map/Internal.hs ===================================== @@ -100,6 +100,7 @@ module GHC.Data.Word64Map.Internal ( , updateWithKey , updateLookupWithKey , alter + , alterLookupWithKey , alterF -- * Combine @@ -986,6 +987,39 @@ alter f k Nil = case f Nothing of Just x -> Tip k x Nothing -> Nil +-- | \(O(\min(n,W))\). The expression (@'alterLookupWithKey' f k map@) alters +-- the value @x@ at @k@, or absence thereof, and returns the result of the +-- alteration. 'alterLookupWithKey' can be used to insert, delete, or update a +-- value in a 'Word64Map'. +-- +-- Note that the behavior of this function differs from 'updateLookupWithKey', +-- and instead matches the behavior of 'Data.Map.updateLookupWithKey'. +alterLookupWithKey :: (Maybe a -> Maybe a) -> Key -> Word64Map a -> (Maybe a, Word64Map a) +alterLookupWithKey f !k t@(Bin p m l r) + | nomatch k p m = + case f Nothing of + Nothing -> (Nothing, t) + Just x -> (Just x, link k (Tip k x) p t) + | zero k m = + let !(res, l') = alterLookupWithKey f k l + in (res, binCheckLeft p m l' r) + | otherwise = + let !(res, r') = alterLookupWithKey f k r + in (res, binCheckRight p m l r') +alterLookupWithKey f k t@(Tip ky y) + | k==ky = + case f (Just y) of + Just x -> (Just x, Tip ky x) + Nothing -> (Nothing, Nil) + | otherwise = + case f Nothing of + Just x -> (Just x, link k (Tip k x) ky t) + Nothing -> (Nothing, Tip ky y) +alterLookupWithKey f k Nil = + case f Nothing of + Just x -> (Just x, Tip k x) + Nothing -> (Nothing, Nil) + -- | \(O(\min(n,W))\). The expression (@'alterF' f k map@) alters the value @x@ at -- @k@, or absence thereof. 'alterF' can be used to inspect, insert, delete, -- or update a value in an 'Word64Map'. In short : @'lookup' k <$> 'alterF' f k m = f ===================================== compiler/GHC/Data/Word64Map/Lazy.hs ===================================== @@ -93,6 +93,7 @@ module GHC.Data.Word64Map.Lazy ( , updateWithKey , updateLookupWithKey , alter + , alterLookupWithKey , alterF -- * Query ===================================== compiler/GHC/Driver/Config/Stg/Debug.hs ===================================== @@ -10,5 +10,5 @@ import GHC.Driver.DynFlags initStgDebugOpts :: DynFlags -> StgDebugOpts initStgDebugOpts dflags = StgDebugOpts { stgDebug_infoTableMap = gopt Opt_InfoTableMap dflags - , stgDebug_distinctConstructorTables = gopt Opt_DistinctConstructorTables dflags + , stgDebug_distinctConstructorTables = distinctConstructorTables dflags } ===================================== compiler/GHC/Driver/DynFlags.hs ===================================== @@ -117,6 +117,7 @@ import GHC.Types.SrcLoc import GHC.Unit.Module import GHC.Unit.Module.Warnings import GHC.Utils.CliOption +import GHC.Stg.Debug.Types (StgDebugDctConfig(..)) import GHC.SysTools.Terminal ( stderrSupportsAnsiColors ) import GHC.UniqueSubdir (uniqueSubdir) import GHC.Utils.Outputable @@ -134,6 +135,7 @@ import Control.Monad.Trans.Class (lift) import Control.Monad.Trans.Except (ExceptT) import Control.Monad.Trans.Reader (ReaderT) import Control.Monad.Trans.Writer (WriterT) +import qualified Data.Set as Set import Data.Word import System.IO import System.IO.Error (catchIOError) @@ -142,7 +144,6 @@ import System.FilePath (normalise, (>)) import System.Directory import GHC.Foreign (withCString, peekCString) -import qualified Data.Set as Set import GHC.Types.Unique.Set import qualified GHC.LanguageExtensions as LangExt @@ -477,7 +478,11 @@ data DynFlags = DynFlags { -- 'Int' because it can be used to test uniques in decreasing order. -- | Temporary: CFG Edge weights for fast iterations - cfgWeights :: Weights + cfgWeights :: Weights, + + -- | Configuration specifying which constructor names we should create + -- distinct info tables for + distinctConstructorTables :: StgDebugDctConfig } class HasDynFlags m where @@ -739,7 +744,9 @@ defaultDynFlags mySettings = reverseErrors = False, maxErrors = Nothing, - cfgWeights = defaultWeights + cfgWeights = defaultWeights, + + distinctConstructorTables = None } type FatalMessager = String -> IO () ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -593,7 +593,6 @@ data GeneralFlag | Opt_FastLlvm -- hidden flag | Opt_NoTypeableBinds - | Opt_DistinctConstructorTables | Opt_InfoTableMap | Opt_InfoTableMapWithFallback | Opt_InfoTableMapWithStack @@ -982,7 +981,6 @@ codeGenFlags = EnumSet.fromList , Opt_DoTagInferenceChecks -- Flags that affect debugging information - , Opt_DistinctConstructorTables , Opt_InfoTableMap , Opt_InfoTableMapWithStack , Opt_InfoTableMapWithFallback ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -277,6 +277,7 @@ import GHC.CmmToAsm.CFG.Weight import GHC.Core.Opt.CallerCC import GHC.Parser (parseIdentifier) import GHC.Parser.Lexer (mkParserOpts, initParserState, P(..), ParseResult(..)) +import GHC.Stg.Debug.Types import GHC.SysTools.BaseDir ( expandToolDir, expandTopDir ) @@ -1908,6 +1909,10 @@ dynamic_flags_deps = [ -- Caller-CC , make_ord_flag defGhcFlag "fprof-callers" (HasArg setCallerCcFilters) + , make_ord_flag defGhcFlag "fdistinct-constructor-tables" + (OptPrefix setDistinctConstructorTables) + , make_ord_flag defGhcFlag "fno-distinct-constructor-tables" + (OptPrefix unSetDistinctConstructorTables) ------ Compiler flags ----------------------------------------------- , make_ord_flag defGhcFlag "fasm" (NoArg (setObjBackend ncgBackend)) @@ -2609,7 +2614,6 @@ fFlagsDeps = [ flagSpec "cmm-thread-sanitizer" Opt_CmmThreadSanitizer, flagSpec "split-sections" Opt_SplitSections, flagSpec "break-points" Opt_InsertBreakpoints, - flagSpec "distinct-constructor-tables" Opt_DistinctConstructorTables, flagSpec "info-table-map" Opt_InfoTableMap, flagSpec "info-table-map-with-stack" Opt_InfoTableMapWithStack, flagSpec "info-table-map-with-fallback" Opt_InfoTableMapWithFallback @@ -3207,6 +3211,39 @@ setCallerCcFilters arg = Right filt -> upd $ \d -> d { callerCcFilters = filt : callerCcFilters d } Left err -> addErr err +setDistinctConstructorTables :: String -> DynP () +setDistinctConstructorTables arg = do + let cs = parseDistinctConstructorTablesArg arg + upd $ \d -> + d { distinctConstructorTables = + (distinctConstructorTables d) `dctConfigPlus` cs + } + +unSetDistinctConstructorTables :: String -> DynP () +unSetDistinctConstructorTables arg = do + let cs = parseDistinctConstructorTablesArg arg + upd $ \d -> + d { distinctConstructorTables = + (distinctConstructorTables d) `dctConfigMinus` cs + } + +-- | Parse a string of comma-separated constructor names into a 'Set' of +-- 'String's with one entry per constructor. +parseDistinctConstructorTablesArg :: String -> Set.Set String +parseDistinctConstructorTablesArg = + -- Ensure we insert the last constructor name built by the fold, if not + -- empty + uncurry insertNonEmpty + . foldr go ("", Set.empty) + where + go :: Char -> (String, Set.Set String) -> (String, Set.Set String) + go ',' (cur, acc) = ("", Set.insert cur acc) + go c (cur, acc) = (c : cur, acc) + + insertNonEmpty :: String -> Set.Set String -> Set.Set String + insertNonEmpty "" = id + insertNonEmpty cs = Set.insert cs + setMainIs :: String -> DynP () setMainIs arg = parse parse_main_f arg where ===================================== compiler/GHC/Iface/Flags.hs ===================================== @@ -6,12 +6,15 @@ module GHC.Iface.Flags ( , IfaceExtension(..) , IfaceLanguage(..) , IfaceCppOptions(..) + , IfaceCodeGen(..) + , IfaceDistinctConstructorConfig(..) , pprIfaceDynFlags , missingExtraFlagInfo ) where import GHC.Prelude +import qualified Data.Set as Set import GHC.Utils.Outputable import Control.DeepSeq import GHC.Utils.Fingerprint @@ -22,6 +25,7 @@ import GHC.Types.SafeHaskell import GHC.Core.Opt.CallerCC.Types import qualified GHC.LanguageExtensions as LangExt +import GHC.Stg.Debug.Types -- The part of DynFlags which recompilation information needs data IfaceDynFlags = IfaceDynFlags @@ -35,7 +39,7 @@ data IfaceDynFlags = IfaceDynFlags , ifacePaths :: [String] , ifaceProf :: Maybe IfaceProfAuto , ifaceTicky :: [IfaceGeneralFlag] - , ifaceCodeGen :: [IfaceGeneralFlag] + , ifaceCodeGen :: IfaceCodeGen , ifaceFatIface :: Bool , ifaceDebugLevel :: Int , ifaceCallerCCFilters :: [CallerCcFilter] @@ -58,7 +62,7 @@ pprIfaceDynFlags (IfaceDynFlags a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14) , text "ticky:" , nest 2 $ vcat (map ppr a10) , text "codegen:" - , nest 2 $ vcat (map ppr a11) + , nest 2 $ ppr a11 , text "fat-iface:" <+> ppr a12 , text "debug-level:" <+> ppr a13 , text "caller-cc-filters:" <+> ppr a14 @@ -191,4 +195,66 @@ instance Outputable IfaceCppOptions where , text "signature:" , nest 2 $ parens (ppr fp) <+> ppr (map (text @SDoc) wos) - ] \ No newline at end of file + ] + +data IfaceCodeGen = IfaceCodeGen + { ifaceCodeGenFlags :: [IfaceGeneralFlag] + , ifaceCodeGenDistinctConstructorTables :: IfaceDistinctConstructorConfig + } + +instance NFData IfaceCodeGen where + rnf (IfaceCodeGen flags distinctCnstrTables) = + rnf flags `seq` rnf distinctCnstrTables + +instance Binary IfaceCodeGen where + put_ bh (IfaceCodeGen flags distinctCnstrTables) = do + put_ bh flags + put_ bh distinctCnstrTables + + get bh = + IfaceCodeGen <$> get bh <*> get bh + +instance Outputable IfaceCodeGen where + ppr (IfaceCodeGen flags distinctCnstrTables) = + vcat + [ text "flags:" + , nest 2 $ ppr flags + , text "distinct constructor tables:" + , nest 2 $ ppr distinctCnstrTables + ] + +newtype IfaceDistinctConstructorConfig = IfaceDistinctConstructorConfig StgDebugDctConfig + +instance NFData IfaceDistinctConstructorConfig where + rnf (IfaceDistinctConstructorConfig cnf) = case cnf of + All -> () + (Only v) -> rnf v + (AllExcept v) -> rnf v + None -> () + +instance Outputable IfaceDistinctConstructorConfig where + ppr (IfaceDistinctConstructorConfig cnf) = case cnf of + All -> text "all" + (Only v) -> text "only" <+> brackets (hcat $ fmap text $ Set.toList v) + (AllExcept v) -> text "all except" <+> brackets (hcat $ fmap text $ Set.toList v) + None -> text "none" + +instance Binary IfaceDistinctConstructorConfig where + put_ bh (IfaceDistinctConstructorConfig cnf) = case cnf of + All -> putByte bh 0 + (Only cs) -> do + putByte bh 1 + put_ bh cs + (AllExcept cs) -> do + putByte bh 2 + put_ bh cs + None -> putByte bh 3 + + get bh = do + h <- getByte bh + IfaceDistinctConstructorConfig <$> + case h of + 0 -> pure All + 1 -> Only <$> get bh + 2 -> AllExcept <$> get bh + _ -> pure None ===================================== compiler/GHC/Iface/Recomp/Flags.hs ===================================== @@ -91,12 +91,30 @@ fingerprintDynFlags hsc_env this_mod nameio = mapMaybe (\f -> (if f `gopt` dflags then Just (IfaceGeneralFlag f) else Nothing)) [Opt_Ticky, Opt_Ticky_Allocd, Opt_Ticky_LNE, Opt_Ticky_Dyn_Thunk, Opt_Ticky_Tag] -- Other flags which affect code generation - codegen = mapMaybe (\f -> (if f `gopt` dflags then Just (IfaceGeneralFlag f) else Nothing)) (EnumSet.toList codeGenFlags) + codegen = IfaceCodeGen + { ifaceCodeGenFlags = mapMaybe (\f -> (if f `gopt` dflags then Just (IfaceGeneralFlag f) else Nothing)) (EnumSet.toList codeGenFlags) + , ifaceCodeGenDistinctConstructorTables = IfaceDistinctConstructorConfig distinctConstructorTables + } -- Did we include core for all bindings? fat_iface = gopt Opt_WriteIfSimplifiedCore dflags - f = IfaceDynFlags mainis safeHs lang exts cpp js cmm paths prof ticky codegen fat_iface debugLevel callerCcFilters + f = IfaceDynFlags + { ifaceMainIs = mainis + , ifaceSafeMode = safeHs + , ifaceLang = lang + , ifaceExts = exts + , ifaceCppOptions = cpp + , ifaceJsOptions = js + , ifaceCmmOptions = cmm + , ifacePaths = paths + , ifaceProf = prof + , ifaceTicky = ticky + , ifaceCodeGen = codegen + , ifaceFatIface = fat_iface + , ifaceDebugLevel = debugLevel + , ifaceCallerCCFilters = callerCcFilters + } in (computeFingerprint nameio f, f) ===================================== compiler/GHC/Stg/Debug.hs ===================================== @@ -1,9 +1,13 @@ -{-# LANGUAGE TupleSections #-} +{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE TupleSections #-} -- This module contains functions which implement -- the -finfo-table-map and -fdistinct-constructor-tables flags module GHC.Stg.Debug ( StgDebugOpts(..) + , StgDebugDctConfig(..) + , dctConfigPlus + , dctConfigMinus , collectDebugInformation ) where @@ -17,11 +21,13 @@ import GHC.Types.Tickish import GHC.Core.DataCon import GHC.Types.IPE import GHC.Unit.Module -import GHC.Types.Name ( getName, getOccName, occNameFS, nameSrcSpan) +import GHC.Types.Name ( getName, getOccName, occNameFS, nameSrcSpan, occName, occNameString) import GHC.Data.FastString +import GHC.Stg.Debug.Types import Control.Monad (when) import Control.Monad.Trans.Reader +import qualified Data.Set as Set import GHC.Utils.Monad.State.Strict import Control.Monad.Trans.Class import GHC.Types.SrcLoc @@ -29,13 +35,6 @@ import Control.Applicative import qualified Data.List.NonEmpty as NE import Data.List.NonEmpty (NonEmpty(..)) -data SpanWithLabel = SpanWithLabel RealSrcSpan LexicalFastString - -data StgDebugOpts = StgDebugOpts - { stgDebug_infoTableMap :: !Bool - , stgDebug_distinctConstructorTables :: !Bool - } - data R = R { rOpts :: StgDebugOpts, rModLocation :: ModLocation, rSpan :: Maybe SpanWithLabel } type M a = ReaderT R (State InfoTableProvMap) a @@ -155,6 +154,8 @@ recordStgIdPosition id best_span ss = do let mbspan = (\(SpanWithLabel rss d) -> (rss, d)) <$> (best_span <|> cc <|> ss) lift $ modify (\env -> env { provClosure = addToUDFM (provClosure env) (idName id) (idName id, (idType id, mbspan)) }) +-- | If @-fdistinct-constructor-tables@ is enabled, each occurrence of a data +-- constructor will be given its own info table numberDataCon :: DataCon -> [StgTickish] -> M ConstructorNumber -- Unboxed tuples and sums do not allocate so they -- have no info tables. @@ -162,22 +163,59 @@ numberDataCon dc _ | isUnboxedTupleDataCon dc = return NoNumber numberDataCon dc _ | isUnboxedSumDataCon dc = return NoNumber numberDataCon dc ts = do opts <- asks rOpts - if not (stgDebug_distinctConstructorTables opts) then return NoNumber else do + if shouldMakeDistinctTable opts dc then do + -- -fdistinct-constructor-tables is enabled and we do want to make distinct + -- tables for this constructor. Add an entry to the data constructor map for + -- this occurrence of the data constructor with a unique number and a src + -- span env <- lift get mcc <- asks rSpan - let !mbest_span = (\(SpanWithLabel rss l) -> (rss, l)) <$> (selectTick ts <|> mcc) - let !dcMap' = alterUDFM (maybe (Just (dc, (0, mbest_span) :| [] )) - (\(_dc, xs@((k, _):|_)) -> Just $! (dc, (k + 1, mbest_span) `NE.cons` xs))) (provDC env) dc + let + -- Guess a src span for this occurrence using source note ticks and the + -- current span in the environment + !mbest_span = selectTick ts <|> (\(SpanWithLabel rss l) -> (rss, l)) <$> mcc + + -- Add the occurrence to the data constructor map of the InfoTableProvMap, + -- noting the unique number assigned for this occurence + (!r, !dcMap') = + alterUDFM_L + ( maybe + (Just (dc, (0, mbest_span) :| [] )) + ( \(_dc, xs@((k, _):|_)) -> + Just $! (dc, (k + 1, mbest_span) `NE.cons` xs) + ) + ) + (provDC env) + dc lift $ put (env { provDC = dcMap' }) - let r = lookupUDFM dcMap' dc return $ case r of Nothing -> NoNumber Just (_, res) -> Numbered (fst (NE.head res)) + else do + -- -fdistinct-constructor-tables is not enabled, or we do not want to make + -- distinct tables for this specific constructor + return NoNumber -selectTick :: [StgTickish] -> Maybe SpanWithLabel -selectTick [] = Nothing -selectTick (SourceNote rss d : ts ) = selectTick ts <|> Just (SpanWithLabel rss d) -selectTick (_:ts) = selectTick ts +selectTick :: [StgTickish] -> Maybe (RealSrcSpan, LexicalFastString) +selectTick = foldl' go Nothing + where + go :: Maybe (RealSrcSpan, LexicalFastString) -> StgTickish -> Maybe (RealSrcSpan, LexicalFastString) + go _ (SourceNote rss d) = Just (rss, d) + go acc _ = acc + +-- | Descide whether a distinct info table should be made for a usage of a data +-- constructor. We only want to do this if -fdistinct-constructor-tables was +-- given and this constructor name was given, or no constructor names were +-- given. +shouldMakeDistinctTable :: StgDebugOpts -> DataCon -> Bool +shouldMakeDistinctTable StgDebugOpts{..} dc = + case stgDebug_distinctConstructorTables of + All -> True + Only these -> Set.member dcStr these + AllExcept these -> Set.notMember dcStr these + None -> False + where + dcStr = occNameString . occName $ dataConName dc {- Note [Mapping Info Tables to Source Positions] ===================================== compiler/GHC/Stg/Debug/Types.hs ===================================== @@ -0,0 +1,80 @@ +module GHC.Stg.Debug.Types where + +import GHC.Prelude + +import GHC.Data.FastString +import GHC.Types.SrcLoc + +import Data.Set (Set) +import qualified Data.Set as Set + +data SpanWithLabel = SpanWithLabel RealSrcSpan LexicalFastString + +data StgDebugOpts = StgDebugOpts + { stgDebug_infoTableMap :: !Bool + , stgDebug_distinctConstructorTables :: !StgDebugDctConfig + } + +-- | Configuration describing which constructors should be given distinct info +-- tables for each usage. +data StgDebugDctConfig = + -- | Create distinct constructor tables for each usage of any data + -- constructor. + -- + -- This is the behavior if just @-fdistinct-constructor-tables@ is supplied. + All + + -- | Create distinct constructor tables for each usage of only these data + -- constructors. + -- + -- This is the behavior if @-fdistinct-constructor-tables=C1,...,CN@ is + -- supplied. + | Only !(Set String) + + -- | Create distinct constructor tables for each usage of any data + -- constructor except these ones. + -- + -- This is the behavior if @-fdistinct-constructor-tables@ and + -- @-fno-distinct-constructor-tables=C1,...,CN@ is given. + | AllExcept !(Set String) + + -- | Do not create distinct constructor tables for any data constructor. + -- + -- This is the behavior if no @-fdistinct-constructor-tables@ is given (or + -- @-fno-distinct-constructor-tables@ is given). + | None + +-- | Given a distinct constructor tables configuration and a set of constructor +-- names that we want to generate distinct info tables for, create a new +-- configuration which includes those constructors. +-- +-- If the given set is empty, that means the user has entered +-- @-fdistinct-constructor-tables@ with no constructor names specified, and +-- therefore we consider that an 'All' configuration. +dctConfigPlus :: StgDebugDctConfig -> Set String -> StgDebugDctConfig +dctConfigPlus cfg cs + | Set.null cs = All + | otherwise = + case cfg of + All -> All + Only cs' -> Only $ Set.union cs' cs + AllExcept cs' -> AllExcept $ Set.difference cs' cs + None -> Only cs + +-- | Given a distinct constructor tables configuration and a set of constructor +-- names that we /do not/ want to generate distinct info tables for, create a +-- new configuration which excludes those constructors. +-- +-- If the given set is empty, that means the user has entered +-- @-fno-distinct-constructor-tables@ with no constructor names specified, and +-- therefore we consider that a 'None' configuration. +dctConfigMinus :: StgDebugDctConfig -> Set String -> StgDebugDctConfig +dctConfigMinus cfg cs + | Set.null cs = None + | otherwise = + case cfg of + All -> AllExcept cs + Only cs' -> Only $ Set.difference cs' cs + AllExcept cs' -> AllExcept $ Set.union cs' cs + None -> None + ===================================== compiler/GHC/Types/Unique/DFM.hs ===================================== @@ -39,6 +39,7 @@ module GHC.Types.Unique.DFM ( adjustUDFM, adjustUDFM_Directly, alterUDFM, + alterUDFM_L, mapUDFM, mapMaybeUDFM, mapMUDFM, @@ -436,16 +437,18 @@ adjustUDFM f (UDFM m i) k = UDFM (M.adjust (fmap f) (getKey $ getUnique k) m) i adjustUDFM_Directly :: (elt -> elt) -> UniqDFM key elt -> Unique -> UniqDFM key elt adjustUDFM_Directly f (UDFM m i) k = UDFM (M.adjust (fmap f) (getKey k) m) i --- | The expression (alterUDFM f k map) alters value x at k, or absence --- thereof. alterUDFM can be used to insert, delete, or update a value in +-- | The expression (@'alterUDFM' f map k@) alters value x at k, or absence +-- thereof. 'alterUDFM' can be used to insert, delete, or update a value in -- UniqDFM. Use addToUDFM, delFromUDFM or adjustUDFM when possible, they are -- more efficient. +-- +-- 'alterUDFM' is non-strict in @k@. alterUDFM :: Uniquable key - => (Maybe elt -> Maybe elt) -- How to adjust - -> UniqDFM key elt -- old - -> key -- new - -> UniqDFM key elt -- result + => (Maybe elt -> Maybe elt) -- ^ How to adjust the element + -> UniqDFM key elt -- ^ Old 'UniqDFM' + -> key -- ^ @key@ of the element to adjust + -> UniqDFM key elt -- ^ New element at @key@ and modified 'UniqDFM' alterUDFM f (UDFM m i) k = UDFM (M.alter alterf (getKey $ getUnique k) m) (i + 1) where @@ -454,6 +457,35 @@ alterUDFM f (UDFM m i) k = inject Nothing = Nothing inject (Just v) = Just $ TaggedVal v i +-- | The expression (@'alterUDFM_L' f map k@) alters value @x@ at @k@, or absence +-- thereof and returns the new element at @k@ if there is any. +-- 'alterUDFM_L' can be used to insert, delete, or update a value in +-- UniqDFM. Use addToUDFM, delFromUDFM or adjustUDFM when possible, they are +-- more efficient. +-- +-- Note, 'alterUDFM_L' is strict in @k@. +alterUDFM_L + :: forall key elt . Uniquable key + => (Maybe elt -> Maybe elt) -- ^ How to adjust the element + -> UniqDFM key elt -- ^ Old 'UniqDFM' + -> key -- ^ @key@ of the element to adjust + -> (Maybe elt, UniqDFM key elt) -- ^ New element at @key@ and modified 'UniqDFM' +alterUDFM_L f (UDFM m i) k = + let + -- Force the key Word64 as the thunk is almost never worth it. + !key = getKey $ getUnique k + (mElt, udfm) = M.alterF (dupe . alterf) key m + in + (mElt, UDFM udfm (i + 1)) + where + dupe :: Maybe (TaggedVal elt) -> (Maybe elt, Maybe (TaggedVal elt)) + dupe mt = (fmap taggedFst mt, mt) + alterf :: Maybe (TaggedVal elt) -> (Maybe (TaggedVal elt)) + alterf Nothing = inject $ f Nothing + alterf (Just (TaggedVal v _)) = inject $ f (Just v) + inject Nothing = Nothing + inject (Just v) = Just $ TaggedVal v i + -- | Map a function over every value in a UniqDFM mapUDFM :: (elt1 -> elt2) -> UniqDFM key elt1 -> UniqDFM key elt2 mapUDFM f (UDFM m i) = UDFM (MS.map (fmap f) m) i ===================================== compiler/GHC/Types/Unique/FM.hs ===================================== @@ -44,7 +44,7 @@ module GHC.Types.Unique.FM ( addListToUFM,addListToUFM_C, addToUFM_Directly, addListToUFM_Directly, - adjustUFM, alterUFM, alterUFM_Directly, + adjustUFM, alterUFM, alterUFM_L, alterUFM_Directly, adjustUFM_Directly, delFromUFM, delFromUFM_Directly, @@ -215,6 +215,16 @@ alterUFM -> UniqFM key elt -- ^ result alterUFM f (UFM m) k = UFM (M.alter f (getKey $ getUnique k) m) +alterUFM_L + :: Uniquable key + => (Maybe elt -> Maybe elt) -- ^ How to adjust + -> UniqFM key elt -- ^ old + -> key -- ^ new + -> (Maybe elt, UniqFM key elt) -- ^ result +alterUFM_L f (UFM m) k = + let (r, m') = (M.alterLookupWithKey f (getKey $ getUnique k) m) + in (r, UFM m') + alterUFM_Directly :: (Maybe elt -> Maybe elt) -- ^ How to adjust -> UniqFM key elt -- ^ old ===================================== compiler/GHC/Types/Unique/Map.hs ===================================== @@ -22,6 +22,7 @@ module GHC.Types.Unique.Map ( addToUniqMap_Acc, addToUniqMap_L, alterUniqMap, + alterUniqMap_L, addListToUniqMap_C, adjustUniqMap, delFromUniqMap, @@ -160,6 +161,15 @@ alterUniqMap :: Uniquable k alterUniqMap f (UniqMap m) k = UniqMap $ alterUFM (fmap (k,) . f . fmap snd) m k +alterUniqMap_L :: Uniquable k + => (Maybe a -> Maybe a) + -> UniqMap k a + -> k + -> (Maybe a, UniqMap k a) +alterUniqMap_L f (UniqMap m) k = + let (r, m') = alterUFM_L (fmap (k,) . f . fmap snd) m k + in (snd <$> r, UniqMap m') + addListToUniqMap_C :: Uniquable k => (a -> a -> a) ===================================== compiler/ghc.cabal.in ===================================== @@ -737,6 +737,7 @@ Library GHC.Stg.EnforceEpt.Rewrite GHC.Stg.EnforceEpt.TagSig GHC.Stg.EnforceEpt.Types + GHC.Stg.Debug.Types GHC.Stg.FVs GHC.Stg.Lift GHC.Stg.Lift.Analysis ===================================== docs/users_guide/debug-info.rst ===================================== @@ -368,7 +368,8 @@ to a source location. This lookup table is generated by using the ``-finfo-table an info table to an approximate source position of where that info table statically originated from. If you also want more precise information about constructor info tables then you - should also use :ghc-flag:`-fdistinct-constructor-tables`. + should also use :ghc-flag:`-fdistinct-constructor-tables + <-fdistinct-constructor-tables=⟨cs⟩>`. The :ghc-flag:`-finfo-table-map` flag will increase the binary size by quite a lot, depending on how big your project is. For compiling a project the @@ -453,7 +454,7 @@ to a source location. This lookup table is generated by using the ``-finfo-table from the info table map and decrease the size of executables with info table profiling information. -.. ghc-flag:: -fdistinct-constructor-tables +.. ghc-flag:: -fdistinct-constructor-tables=⟨cs⟩ :shortdesc: Generate a fresh info table for each usage of a data constructor. :type: dynamic @@ -467,6 +468,41 @@ to a source location. This lookup table is generated by using the ``-finfo-table each info table will correspond to the usage of a data constructor rather than the data constructor itself. + :since: 9.16 + + The entries in the info table map resulting from this flag may significantly + increase the size of executables. However, generating distinct info tables + for *every* usage of *every* data constructor often results in more + information than necessary. Instead, we would like to generate these + distinct tables for some specific constructors. To do this, the names of the + constructors we are interested in may be supplied to this flag in a + comma-separated list. If no constructor names are supplied (i.e. just + ``-fdistinct-constructor-tables`` is given) then fresh info tables will be + generated for every usage of every constructor. + + For example, to only generate distinct info tables for the ``Just`` and + ``Right`` constructors, use ``-fdistinct-constructor-tables=Just,Right``. + +.. ghc-flag:: -fno-distinct-constructor-tables=⟨cs⟩ + :shortdesc: Avoid generating a fresh info table for each usage of a data + constructor. + :type: dynamic + :category: debugging + + :since: 9.16 + + Use this flag to refine the set of data constructors for which distinct info + tables are generated (as specified by + :ghc-flag:`-fdistinct-constructor-tables + <-fdistinct-constructor-tables=⟨cs⟩>`). + If no constructor names are given + (i.e. just ``-fno-distinct-constructor-tables`` is given) then no distinct + info tables will be generated for any usages of any data constructors. + + For example, to generate distinct constructor tables for all data + constructors except those named ``MyConstr``, pass both + ``-fdistinct-constructor-tables`` and + ``-fno-distinct-constructor-tables=MyConstr``. Querying the Info Table Map --------------------------- ===================================== testsuite/tests/count-deps/CountDepsAst.stdout ===================================== @@ -132,6 +132,7 @@ GHC.Runtime.Heap.Layout GHC.Settings GHC.Settings.Config GHC.Settings.Constants +GHC.Stg.Debug.Types GHC.Stg.EnforceEpt.TagSig GHC.StgToCmm.Types GHC.SysTools.Terminal ===================================== testsuite/tests/count-deps/CountDepsParser.stdout ===================================== @@ -151,6 +151,7 @@ GHC.Runtime.Heap.Layout GHC.Settings GHC.Settings.Config GHC.Settings.Constants +GHC.Stg.Debug.Types GHC.Stg.EnforceEpt.TagSig GHC.StgToCmm.Types GHC.SysTools.Terminal ===================================== testsuite/tests/rts/ipe/distinct-tables/Main.hs ===================================== @@ -0,0 +1,37 @@ +module Main where + +import GHC.InfoProv +import qualified X + +main = do + printIp =<< whereFrom cafA1 + printIp =<< whereFrom cafA2 + printIp =<< whereFrom cafB1 + printIp =<< whereFrom cafB2 + printIp =<< whereFrom cafC1 + printIp =<< whereFrom cafC2 + printIp =<< whereFrom (ACon ()) + printIp =<< whereFrom cafXA + printIp =<< whereFrom X.cafXA1 + printIp =<< whereFrom X.cafXA2 + printIp =<< whereFrom (X.ACon ()) + printIp =<< whereFrom (BCon cafA1) + printIp =<< whereFrom (CCon (cafA1, BCon (ACon ()))) + where + -- Get rid of the src file path since it makes test output difficult to diff + -- on Windows + printIp = print . stripIpSrc + stripIpSrc (Just ip) = ip { ipSrcFile = "" } + +data A = ACon () +data B = BCon A +data C = CCon (A, B) + +cafA1 = ACon () +cafA2 = ACon () +cafB1 = BCon cafA1 +cafB2 = BCon cafA2 +cafC1 = CCon (cafA1, cafB1) +cafC2 = CCon (cafA2, cafB2) + +cafXA = X.ACon () ===================================== testsuite/tests/rts/ipe/distinct-tables/Makefile ===================================== @@ -0,0 +1,31 @@ +TOP=../../../.. +include $(TOP)/mk/boilerplate.mk +include $(TOP)/mk/test.mk + +# This test runs ghc with various combinations of +# -f{no-}distinct-constructor-tables for different constructors and checks that +# whereFrom finds (or fails to find) their provenance appropriately. + +distinct_tables01: + @$$TEST_HC $$TEST_HC_OPTS -v0 -finfo-table-map -fdistinct-constructor-tables=ACon Main.hs && ./Main + +distinct_tables02: + @$$TEST_HC $$TEST_HC_OPTS -v0 -finfo-table-map -fdistinct-constructor-tables=BCon Main.hs && ./Main + +distinct_tables03: + @$$TEST_HC $$TEST_HC_OPTS -v0 -finfo-table-map -fdistinct-constructor-tables=CCon Main.hs && ./Main + +distinct_tables04: + @$$TEST_HC $$TEST_HC_OPTS -v0 -finfo-table-map -fdistinct-constructor-tables=ACon,BCon Main.hs && ./Main + +distinct_tables05: + @$$TEST_HC $$TEST_HC_OPTS -v0 -finfo-table-map -fdistinct-constructor-tables -fno-distinct-constructor-tables=ACon Main.hs && ./Main + +distinct_tables06: + @$$TEST_HC $$TEST_HC_OPTS -v0 -finfo-table-map -fdistinct-constructor-tables -fno-distinct-constructor-tables=BCon Main.hs && ./Main + +distinct_tables07: + @$$TEST_HC $$TEST_HC_OPTS -v0 -finfo-table-map -fdistinct-constructor-tables -fno-distinct-constructor-tables=CCon Main.hs && ./Main + +distinct_tables08: + @$$TEST_HC $$TEST_HC_OPTS -v0 -finfo-table-map -fdistinct-constructor-tables -fno-distinct-constructor-tables=BCon,CCon Main.hs && ./Main ===================================== testsuite/tests/rts/ipe/distinct-tables/X.hs ===================================== @@ -0,0 +1,7 @@ +module X where + +-- A type with the same constructor name as 'Main.ACon' +data X = ACon () + +cafXA1 = ACon () +cafXA2 = ACon () ===================================== testsuite/tests/rts/ipe/distinct-tables/all.T ===================================== @@ -0,0 +1,8 @@ +test('distinct_tables01', [extra_files(['Main.hs', 'X.hs',])], makefile_test, []) +test('distinct_tables02', [extra_files(['Main.hs', 'X.hs',])], makefile_test, []) +test('distinct_tables03', [extra_files(['Main.hs', 'X.hs',])], makefile_test, []) +test('distinct_tables04', [extra_files(['Main.hs', 'X.hs',])], makefile_test, []) +test('distinct_tables05', [extra_files(['Main.hs', 'X.hs',])], makefile_test, []) +test('distinct_tables06', [extra_files(['Main.hs', 'X.hs',])], makefile_test, []) +test('distinct_tables07', [extra_files(['Main.hs', 'X.hs',])], makefile_test, []) +test('distinct_tables08', [extra_files(['Main.hs', 'X.hs',])], makefile_test, []) ===================================== testsuite/tests/rts/ipe/distinct-tables/distinct_tables01.stdout ===================================== @@ -0,0 +1,13 @@ +InfoProv {ipName = "ACon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "cafA1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "30:1-15"} +InfoProv {ipName = "ACon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "cafA2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "31:1-15"} +InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "ACon_Main_4_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "13:17-35"} +InfoProv {ipName = "ACon_Main_0_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "37:1-17"} +InfoProv {ipName = "ACon_X_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA1", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = "6:1-16"} +InfoProv {ipName = "ACon_X_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA2", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = "7:1-16"} +InfoProv {ipName = "ACon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "17:17-37"} +InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""} ===================================== testsuite/tests/rts/ipe/distinct-tables/distinct_tables02.stdout ===================================== @@ -0,0 +1,13 @@ +InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "BCon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "cafB1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "32:1-18"} +InfoProv {ipName = "BCon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "cafB2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "33:1-18"} +InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "BCon_Main_4_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "18:17-38"} +InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""} ===================================== testsuite/tests/rts/ipe/distinct-tables/distinct_tables03.stdout ===================================== @@ -0,0 +1,13 @@ +InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "CCon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "C", ipLabel = "cafC1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "34:1-27"} +InfoProv {ipName = "CCon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "C", ipLabel = "cafC2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "35:1-27"} +InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "CCon_Main_3_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "C", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "19:34-38"} ===================================== testsuite/tests/rts/ipe/distinct-tables/distinct_tables04.stdout ===================================== @@ -0,0 +1,13 @@ +InfoProv {ipName = "ACon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "cafA1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "30:1-15"} +InfoProv {ipName = "ACon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "cafA2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "31:1-15"} +InfoProv {ipName = "BCon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "cafB1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "32:1-18"} +InfoProv {ipName = "BCon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "cafB2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "33:1-18"} +InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "ACon_Main_4_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "13:17-35"} +InfoProv {ipName = "ACon_Main_0_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "37:1-17"} +InfoProv {ipName = "ACon_X_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA1", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = "6:1-16"} +InfoProv {ipName = "ACon_X_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA2", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = "7:1-16"} +InfoProv {ipName = "ACon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "17:17-37"} +InfoProv {ipName = "BCon_Main_4_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "18:17-38"} +InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""} ===================================== testsuite/tests/rts/ipe/distinct-tables/distinct_tables05.stdout ===================================== @@ -0,0 +1,13 @@ +InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "BCon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "cafB1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "32:1-18"} +InfoProv {ipName = "BCon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "cafB2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "33:1-18"} +InfoProv {ipName = "CCon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "C", ipLabel = "cafC1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "34:1-27"} +InfoProv {ipName = "CCon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "C", ipLabel = "cafC2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "35:1-27"} +InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "BCon_Main_4_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "18:17-38"} +InfoProv {ipName = "CCon_Main_3_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "C", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "19:34-38"} ===================================== testsuite/tests/rts/ipe/distinct-tables/distinct_tables06.stdout ===================================== @@ -0,0 +1,13 @@ +InfoProv {ipName = "ACon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "cafA1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "30:1-15"} +InfoProv {ipName = "ACon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "cafA2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "31:1-15"} +InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "CCon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "C", ipLabel = "cafC1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "34:1-27"} +InfoProv {ipName = "CCon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "C", ipLabel = "cafC2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "35:1-27"} +InfoProv {ipName = "ACon_Main_4_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "13:17-35"} +InfoProv {ipName = "ACon_Main_0_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "37:1-17"} +InfoProv {ipName = "ACon_X_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA1", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = "6:1-16"} +InfoProv {ipName = "ACon_X_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA2", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = "7:1-16"} +InfoProv {ipName = "ACon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "17:17-37"} +InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "CCon_Main_3_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "C", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "19:34-38"} ===================================== testsuite/tests/rts/ipe/distinct-tables/distinct_tables07.stdout ===================================== @@ -0,0 +1,13 @@ +InfoProv {ipName = "ACon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "cafA1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "30:1-15"} +InfoProv {ipName = "ACon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "cafA2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "31:1-15"} +InfoProv {ipName = "BCon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "cafB1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "32:1-18"} +InfoProv {ipName = "BCon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "cafB2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "33:1-18"} +InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "ACon_Main_4_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "13:17-35"} +InfoProv {ipName = "ACon_Main_0_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "37:1-17"} +InfoProv {ipName = "ACon_X_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA1", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = "6:1-16"} +InfoProv {ipName = "ACon_X_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA2", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = "7:1-16"} +InfoProv {ipName = "ACon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "17:17-37"} +InfoProv {ipName = "BCon_Main_4_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "18:17-38"} +InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""} ===================================== testsuite/tests/rts/ipe/distinct-tables/distinct_tables08.stdout ===================================== @@ -0,0 +1,13 @@ +InfoProv {ipName = "ACon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "cafA1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "30:1-15"} +InfoProv {ipName = "ACon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "cafA2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "31:1-15"} +InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "ACon_Main_4_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "13:17-35"} +InfoProv {ipName = "ACon_Main_0_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "37:1-17"} +InfoProv {ipName = "ACon_X_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA1", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = "6:1-16"} +InfoProv {ipName = "ACon_X_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA2", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = "7:1-16"} +InfoProv {ipName = "ACon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "17:17-37"} +InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""} +InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""} View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bbc3179500756a427cdafb2feecde4f... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bbc3179500756a427cdafb2feecde4f... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Hannes Siebenhandl (@fendor)