Hannes Siebenhandl pushed to branch wip/fendor/t23703 at Glasgow Haskell Compiler / GHC

Commits:

28 changed files:

Changes:

  • compiler/GHC/Data/Word64Map/Internal.hs
    ... ... @@ -100,6 +100,7 @@ module GHC.Data.Word64Map.Internal (
    100 100
         , updateWithKey
    
    101 101
         , updateLookupWithKey
    
    102 102
         , alter
    
    103
    +    , alterLookupWithKey
    
    103 104
         , alterF
    
    104 105
     
    
    105 106
         -- * Combine
    
    ... ... @@ -986,6 +987,39 @@ alter f k Nil = case f Nothing of
    986 987
                           Just x -> Tip k x
    
    987 988
                           Nothing -> Nil
    
    988 989
     
    
    990
    +-- | \(O(\min(n,W))\). The expression (@'alterLookupWithKey' f k map@) alters
    
    991
    +-- the value @x@ at @k@, or absence thereof, and returns the result of the
    
    992
    +-- alteration. 'alterLookupWithKey' can be used to insert, delete, or update a
    
    993
    +-- value in a 'Word64Map'.
    
    994
    +--
    
    995
    +-- Note that the behavior of this function differs from 'updateLookupWithKey',
    
    996
    +-- and instead matches the behavior of 'Data.Map.updateLookupWithKey'.
    
    997
    +alterLookupWithKey :: (Maybe a -> Maybe a) -> Key -> Word64Map a -> (Maybe a, Word64Map a)
    
    998
    +alterLookupWithKey f !k t@(Bin p m l r)
    
    999
    +  | nomatch k p m =
    
    1000
    +      case f Nothing of
    
    1001
    +        Nothing -> (Nothing, t)
    
    1002
    +        Just x -> (Just x, link k (Tip k x) p t)
    
    1003
    +  | zero k m =
    
    1004
    +      let !(res, l') = alterLookupWithKey f k l
    
    1005
    +      in (res, binCheckLeft p m l' r)
    
    1006
    +  | otherwise =
    
    1007
    +      let !(res, r') = alterLookupWithKey f k r
    
    1008
    +      in (res, binCheckRight p m l r')
    
    1009
    +alterLookupWithKey f k t@(Tip ky y)
    
    1010
    +  | k==ky =
    
    1011
    +      case f (Just y) of
    
    1012
    +        Just x -> (Just x, Tip ky x)
    
    1013
    +        Nothing -> (Nothing, Nil)
    
    1014
    +  | otherwise =
    
    1015
    +      case f Nothing of
    
    1016
    +        Just x -> (Just x, link k (Tip k x) ky t)
    
    1017
    +        Nothing -> (Nothing, Tip ky y)
    
    1018
    +alterLookupWithKey f k Nil =
    
    1019
    +  case f Nothing of
    
    1020
    +    Just x -> (Just x, Tip k x)
    
    1021
    +    Nothing -> (Nothing, Nil)
    
    1022
    +
    
    989 1023
     -- | \(O(\min(n,W))\). The expression (@'alterF' f k map@) alters the value @x@ at
    
    990 1024
     -- @k@, or absence thereof.  'alterF' can be used to inspect, insert, delete,
    
    991 1025
     -- 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 (
    93 93
         , updateWithKey
    
    94 94
         , updateLookupWithKey
    
    95 95
         , alter
    
    96
    +    , alterLookupWithKey
    
    96 97
         , alterF
    
    97 98
     
    
    98 99
         -- * Query
    

  • compiler/GHC/Driver/Config/Stg/Debug.hs
    ... ... @@ -10,5 +10,5 @@ import GHC.Driver.DynFlags
    10 10
     initStgDebugOpts :: DynFlags -> StgDebugOpts
    
    11 11
     initStgDebugOpts dflags = StgDebugOpts
    
    12 12
       { stgDebug_infoTableMap = gopt Opt_InfoTableMap dflags
    
    13
    -  , stgDebug_distinctConstructorTables = gopt Opt_DistinctConstructorTables dflags
    
    13
    +  , stgDebug_distinctConstructorTables = distinctConstructorTables dflags
    
    14 14
       }

  • compiler/GHC/Driver/DynFlags.hs
    ... ... @@ -117,6 +117,7 @@ import GHC.Types.SrcLoc
    117 117
     import GHC.Unit.Module
    
    118 118
     import GHC.Unit.Module.Warnings
    
    119 119
     import GHC.Utils.CliOption
    
    120
    +import GHC.Stg.Debug.Types (StgDebugDctConfig(..))
    
    120 121
     import GHC.SysTools.Terminal ( stderrSupportsAnsiColors )
    
    121 122
     import GHC.UniqueSubdir (uniqueSubdir)
    
    122 123
     import GHC.Utils.Outputable
    
    ... ... @@ -134,6 +135,7 @@ import Control.Monad.Trans.Class (lift)
    134 135
     import Control.Monad.Trans.Except (ExceptT)
    
    135 136
     import Control.Monad.Trans.Reader (ReaderT)
    
    136 137
     import Control.Monad.Trans.Writer (WriterT)
    
    138
    +import qualified Data.Set as Set
    
    137 139
     import Data.Word
    
    138 140
     import System.IO
    
    139 141
     import System.IO.Error (catchIOError)
    
    ... ... @@ -142,7 +144,6 @@ import System.FilePath (normalise, (</>))
    142 144
     import System.Directory
    
    143 145
     import GHC.Foreign (withCString, peekCString)
    
    144 146
     
    
    145
    -import qualified Data.Set as Set
    
    146 147
     import GHC.Types.Unique.Set
    
    147 148
     
    
    148 149
     import qualified GHC.LanguageExtensions as LangExt
    
    ... ... @@ -479,7 +480,11 @@ data DynFlags = DynFlags {
    479 480
         -- 'Int' because it can be used to test uniques in decreasing order.
    
    480 481
     
    
    481 482
       -- | Temporary: CFG Edge weights for fast iterations
    
    482
    -  cfgWeights            :: Weights
    
    483
    +  cfgWeights            :: Weights,
    
    484
    +
    
    485
    +  -- | Configuration specifying which constructor names we should create
    
    486
    +  -- distinct info tables for
    
    487
    +  distinctConstructorTables :: StgDebugDctConfig
    
    483 488
     }
    
    484 489
     
    
    485 490
     class HasDynFlags m where
    
    ... ... @@ -742,7 +747,9 @@ defaultDynFlags mySettings =
    742 747
     
    
    743 748
             reverseErrors = False,
    
    744 749
             maxErrors     = Nothing,
    
    745
    -        cfgWeights    = defaultWeights
    
    750
    +        cfgWeights    = defaultWeights,
    
    751
    +
    
    752
    +        distinctConstructorTables = None
    
    746 753
           }
    
    747 754
     
    
    748 755
     type FatalMessager = String -> IO ()
    

  • compiler/GHC/Driver/Flags.hs
    ... ... @@ -595,7 +595,6 @@ data GeneralFlag
    595 595
        | Opt_NoBuiltinRules
    
    596 596
        | Opt_NoBignumRules
    
    597 597
     
    
    598
    -   | Opt_DistinctConstructorTables
    
    599 598
        | Opt_InfoTableMap
    
    600 599
        | Opt_InfoTableMapWithFallback
    
    601 600
        | Opt_InfoTableMapWithStack
    
    ... ... @@ -986,7 +985,6 @@ codeGenFlags = EnumSet.fromList
    986 985
        , Opt_DoTagInferenceChecks
    
    987 986
     
    
    988 987
          -- Flags that affect debugging information
    
    989
    -   , Opt_DistinctConstructorTables
    
    990 988
        , Opt_InfoTableMap
    
    991 989
        , Opt_InfoTableMapWithStack
    
    992 990
        , Opt_InfoTableMapWithFallback
    

  • compiler/GHC/Driver/Session.hs
    ... ... @@ -277,6 +277,7 @@ import GHC.CmmToAsm.CFG.Weight
    277 277
     import GHC.Core.Opt.CallerCC
    
    278 278
     import GHC.Parser (parseIdentifier)
    
    279 279
     import GHC.Parser.Lexer (mkParserOpts, initParserState, P(..), ParseResult(..))
    
    280
    +import GHC.Stg.Debug.Types
    
    280 281
     
    
    281 282
     import GHC.SysTools.BaseDir ( expandToolDir, expandTopDir )
    
    282 283
     
    
    ... ... @@ -1916,6 +1917,10 @@ dynamic_flags_deps = [
    1916 1917
             -- Caller-CC
    
    1917 1918
       , make_ord_flag defGhcFlag "fprof-callers"
    
    1918 1919
              (HasArg setCallerCcFilters)
    
    1920
    +  , make_ord_flag defGhcFlag "fdistinct-constructor-tables"
    
    1921
    +      (OptPrefix setDistinctConstructorTables)
    
    1922
    +  , make_ord_flag defGhcFlag "fno-distinct-constructor-tables"
    
    1923
    +      (OptPrefix unSetDistinctConstructorTables)
    
    1919 1924
             ------ Compiler flags -----------------------------------------------
    
    1920 1925
     
    
    1921 1926
       , make_ord_flag defGhcFlag "fasm"             (NoArg (setObjBackend ncgBackend))
    
    ... ... @@ -2617,7 +2622,6 @@ fFlagsDeps = [
    2617 2622
       flagSpec "cmm-thread-sanitizer"             Opt_CmmThreadSanitizer,
    
    2618 2623
       flagSpec "split-sections"                   Opt_SplitSections,
    
    2619 2624
       flagSpec "break-points"                     Opt_InsertBreakpoints,
    
    2620
    -  flagSpec "distinct-constructor-tables"      Opt_DistinctConstructorTables,
    
    2621 2625
       flagSpec "info-table-map"                   Opt_InfoTableMap,
    
    2622 2626
       flagSpec "info-table-map-with-stack"        Opt_InfoTableMapWithStack,
    
    2623 2627
       flagSpec "info-table-map-with-fallback"     Opt_InfoTableMapWithFallback
    
    ... ... @@ -3215,6 +3219,39 @@ setCallerCcFilters arg =
    3215 3219
         Right filt -> upd $ \d -> d { callerCcFilters = filt : callerCcFilters d }
    
    3216 3220
         Left err -> addErr err
    
    3217 3221
     
    
    3222
    +setDistinctConstructorTables :: String -> DynP ()
    
    3223
    +setDistinctConstructorTables arg = do
    
    3224
    +  let cs = parseDistinctConstructorTablesArg arg
    
    3225
    +  upd $ \d ->
    
    3226
    +    d { distinctConstructorTables =
    
    3227
    +        (distinctConstructorTables d) `dctConfigPlus` cs
    
    3228
    +      }
    
    3229
    +
    
    3230
    +unSetDistinctConstructorTables :: String -> DynP ()
    
    3231
    +unSetDistinctConstructorTables arg = do
    
    3232
    +  let cs = parseDistinctConstructorTablesArg arg
    
    3233
    +  upd $ \d ->
    
    3234
    +    d { distinctConstructorTables =
    
    3235
    +        (distinctConstructorTables d) `dctConfigMinus` cs
    
    3236
    +      }
    
    3237
    +
    
    3238
    +-- | Parse a string of comma-separated constructor names into a 'Set' of
    
    3239
    +-- 'String's with one entry per constructor.
    
    3240
    +parseDistinctConstructorTablesArg :: String -> Set.Set String
    
    3241
    +parseDistinctConstructorTablesArg =
    
    3242
    +      -- Ensure we insert the last constructor name built by the fold, if not
    
    3243
    +      -- empty
    
    3244
    +      uncurry insertNonEmpty
    
    3245
    +    . foldr go ("", Set.empty)
    
    3246
    +  where
    
    3247
    +    go :: Char -> (String, Set.Set String) -> (String, Set.Set String)
    
    3248
    +    go ',' (cur, acc) = ("", Set.insert cur acc)
    
    3249
    +    go c   (cur, acc) = (c : cur, acc)
    
    3250
    +
    
    3251
    +    insertNonEmpty :: String -> Set.Set String -> Set.Set String
    
    3252
    +    insertNonEmpty "" = id
    
    3253
    +    insertNonEmpty cs = Set.insert cs
    
    3254
    +
    
    3218 3255
     setMainIs :: String -> DynP ()
    
    3219 3256
     setMainIs arg = parse parse_main_f arg
    
    3220 3257
       where
    

  • compiler/GHC/Iface/Flags.hs
    ... ... @@ -6,12 +6,15 @@ module GHC.Iface.Flags (
    6 6
        , IfaceExtension(..)
    
    7 7
        , IfaceLanguage(..)
    
    8 8
        , IfaceCppOptions(..)
    
    9
    +   , IfaceCodeGen(..)
    
    10
    +   , IfaceDistinctConstructorConfig(..)
    
    9 11
        , pprIfaceDynFlags
    
    10 12
        , missingExtraFlagInfo
    
    11 13
        ) where
    
    12 14
     
    
    13 15
     import GHC.Prelude
    
    14 16
     
    
    17
    +import qualified Data.Set as Set
    
    15 18
     import GHC.Utils.Outputable
    
    16 19
     import Control.DeepSeq
    
    17 20
     import GHC.Utils.Fingerprint
    
    ... ... @@ -22,6 +25,7 @@ import GHC.Types.SafeHaskell
    22 25
     import GHC.Core.Opt.CallerCC.Types
    
    23 26
     
    
    24 27
     import qualified GHC.LanguageExtensions as LangExt
    
    28
    +import GHC.Stg.Debug.Types
    
    25 29
     
    
    26 30
     -- The part of DynFlags which recompilation information needs
    
    27 31
     data IfaceDynFlags = IfaceDynFlags
    
    ... ... @@ -35,7 +39,7 @@ data IfaceDynFlags = IfaceDynFlags
    35 39
             , ifacePaths :: [String]
    
    36 40
             , ifaceProf  :: Maybe IfaceProfAuto
    
    37 41
             , ifaceTicky :: [IfaceGeneralFlag]
    
    38
    -        , ifaceCodeGen :: [IfaceGeneralFlag]
    
    42
    +        , ifaceCodeGen :: IfaceCodeGen
    
    39 43
             , ifaceFatIface :: Bool
    
    40 44
             , ifaceDebugLevel :: Int
    
    41 45
             , ifaceCallerCCFilters :: [CallerCcFilter]
    
    ... ... @@ -58,7 +62,7 @@ pprIfaceDynFlags (IfaceDynFlags a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14)
    58 62
            , text "ticky:"
    
    59 63
            , nest 2 $ vcat (map ppr a10)
    
    60 64
            , text "codegen:"
    
    61
    -       , nest 2 $ vcat (map ppr a11)
    
    65
    +       , nest 2 $ ppr a11
    
    62 66
            , text "fat-iface:" <+> ppr a12
    
    63 67
            , text "debug-level:" <+> ppr a13
    
    64 68
            , text "caller-cc-filters:" <+> ppr a14
    
    ... ... @@ -191,4 +195,66 @@ instance Outputable IfaceCppOptions where
    191 195
                  , text "signature:"
    
    192 196
                  , nest 2 $ parens (ppr fp) <+> ppr (map (text @SDoc) wos)
    
    193 197
     
    
    194
    -             ]
    \ No newline at end of file
    198
    +             ]
    
    199
    +
    
    200
    +data IfaceCodeGen = IfaceCodeGen
    
    201
    +  { ifaceCodeGenFlags :: [IfaceGeneralFlag]
    
    202
    +  , ifaceCodeGenDistinctConstructorTables :: IfaceDistinctConstructorConfig
    
    203
    +  }
    
    204
    +
    
    205
    +instance NFData IfaceCodeGen where
    
    206
    +  rnf (IfaceCodeGen flags distinctCnstrTables) =
    
    207
    +    rnf flags `seq` rnf distinctCnstrTables
    
    208
    +
    
    209
    +instance Binary IfaceCodeGen where
    
    210
    +  put_ bh (IfaceCodeGen flags distinctCnstrTables) = do
    
    211
    +    put_ bh flags
    
    212
    +    put_ bh distinctCnstrTables
    
    213
    +
    
    214
    +  get bh =
    
    215
    +    IfaceCodeGen <$> get bh <*> get bh
    
    216
    +
    
    217
    +instance Outputable IfaceCodeGen where
    
    218
    +  ppr (IfaceCodeGen flags distinctCnstrTables) =
    
    219
    +    vcat
    
    220
    +      [ text "flags:"
    
    221
    +      , nest 2 $ ppr flags
    
    222
    +      , text "distinct constructor tables:"
    
    223
    +      , nest 2 $ ppr distinctCnstrTables
    
    224
    +      ]
    
    225
    +
    
    226
    +newtype IfaceDistinctConstructorConfig = IfaceDistinctConstructorConfig StgDebugDctConfig
    
    227
    +
    
    228
    +instance NFData IfaceDistinctConstructorConfig where
    
    229
    +  rnf (IfaceDistinctConstructorConfig cnf) = case cnf of
    
    230
    +    All -> ()
    
    231
    +    (Only v) -> rnf v
    
    232
    +    (AllExcept v) -> rnf v
    
    233
    +    None -> ()
    
    234
    +
    
    235
    +instance Outputable IfaceDistinctConstructorConfig where
    
    236
    +  ppr (IfaceDistinctConstructorConfig cnf) = case cnf of
    
    237
    +    All -> text "all"
    
    238
    +    (Only v) -> text "only" <+> brackets (hcat $ fmap text $ Set.toList v)
    
    239
    +    (AllExcept v) -> text "all except" <+> brackets (hcat $ fmap text $ Set.toList v)
    
    240
    +    None -> text "none"
    
    241
    +
    
    242
    +instance Binary IfaceDistinctConstructorConfig where
    
    243
    +  put_ bh (IfaceDistinctConstructorConfig cnf) = case cnf of
    
    244
    +    All -> putByte bh 0
    
    245
    +    (Only cs) -> do
    
    246
    +      putByte bh 1
    
    247
    +      put_ bh cs
    
    248
    +    (AllExcept cs) -> do
    
    249
    +      putByte bh 2
    
    250
    +      put_ bh cs
    
    251
    +    None -> putByte bh 3
    
    252
    +
    
    253
    +  get bh = do
    
    254
    +    h <- getByte bh
    
    255
    +    IfaceDistinctConstructorConfig <$>
    
    256
    +      case h of
    
    257
    +        0 -> pure All
    
    258
    +        1 -> Only <$> get bh
    
    259
    +        2 -> AllExcept <$> get bh
    
    260
    +        _ -> pure None

  • compiler/GHC/Iface/Recomp/Flags.hs
    ... ... @@ -91,12 +91,30 @@ fingerprintDynFlags hsc_env this_mod nameio =
    91 91
               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]
    
    92 92
     
    
    93 93
             -- Other flags which affect code generation
    
    94
    -        codegen = mapMaybe (\f -> (if f `gopt` dflags then Just (IfaceGeneralFlag f) else Nothing)) (EnumSet.toList codeGenFlags)
    
    94
    +        codegen = IfaceCodeGen
    
    95
    +          { ifaceCodeGenFlags = mapMaybe (\f -> (if f `gopt` dflags then Just (IfaceGeneralFlag f) else Nothing)) (EnumSet.toList codeGenFlags)
    
    96
    +          , ifaceCodeGenDistinctConstructorTables = IfaceDistinctConstructorConfig distinctConstructorTables
    
    97
    +          }
    
    95 98
     
    
    96 99
             -- Did we include core for all bindings?
    
    97 100
             fat_iface = gopt Opt_WriteIfSimplifiedCore dflags
    
    98 101
     
    
    99
    -        f = IfaceDynFlags mainis safeHs lang exts cpp js cmm paths prof ticky codegen fat_iface debugLevel callerCcFilters
    
    102
    +        f = IfaceDynFlags
    
    103
    +          { ifaceMainIs = mainis
    
    104
    +          , ifaceSafeMode = safeHs
    
    105
    +          , ifaceLang = lang
    
    106
    +          , ifaceExts = exts
    
    107
    +          , ifaceCppOptions = cpp
    
    108
    +          , ifaceJsOptions = js
    
    109
    +          , ifaceCmmOptions = cmm
    
    110
    +          , ifacePaths = paths
    
    111
    +          , ifaceProf = prof
    
    112
    +          , ifaceTicky = ticky
    
    113
    +          , ifaceCodeGen = codegen
    
    114
    +          , ifaceFatIface = fat_iface
    
    115
    +          , ifaceDebugLevel = debugLevel
    
    116
    +          , ifaceCallerCCFilters = callerCcFilters
    
    117
    +          }
    
    100 118
     
    
    101 119
         in (computeFingerprint nameio f, f)
    
    102 120
     
    

  • compiler/GHC/Stg/Debug.hs
    1
    -{-# LANGUAGE TupleSections #-}
    
    1
    +{-# LANGUAGE RecordWildCards #-}
    
    2
    +{-# LANGUAGE TupleSections   #-}
    
    2 3
     
    
    3 4
     -- This module contains functions which implement
    
    4 5
     -- the -finfo-table-map and -fdistinct-constructor-tables flags
    
    5 6
     module GHC.Stg.Debug
    
    6 7
       ( StgDebugOpts(..)
    
    8
    +  , StgDebugDctConfig(..)
    
    9
    +  , dctConfigPlus
    
    10
    +  , dctConfigMinus
    
    7 11
       , collectDebugInformation
    
    8 12
       ) where
    
    9 13
     
    
    ... ... @@ -17,11 +21,13 @@ import GHC.Types.Tickish
    17 21
     import GHC.Core.DataCon
    
    18 22
     import GHC.Types.IPE
    
    19 23
     import GHC.Unit.Module
    
    20
    -import GHC.Types.Name   ( getName, getOccName, occNameFS, nameSrcSpan)
    
    24
    +import GHC.Types.Name   ( getName, getOccName, occNameFS, nameSrcSpan, occName, occNameString)
    
    21 25
     import GHC.Data.FastString
    
    26
    +import GHC.Stg.Debug.Types
    
    22 27
     
    
    23 28
     import Control.Monad (when)
    
    24 29
     import Control.Monad.Trans.Reader
    
    30
    +import qualified Data.Set as Set
    
    25 31
     import GHC.Utils.Monad.State.Strict
    
    26 32
     import Control.Monad.Trans.Class
    
    27 33
     import GHC.Types.SrcLoc
    
    ... ... @@ -29,13 +35,6 @@ import Control.Applicative
    29 35
     import qualified Data.List.NonEmpty as NE
    
    30 36
     import Data.List.NonEmpty (NonEmpty(..))
    
    31 37
     
    
    32
    -data SpanWithLabel = SpanWithLabel RealSrcSpan LexicalFastString
    
    33
    -
    
    34
    -data StgDebugOpts = StgDebugOpts
    
    35
    -  { stgDebug_infoTableMap              :: !Bool
    
    36
    -  , stgDebug_distinctConstructorTables :: !Bool
    
    37
    -  }
    
    38
    -
    
    39 38
     data R = R { rOpts :: StgDebugOpts, rModLocation :: ModLocation, rSpan :: Maybe SpanWithLabel }
    
    40 39
     
    
    41 40
     type M a = ReaderT R (State InfoTableProvMap) a
    
    ... ... @@ -155,6 +154,8 @@ recordStgIdPosition id best_span ss = do
    155 154
         let mbspan = (\(SpanWithLabel rss d) -> (rss, d)) <$> (best_span <|> cc <|> ss)
    
    156 155
         lift $ modify (\env -> env { provClosure = addToUDFM (provClosure env) (idName id) (idName id, (idType id, mbspan)) })
    
    157 156
     
    
    157
    +-- | If @-fdistinct-constructor-tables@ is enabled, each occurrence of a data
    
    158
    +-- constructor will be given its own info table
    
    158 159
     numberDataCon :: DataCon -> [StgTickish] -> M ConstructorNumber
    
    159 160
     -- Unboxed tuples and sums do not allocate so they
    
    160 161
     -- have no info tables.
    
    ... ... @@ -162,22 +163,59 @@ numberDataCon dc _ | isUnboxedTupleDataCon dc = return NoNumber
    162 163
     numberDataCon dc _ | isUnboxedSumDataCon dc = return NoNumber
    
    163 164
     numberDataCon dc ts = do
    
    164 165
       opts <- asks rOpts
    
    165
    -  if not (stgDebug_distinctConstructorTables opts) then return NoNumber else do
    
    166
    +  if shouldMakeDistinctTable opts dc then do
    
    167
    +    -- -fdistinct-constructor-tables is enabled and we do want to make distinct
    
    168
    +    -- tables for this constructor. Add an entry to the data constructor map for
    
    169
    +    -- this occurrence of the data constructor with a unique number and a src
    
    170
    +    -- span
    
    166 171
         env <- lift get
    
    167 172
         mcc <- asks rSpan
    
    168
    -    let !mbest_span = (\(SpanWithLabel rss l) -> (rss, l)) <$> (selectTick ts <|> mcc)
    
    169
    -    let !dcMap' = alterUDFM (maybe (Just (dc, (0, mbest_span) :| [] ))
    
    170
    -                        (\(_dc, xs@((k, _):|_)) -> Just $! (dc, (k + 1, mbest_span) `NE.cons` xs))) (provDC env) dc
    
    173
    +    let
    
    174
    +      -- Guess a src span for this occurrence using source note ticks and the
    
    175
    +      -- current span in the environment
    
    176
    +      !mbest_span = selectTick ts <|> (\(SpanWithLabel rss l) -> (rss, l)) <$> mcc
    
    177
    +
    
    178
    +      -- Add the occurrence to the data constructor map of the InfoTableProvMap,
    
    179
    +      -- noting the unique number assigned for this occurence
    
    180
    +      (!r, !dcMap') =
    
    181
    +        alterUDFM_L
    
    182
    +          ( maybe
    
    183
    +              (Just (dc, (0, mbest_span) :| [] ))
    
    184
    +              ( \(_dc, xs@((k, _):|_)) ->
    
    185
    +                  Just $! (dc, (k + 1, mbest_span) `NE.cons` xs)
    
    186
    +              )
    
    187
    +          )
    
    188
    +          (provDC env)
    
    189
    +          dc
    
    171 190
         lift $ put (env { provDC = dcMap' })
    
    172
    -    let r = lookupUDFM dcMap' dc
    
    173 191
         return $ case r of
    
    174 192
           Nothing -> NoNumber
    
    175 193
           Just (_, res) -> Numbered (fst (NE.head res))
    
    194
    +  else do
    
    195
    +    -- -fdistinct-constructor-tables is not enabled, or we do not want to make
    
    196
    +    -- distinct tables for this specific constructor
    
    197
    +    return NoNumber
    
    176 198
     
    
    177
    -selectTick :: [StgTickish] -> Maybe SpanWithLabel
    
    178
    -selectTick [] = Nothing
    
    179
    -selectTick (SourceNote rss d : ts ) = selectTick ts <|> Just (SpanWithLabel rss d)
    
    180
    -selectTick (_:ts) = selectTick ts
    
    199
    +selectTick :: [StgTickish] -> Maybe (RealSrcSpan, LexicalFastString)
    
    200
    +selectTick = foldl' go Nothing
    
    201
    +  where
    
    202
    +    go :: Maybe (RealSrcSpan, LexicalFastString) -> StgTickish -> Maybe (RealSrcSpan, LexicalFastString)
    
    203
    +    go _   (SourceNote rss d) = Just (rss, d)
    
    204
    +    go acc _                  = acc
    
    205
    +
    
    206
    +-- | Descide whether a distinct info table should be made for a usage of a data
    
    207
    +-- constructor. We only want to do this if -fdistinct-constructor-tables was
    
    208
    +-- given and this constructor name was given, or no constructor names were
    
    209
    +-- given.
    
    210
    +shouldMakeDistinctTable :: StgDebugOpts -> DataCon -> Bool
    
    211
    +shouldMakeDistinctTable StgDebugOpts{..} dc =
    
    212
    +  case stgDebug_distinctConstructorTables of
    
    213
    +    All -> True
    
    214
    +    Only these -> Set.member dcStr these
    
    215
    +    AllExcept these -> Set.notMember dcStr these
    
    216
    +    None -> False
    
    217
    +  where
    
    218
    +    dcStr = occNameString . occName $ dataConName dc
    
    181 219
     
    
    182 220
     {-
    
    183 221
     Note [Mapping Info Tables to Source Positions]
    

  • compiler/GHC/Stg/Debug/Types.hs
    1
    +module GHC.Stg.Debug.Types where
    
    2
    +
    
    3
    +import GHC.Prelude
    
    4
    +
    
    5
    +import GHC.Data.FastString
    
    6
    +import GHC.Types.SrcLoc
    
    7
    +
    
    8
    +import Data.Set (Set)
    
    9
    +import qualified Data.Set as Set
    
    10
    +
    
    11
    +data SpanWithLabel = SpanWithLabel RealSrcSpan LexicalFastString
    
    12
    +
    
    13
    +data StgDebugOpts = StgDebugOpts
    
    14
    +  { stgDebug_infoTableMap              :: !Bool
    
    15
    +  , stgDebug_distinctConstructorTables :: !StgDebugDctConfig
    
    16
    +  }
    
    17
    +
    
    18
    +-- | Configuration describing which constructors should be given distinct info
    
    19
    +-- tables for each usage.
    
    20
    +data StgDebugDctConfig =
    
    21
    +    -- | Create distinct constructor tables for each usage of any data
    
    22
    +    -- constructor.
    
    23
    +    --
    
    24
    +    -- This is the behavior if just @-fdistinct-constructor-tables@ is supplied.
    
    25
    +    All
    
    26
    +
    
    27
    +    -- | Create distinct constructor tables for each usage of only these data
    
    28
    +    -- constructors.
    
    29
    +    --
    
    30
    +    -- This is the behavior if @-fdistinct-constructor-tables=C1,...,CN@ is
    
    31
    +    -- supplied.
    
    32
    +  | Only !(Set String)
    
    33
    +
    
    34
    +    -- | Create distinct constructor tables for each usage of any data
    
    35
    +    -- constructor except these ones.
    
    36
    +    --
    
    37
    +    -- This is the behavior if @-fdistinct-constructor-tables@ and
    
    38
    +    -- @-fno-distinct-constructor-tables=C1,...,CN@ is given.
    
    39
    +  | AllExcept !(Set String)
    
    40
    +
    
    41
    +    -- | Do not create distinct constructor tables for any data constructor.
    
    42
    +    --
    
    43
    +    -- This is the behavior if no @-fdistinct-constructor-tables@ is given (or
    
    44
    +    -- @-fno-distinct-constructor-tables@ is given).
    
    45
    +  | None
    
    46
    +
    
    47
    +-- | Given a distinct constructor tables configuration and a set of constructor
    
    48
    +-- names that we want to generate distinct info tables for, create a new
    
    49
    +-- configuration which includes those constructors.
    
    50
    +--
    
    51
    +-- If the given set is empty, that means the user has entered
    
    52
    +-- @-fdistinct-constructor-tables@ with no constructor names specified, and
    
    53
    +-- therefore we consider that an 'All' configuration.
    
    54
    +dctConfigPlus :: StgDebugDctConfig -> Set String -> StgDebugDctConfig
    
    55
    +dctConfigPlus cfg cs
    
    56
    +    | Set.null cs = All
    
    57
    +    | otherwise =
    
    58
    +        case cfg of
    
    59
    +          All -> All
    
    60
    +          Only cs' -> Only $ Set.union cs' cs
    
    61
    +          AllExcept cs' -> AllExcept $ Set.difference cs' cs
    
    62
    +          None -> Only cs
    
    63
    +
    
    64
    +-- | Given a distinct constructor tables configuration and a set of constructor
    
    65
    +-- names that we /do not/ want to generate distinct info tables for, create a
    
    66
    +-- new configuration which excludes those constructors.
    
    67
    +--
    
    68
    +-- If the given set is empty, that means the user has entered
    
    69
    +-- @-fno-distinct-constructor-tables@ with no constructor names specified, and
    
    70
    +-- therefore we consider that a 'None' configuration.
    
    71
    +dctConfigMinus :: StgDebugDctConfig -> Set String -> StgDebugDctConfig
    
    72
    +dctConfigMinus cfg cs
    
    73
    +    | Set.null cs = None
    
    74
    +    | otherwise =
    
    75
    +        case cfg of
    
    76
    +          All -> AllExcept cs
    
    77
    +          Only cs' -> Only $ Set.difference cs' cs
    
    78
    +          AllExcept cs' -> AllExcept $ Set.union cs' cs
    
    79
    +          None -> None
    
    80
    +

  • compiler/GHC/Types/Unique/DFM.hs
    ... ... @@ -39,6 +39,7 @@ module GHC.Types.Unique.DFM (
    39 39
             adjustUDFM,
    
    40 40
             adjustUDFM_Directly,
    
    41 41
             alterUDFM,
    
    42
    +        alterUDFM_L,
    
    42 43
             mapUDFM,
    
    43 44
             mapMaybeUDFM,
    
    44 45
             mapMUDFM,
    
    ... ... @@ -436,16 +437,18 @@ adjustUDFM f (UDFM m i) k = UDFM (M.adjust (fmap f) (getKey $ getUnique k) m) i
    436 437
     adjustUDFM_Directly :: (elt -> elt) -> UniqDFM key elt -> Unique -> UniqDFM key elt
    
    437 438
     adjustUDFM_Directly f (UDFM m i) k = UDFM (M.adjust (fmap f) (getKey k) m) i
    
    438 439
     
    
    439
    --- | The expression (alterUDFM f k map) alters value x at k, or absence
    
    440
    --- thereof. alterUDFM can be used to insert, delete, or update a value in
    
    440
    +-- | The expression (@'alterUDFM' f map k@) alters value x at k, or absence
    
    441
    +-- thereof. 'alterUDFM' can be used to insert, delete, or update a value in
    
    441 442
     -- UniqDFM. Use addToUDFM, delFromUDFM or adjustUDFM when possible, they are
    
    442 443
     -- more efficient.
    
    444
    +--
    
    445
    +-- 'alterUDFM' is non-strict in @k@.
    
    443 446
     alterUDFM
    
    444 447
       :: Uniquable key
    
    445
    -  => (Maybe elt -> Maybe elt)  -- How to adjust
    
    446
    -  -> UniqDFM key elt               -- old
    
    447
    -  -> key                       -- new
    
    448
    -  -> UniqDFM key elt               -- result
    
    448
    +  => (Maybe elt -> Maybe elt)  -- ^ How to adjust the element
    
    449
    +  -> UniqDFM key elt           -- ^ Old 'UniqDFM'
    
    450
    +  -> key                       -- ^ @key@ of the element to adjust
    
    451
    +  -> UniqDFM key elt           -- ^ New element at @key@ and modified 'UniqDFM'
    
    449 452
     alterUDFM f (UDFM m i) k =
    
    450 453
       UDFM (M.alter alterf (getKey $ getUnique k) m) (i + 1)
    
    451 454
       where
    
    ... ... @@ -454,6 +457,31 @@ alterUDFM f (UDFM m i) k =
    454 457
       inject Nothing = Nothing
    
    455 458
       inject (Just v) = Just $ TaggedVal v i
    
    456 459
     
    
    460
    +-- | The expression (@'alterUDFM_L' f map k@) alters value @x@ at @k@, or absence
    
    461
    +-- thereof and returns the new element at @k@ if there is any.
    
    462
    +-- 'alterUDFM_L' can be used to insert, delete, or update a value in
    
    463
    +-- UniqDFM. Use addToUDFM, delFromUDFM or adjustUDFM when possible, they are
    
    464
    +-- more efficient.
    
    465
    +--
    
    466
    +-- Note, 'alterUDFM_L' is strict in @k@.
    
    467
    +alterUDFM_L
    
    468
    +  :: forall key elt . Uniquable key
    
    469
    +  => (Maybe elt -> Maybe elt)      -- ^ How to adjust the element
    
    470
    +  -> UniqDFM key elt               -- ^ Old 'UniqDFM'
    
    471
    +  -> key                           -- ^ @key@ of the element to adjust
    
    472
    +  -> (Maybe elt, UniqDFM key elt)  -- ^ New element at @key@ and modified 'UniqDFM'
    
    473
    +alterUDFM_L f (UDFM m i) k =
    
    474
    +  let
    
    475
    +    (mElt, udfm) = M.alterLookupWithKey alterf (getKey $ getUnique k) m
    
    476
    +  in
    
    477
    +    (fmap taggedFst mElt, UDFM udfm (i + 1))
    
    478
    +  where
    
    479
    +  alterf :: Maybe (TaggedVal elt) -> (Maybe (TaggedVal elt))
    
    480
    +  alterf Nothing = inject $ f Nothing
    
    481
    +  alterf (Just (TaggedVal v _)) = inject $ f (Just v)
    
    482
    +  inject Nothing = Nothing
    
    483
    +  inject (Just v) = Just $ TaggedVal v i
    
    484
    +
    
    457 485
     -- | Map a function over every value in a UniqDFM
    
    458 486
     mapUDFM :: (elt1 -> elt2) -> UniqDFM key elt1 -> UniqDFM key elt2
    
    459 487
     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 (
    44 44
             addListToUFM,addListToUFM_C,
    
    45 45
             addToUFM_Directly,
    
    46 46
             addListToUFM_Directly,
    
    47
    -        adjustUFM, alterUFM, alterUFM_Directly,
    
    47
    +        adjustUFM, alterUFM, alterUFM_L, alterUFM_Directly,
    
    48 48
             adjustUFM_Directly,
    
    49 49
             delFromUFM,
    
    50 50
             delFromUFM_Directly,
    
    ... ... @@ -215,6 +215,16 @@ alterUFM
    215 215
       -> UniqFM key elt            -- ^ result
    
    216 216
     alterUFM f (UFM m) k = UFM (M.alter f (getKey $ getUnique k) m)
    
    217 217
     
    
    218
    +alterUFM_L
    
    219
    +  :: Uniquable key
    
    220
    +  => (Maybe elt -> Maybe elt)    -- ^ How to adjust
    
    221
    +  -> UniqFM key elt              -- ^ old
    
    222
    +  -> key                         -- ^ new
    
    223
    +  -> (Maybe elt, UniqFM key elt) -- ^ result
    
    224
    +alterUFM_L f (UFM m) k =
    
    225
    +  let (r, m') = (M.alterLookupWithKey f (getKey $ getUnique k) m)
    
    226
    +  in (r, UFM m')
    
    227
    +
    
    218 228
     alterUFM_Directly
    
    219 229
       :: (Maybe elt -> Maybe elt)  -- ^ How to adjust
    
    220 230
       -> UniqFM key elt            -- ^ old
    

  • compiler/ghc.cabal.in
    ... ... @@ -739,6 +739,7 @@ Library
    739 739
             GHC.Stg.EnforceEpt.Rewrite
    
    740 740
             GHC.Stg.EnforceEpt.TagSig
    
    741 741
             GHC.Stg.EnforceEpt.Types
    
    742
    +        GHC.Stg.Debug.Types
    
    742 743
             GHC.Stg.FVs
    
    743 744
             GHC.Stg.Lift
    
    744 745
             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
    368 368
         an info table to an approximate source position of where that
    
    369 369
         info table statically originated from. If you
    
    370 370
         also want more precise information about constructor info tables then you
    
    371
    -    should also use :ghc-flag:`-fdistinct-constructor-tables`.
    
    371
    +    should also use :ghc-flag:`-fdistinct-constructor-tables
    
    372
    +    <-fdistinct-constructor-tables=⟨cs⟩>`.
    
    372 373
     
    
    373 374
         The :ghc-flag:`-finfo-table-map` flag will increase the binary size by quite
    
    374 375
         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
    453 454
         from the info table map and decrease the size of executables with info table
    
    454 455
         profiling information.
    
    455 456
     
    
    456
    -.. ghc-flag:: -fdistinct-constructor-tables
    
    457
    +.. ghc-flag:: -fdistinct-constructor-tables=⟨cs⟩
    
    457 458
         :shortdesc: Generate a fresh info table for each usage
    
    458 459
                     of a data constructor.
    
    459 460
         :type: dynamic
    
    ... ... @@ -467,6 +468,41 @@ to a source location. This lookup table is generated by using the ``-finfo-table
    467 468
         each info table will correspond to the usage of a data constructor rather
    
    468 469
         than the data constructor itself.
    
    469 470
     
    
    471
    +    :since: 9.16
    
    472
    +
    
    473
    +    The entries in the info table map resulting from this flag may significantly
    
    474
    +    increase the size of executables. However, generating distinct info tables
    
    475
    +    for *every* usage of *every* data constructor often results in more
    
    476
    +    information than necessary. Instead, we would like to generate these
    
    477
    +    distinct tables for some specific constructors. To do this, the names of the
    
    478
    +    constructors we are interested in may be supplied to this flag in a
    
    479
    +    comma-separated list. If no constructor names are supplied (i.e. just
    
    480
    +    ``-fdistinct-constructor-tables`` is given) then fresh info tables will be
    
    481
    +    generated for every usage of every constructor.
    
    482
    +
    
    483
    +    For example, to only generate distinct info tables for the ``Just`` and
    
    484
    +    ``Right`` constructors, use ``-fdistinct-constructor-tables=Just,Right``.
    
    485
    +
    
    486
    +.. ghc-flag:: -fno-distinct-constructor-tables=⟨cs⟩
    
    487
    +    :shortdesc: Avoid generating a fresh info table for each usage of a data
    
    488
    +                constructor.
    
    489
    +    :type: dynamic
    
    490
    +    :category: debugging
    
    491
    +
    
    492
    +    :since: 9.16
    
    493
    +
    
    494
    +    Use this flag to refine the set of data constructors for which distinct info
    
    495
    +    tables are generated (as specified by
    
    496
    +    :ghc-flag:`-fdistinct-constructor-tables
    
    497
    +    <-fdistinct-constructor-tables=⟨cs⟩>`).
    
    498
    +    If no constructor names are given
    
    499
    +    (i.e. just ``-fno-distinct-constructor-tables`` is given) then no distinct
    
    500
    +    info tables will be generated for any usages of any data constructors.
    
    501
    +
    
    502
    +    For example, to generate distinct constructor tables for all data
    
    503
    +    constructors except those named ``MyConstr``, pass both
    
    504
    +    ``-fdistinct-constructor-tables`` and
    
    505
    +    ``-fno-distinct-constructor-tables=MyConstr``.
    
    470 506
     
    
    471 507
     Querying the Info Table Map
    
    472 508
     ---------------------------
    

  • testsuite/tests/count-deps/CountDepsAst.stdout
    ... ... @@ -123,6 +123,7 @@ GHC.Runtime.Heap.Layout
    123 123
     GHC.Settings
    
    124 124
     GHC.Settings.Config
    
    125 125
     GHC.Settings.Constants
    
    126
    +GHC.Stg.Debug.Types
    
    126 127
     GHC.Stg.EnforceEpt.TagSig
    
    127 128
     GHC.StgToCmm.Types
    
    128 129
     GHC.SysTools.Terminal
    

  • testsuite/tests/count-deps/CountDepsParser.stdout
    ... ... @@ -142,6 +142,7 @@ GHC.Runtime.Heap.Layout
    142 142
     GHC.Settings
    
    143 143
     GHC.Settings.Config
    
    144 144
     GHC.Settings.Constants
    
    145
    +GHC.Stg.Debug.Types
    
    145 146
     GHC.Stg.EnforceEpt.TagSig
    
    146 147
     GHC.StgToCmm.Types
    
    147 148
     GHC.SysTools.Terminal
    

  • testsuite/tests/rts/ipe/distinct-tables/Main.hs
    1
    +module Main where
    
    2
    +
    
    3
    +import GHC.InfoProv
    
    4
    +import qualified X
    
    5
    +
    
    6
    +main = do
    
    7
    +    printIp =<< whereFrom cafA1
    
    8
    +    printIp =<< whereFrom cafA2
    
    9
    +    printIp =<< whereFrom cafB1
    
    10
    +    printIp =<< whereFrom cafB2
    
    11
    +    printIp =<< whereFrom cafC1
    
    12
    +    printIp =<< whereFrom cafC2
    
    13
    +    printIp =<< whereFrom (ACon ())
    
    14
    +    printIp =<< whereFrom cafXA
    
    15
    +    printIp =<< whereFrom X.cafXA1
    
    16
    +    printIp =<< whereFrom X.cafXA2
    
    17
    +    printIp =<< whereFrom (X.ACon ())
    
    18
    +    printIp =<< whereFrom (BCon cafA1)
    
    19
    +    printIp =<< whereFrom (CCon (cafA1, BCon (ACon ())))
    
    20
    +  where
    
    21
    +    -- Get rid of the src file path since it makes test output difficult to diff
    
    22
    +    -- on Windows
    
    23
    +    printIp = print . stripIpSrc
    
    24
    +    stripIpSrc (Just ip) = ip { ipSrcFile = "" }
    
    25
    +
    
    26
    +data A = ACon ()
    
    27
    +data B = BCon A
    
    28
    +data C = CCon (A, B)
    
    29
    +
    
    30
    +cafA1 = ACon ()
    
    31
    +cafA2 = ACon ()
    
    32
    +cafB1 = BCon cafA1
    
    33
    +cafB2 = BCon cafA2
    
    34
    +cafC1 = CCon (cafA1, cafB1)
    
    35
    +cafC2 = CCon (cafA2, cafB2)
    
    36
    +
    
    37
    +cafXA = X.ACon ()

  • testsuite/tests/rts/ipe/distinct-tables/Makefile
    1
    +TOP=../../../..
    
    2
    +include $(TOP)/mk/boilerplate.mk
    
    3
    +include $(TOP)/mk/test.mk
    
    4
    +
    
    5
    +# This test runs ghc with various combinations of
    
    6
    +# -f{no-}distinct-constructor-tables for different constructors and checks that
    
    7
    +# whereFrom finds (or fails to find) their provenance appropriately.
    
    8
    +
    
    9
    +distinct_tables01:
    
    10
    +	$(TEST_HC) $(TEST_HC_OPTS) -v0 -finfo-table-map -fdistinct-constructor-tables=ACon Main.hs
    
    11
    +	./Main
    
    12
    +
    
    13
    +distinct_tables02:
    
    14
    +	$(TEST_HC) $(TEST_HC_OPTS) -v0 -finfo-table-map -fdistinct-constructor-tables=BCon Main.hs
    
    15
    +	./Main
    
    16
    +
    
    17
    +distinct_tables03:
    
    18
    +	$(TEST_HC) $(TEST_HC_OPTS) -v0 -finfo-table-map -fdistinct-constructor-tables=CCon Main.hs
    
    19
    +	./Main
    
    20
    +
    
    21
    +distinct_tables04:
    
    22
    +	$(TEST_HC) $(TEST_HC_OPTS) -v0 -finfo-table-map -fdistinct-constructor-tables=ACon,BCon Main.hs
    
    23
    +	./Main
    
    24
    +
    
    25
    +distinct_tables05:
    
    26
    +	$(TEST_HC) $(TEST_HC_OPTS) -v0 -finfo-table-map -fdistinct-constructor-tables -fno-distinct-constructor-tables=ACon Main.hs
    
    27
    +	./Main
    
    28
    +
    
    29
    +distinct_tables06:
    
    30
    +	$(TEST_HC) $(TEST_HC_OPTS) -v0 -finfo-table-map -fdistinct-constructor-tables -fno-distinct-constructor-tables=BCon Main.hs
    
    31
    +	./Main
    
    32
    +
    
    33
    +distinct_tables07:
    
    34
    +	$(TEST_HC) $(TEST_HC_OPTS) -v0 -finfo-table-map -fdistinct-constructor-tables -fno-distinct-constructor-tables=CCon Main.hs
    
    35
    +	./Main
    
    36
    +
    
    37
    +distinct_tables08:
    
    38
    +	$(TEST_HC) $(TEST_HC_OPTS) -v0 -finfo-table-map -fdistinct-constructor-tables -fno-distinct-constructor-tables=BCon,CCon Main.hs
    
    39
    +	./Main

  • testsuite/tests/rts/ipe/distinct-tables/X.hs
    1
    +module X where
    
    2
    +
    
    3
    +-- A type with the same constructor name as 'Main.ACon'
    
    4
    +data X = ACon ()
    
    5
    +
    
    6
    +cafXA1 = ACon ()
    
    7
    +cafXA2 = ACon ()

  • testsuite/tests/rts/ipe/distinct-tables/all.T
    1
    +test('distinct_tables01', [extra_files(['Main.hs', 'X.hs',])], makefile_test, [])
    
    2
    +test('distinct_tables02', [extra_files(['Main.hs', 'X.hs',])], makefile_test, [])
    
    3
    +test('distinct_tables03', [extra_files(['Main.hs', 'X.hs',])], makefile_test, [])
    
    4
    +test('distinct_tables04', [extra_files(['Main.hs', 'X.hs',])], makefile_test, [])
    
    5
    +test('distinct_tables05', [extra_files(['Main.hs', 'X.hs',])], makefile_test, [])
    
    6
    +test('distinct_tables06', [extra_files(['Main.hs', 'X.hs',])], makefile_test, [])
    
    7
    +test('distinct_tables07', [extra_files(['Main.hs', 'X.hs',])], makefile_test, [])
    
    8
    +test('distinct_tables08', [extra_files(['Main.hs', 'X.hs',])], makefile_test, [])

  • testsuite/tests/rts/ipe/distinct-tables/distinct_tables01.stdout
    1
    +InfoProv {ipName = "ACon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "cafA1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "30:1-15"}
    
    2
    +InfoProv {ipName = "ACon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "cafA2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "31:1-15"}
    
    3
    +InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
    
    4
    +InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
    
    5
    +InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
    
    6
    +InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
    
    7
    +InfoProv {ipName = "ACon_Main_4_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "13:17-35"}
    
    8
    +InfoProv {ipName = "ACon_Main_0_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "37:1-17"}
    
    9
    +InfoProv {ipName = "ACon_X_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA1", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = "6:1-16"}
    
    10
    +InfoProv {ipName = "ACon_X_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA2", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = "7:1-16"}
    
    11
    +InfoProv {ipName = "ACon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "17:17-37"}
    
    12
    +InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
    
    13
    +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
    1
    +InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
    
    2
    +InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
    
    3
    +InfoProv {ipName = "BCon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "cafB1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "32:1-18"}
    
    4
    +InfoProv {ipName = "BCon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "cafB2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "33:1-18"}
    
    5
    +InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
    
    6
    +InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
    
    7
    +InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
    
    8
    +InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""}
    
    9
    +InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""}
    
    10
    +InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""}
    
    11
    +InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""}
    
    12
    +InfoProv {ipName = "BCon_Main_4_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "18:17-38"}
    
    13
    +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
    1
    +InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
    
    2
    +InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
    
    3
    +InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
    
    4
    +InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
    
    5
    +InfoProv {ipName = "CCon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "C", ipLabel = "cafC1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "34:1-27"}
    
    6
    +InfoProv {ipName = "CCon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "C", ipLabel = "cafC2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "35:1-27"}
    
    7
    +InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
    
    8
    +InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""}
    
    9
    +InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""}
    
    10
    +InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""}
    
    11
    +InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""}
    
    12
    +InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
    
    13
    +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
    1
    +InfoProv {ipName = "ACon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "cafA1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "30:1-15"}
    
    2
    +InfoProv {ipName = "ACon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "cafA2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "31:1-15"}
    
    3
    +InfoProv {ipName = "BCon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "cafB1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "32:1-18"}
    
    4
    +InfoProv {ipName = "BCon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "cafB2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "33:1-18"}
    
    5
    +InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
    
    6
    +InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
    
    7
    +InfoProv {ipName = "ACon_Main_4_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "13:17-35"}
    
    8
    +InfoProv {ipName = "ACon_Main_0_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "37:1-17"}
    
    9
    +InfoProv {ipName = "ACon_X_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA1", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = "6:1-16"}
    
    10
    +InfoProv {ipName = "ACon_X_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA2", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = "7:1-16"}
    
    11
    +InfoProv {ipName = "ACon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "17:17-37"}
    
    12
    +InfoProv {ipName = "BCon_Main_4_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "18:17-38"}
    
    13
    +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
    1
    +InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
    
    2
    +InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
    
    3
    +InfoProv {ipName = "BCon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "cafB1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "32:1-18"}
    
    4
    +InfoProv {ipName = "BCon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "cafB2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "33:1-18"}
    
    5
    +InfoProv {ipName = "CCon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "C", ipLabel = "cafC1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "34:1-27"}
    
    6
    +InfoProv {ipName = "CCon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "C", ipLabel = "cafC2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "35:1-27"}
    
    7
    +InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
    
    8
    +InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""}
    
    9
    +InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""}
    
    10
    +InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""}
    
    11
    +InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""}
    
    12
    +InfoProv {ipName = "BCon_Main_4_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "18:17-38"}
    
    13
    +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
    1
    +InfoProv {ipName = "ACon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "cafA1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "30:1-15"}
    
    2
    +InfoProv {ipName = "ACon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "cafA2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "31:1-15"}
    
    3
    +InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
    
    4
    +InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
    
    5
    +InfoProv {ipName = "CCon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "C", ipLabel = "cafC1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "34:1-27"}
    
    6
    +InfoProv {ipName = "CCon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "C", ipLabel = "cafC2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "35:1-27"}
    
    7
    +InfoProv {ipName = "ACon_Main_4_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "13:17-35"}
    
    8
    +InfoProv {ipName = "ACon_Main_0_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "37:1-17"}
    
    9
    +InfoProv {ipName = "ACon_X_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA1", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = "6:1-16"}
    
    10
    +InfoProv {ipName = "ACon_X_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA2", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = "7:1-16"}
    
    11
    +InfoProv {ipName = "ACon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "17:17-37"}
    
    12
    +InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
    
    13
    +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
    1
    +InfoProv {ipName = "ACon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "cafA1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "30:1-15"}
    
    2
    +InfoProv {ipName = "ACon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "cafA2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "31:1-15"}
    
    3
    +InfoProv {ipName = "BCon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "cafB1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "32:1-18"}
    
    4
    +InfoProv {ipName = "BCon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "cafB2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "33:1-18"}
    
    5
    +InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
    
    6
    +InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
    
    7
    +InfoProv {ipName = "ACon_Main_4_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "13:17-35"}
    
    8
    +InfoProv {ipName = "ACon_Main_0_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "37:1-17"}
    
    9
    +InfoProv {ipName = "ACon_X_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA1", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = "6:1-16"}
    
    10
    +InfoProv {ipName = "ACon_X_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA2", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = "7:1-16"}
    
    11
    +InfoProv {ipName = "ACon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "17:17-37"}
    
    12
    +InfoProv {ipName = "BCon_Main_4_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "18:17-38"}
    
    13
    +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
    1
    +InfoProv {ipName = "ACon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "cafA1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "30:1-15"}
    
    2
    +InfoProv {ipName = "ACon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "cafA2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "31:1-15"}
    
    3
    +InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
    
    4
    +InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
    
    5
    +InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
    
    6
    +InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
    
    7
    +InfoProv {ipName = "ACon_Main_4_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "13:17-35"}
    
    8
    +InfoProv {ipName = "ACon_Main_0_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "37:1-17"}
    
    9
    +InfoProv {ipName = "ACon_X_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA1", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = "6:1-16"}
    
    10
    +InfoProv {ipName = "ACon_X_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA2", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = "7:1-16"}
    
    11
    +InfoProv {ipName = "ACon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "17:17-37"}
    
    12
    +InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
    
    13
    +InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}