Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC

Commits:

14 changed files:

Changes:

  • compiler/GHC/ByteCode/Asm.hs
    ... ... @@ -843,16 +843,18 @@ assembleI platform i = case i of
    843 843
     
    
    844 844
       BRK_FUN ibi@(InternalBreakpointId info_mod infox) -> do
    
    845 845
         p1 <- ptr $ BCOPtrBreakArray info_mod
    
    846
    -    let -- cast that checks that round-tripping through Word16 doesn't change the value
    
    847
    -        toW16 x = let r = fromIntegral x :: Word16
    
    848
    -                  in if fromIntegral r == x
    
    846
    +    let -- cast that checks that round-tripping through Word32 doesn't change the value
    
    847
    +        infoW32 = let r = fromIntegral infox :: Word32
    
    848
    +                   in if fromIntegral r == infox
    
    849 849
                         then r
    
    850
    -                    else pprPanic "schemeER_wrk: breakpoint tick/info index too large!" (ppr x)
    
    850
    +                    else pprPanic "schemeER_wrk: breakpoint tick/info index too large!" (ppr infox)
    
    851
    +        ix_hi = fromIntegral (infoW32 `shiftR` 16)
    
    852
    +        ix_lo = fromIntegral (infoW32 .&. 0xffff)
    
    851 853
         info_addr        <- lit1 $ BCONPtrFS $ moduleNameFS $ moduleName info_mod
    
    852 854
         info_unitid_addr <- lit1 $ BCONPtrFS $ unitIdFS     $ moduleUnitId info_mod
    
    853 855
         np               <- lit1 $ BCONPtrCostCentre ibi
    
    854 856
         emit_ bci_BRK_FUN [ Op p1, Op info_addr, Op info_unitid_addr
    
    855
    -                      , SmallOp (toW16 infox), Op np ]
    
    857
    +                      , SmallOp ix_hi, SmallOp ix_lo, Op np ]
    
    856 858
     
    
    857 859
       BRK_ALTS active -> emit_ bci_BRK_ALTS [SmallOp (if active then 1 else 0)]
    
    858 860
     
    

  • compiler/GHC/Iface/Ext/Binary.hs
    ... ... @@ -17,7 +17,6 @@ where
    17 17
     
    
    18 18
     import GHC.Prelude
    
    19 19
     
    
    20
    -import GHC.Builtin.Utils
    
    21 20
     import GHC.Settings.Utils         ( maybeRead )
    
    22 21
     import GHC.Settings.Config        ( cProjectVersion )
    
    23 22
     import GHC.Utils.Binary
    
    ... ... @@ -28,10 +27,8 @@ import GHC.Iface.Binary ( putAllTables )
    28 27
     import GHC.Types.Name
    
    29 28
     import GHC.Types.Name.Cache
    
    30 29
     import GHC.Types.SrcLoc as SrcLoc
    
    31
    -import GHC.Types.Unique
    
    32 30
     import GHC.Types.Unique.FM
    
    33 31
     import qualified GHC.Utils.Binary as Binary
    
    34
    -import GHC.Utils.Outputable
    
    35 32
     import GHC.Utils.Panic
    
    36 33
     
    
    37 34
     import qualified Data.Array        as A
    
    ... ... @@ -290,6 +287,9 @@ fromHieName nc hie_name = do
    290 287
       case hie_name of
    
    291 288
         ExternalName mod occ span -> updateNameCache nc mod occ $ \cache -> do
    
    292 289
           case lookupOrigNameCache cache mod occ of
    
    290
    +        -- Note that this may be a wired-in name (provided that the NameCache
    
    291
    +        -- was initialized with known-key names, which is always the case if you
    
    292
    +        -- use `newNameCache`).
    
    293 293
             Just name -> pure (cache, name)
    
    294 294
             Nothing   -> do
    
    295 295
               uniq <- takeUniqFromNameCache nc
    
    ... ... @@ -302,11 +302,6 @@ fromHieName nc hie_name = do
    302 302
           -- don't update the NameCache for local names
    
    303 303
           pure $ mkInternalName uniq occ span
    
    304 304
     
    
    305
    -    KnownKeyName u -> case lookupKnownKeyName u of
    
    306
    -      Nothing -> pprPanic "fromHieName:unknown known-key unique"
    
    307
    -                          (ppr u)
    
    308
    -      Just n -> pure n
    
    309
    -
    
    310 305
     -- ** Reading and writing `HieName`'s
    
    311 306
     
    
    312 307
     putHieName :: WriteBinHandle -> HieName -> IO ()
    
    ... ... @@ -316,9 +311,6 @@ putHieName bh (ExternalName mod occ span) = do
    316 311
     putHieName bh (LocalName occName span) = do
    
    317 312
       putByte bh 1
    
    318 313
       put_ bh (occName, BinSrcSpan span)
    
    319
    -putHieName bh (KnownKeyName uniq) = do
    
    320
    -  putByte bh 2
    
    321
    -  put_ bh $ unpkUnique uniq
    
    322 314
     
    
    323 315
     getHieName :: ReadBinHandle -> IO HieName
    
    324 316
     getHieName bh = do
    
    ... ... @@ -330,7 +322,4 @@ getHieName bh = do
    330 322
         1 -> do
    
    331 323
           (occ, span) <- get bh
    
    332 324
           return $ LocalName occ $ unBinSrcSpan span
    
    333
    -    2 -> do
    
    334
    -      (c,i) <- get bh
    
    335
    -      return $ KnownKeyName $ mkUnique c i
    
    336 325
         _ -> panic "GHC.Iface.Ext.Binary.getHieName: invalid tag"

  • compiler/GHC/Iface/Ext/Types.hs
    ... ... @@ -19,14 +19,12 @@ import GHC.Prelude
    19 19
     import GHC.Settings.Config
    
    20 20
     import GHC.Utils.Binary
    
    21 21
     import GHC.Data.FastString
    
    22
    -import GHC.Builtin.Utils
    
    23 22
     import GHC.Iface.Type
    
    24 23
     import GHC.Unit.Module            ( ModuleName, Module )
    
    25 24
     import GHC.Types.Name
    
    26 25
     import GHC.Utils.Outputable hiding ( (<>) )
    
    27 26
     import GHC.Types.SrcLoc
    
    28 27
     import GHC.Types.Avail
    
    29
    -import GHC.Types.Unique
    
    30 28
     import qualified GHC.Utils.Outputable as O ( (<>) )
    
    31 29
     import GHC.Utils.Panic
    
    32 30
     import GHC.Core.ConLike           ( ConLike(..) )
    
    ... ... @@ -766,7 +764,6 @@ instance Binary TyVarScope where
    766 764
     data HieName
    
    767 765
       = ExternalName !Module !OccName !SrcSpan
    
    768 766
       | LocalName !OccName !SrcSpan
    
    769
    -  | KnownKeyName !Unique
    
    770 767
       deriving (Eq)
    
    771 768
     
    
    772 769
     instance Ord HieName where
    
    ... ... @@ -774,34 +771,28 @@ instance Ord HieName where
    774 771
         -- TODO (int-index): Perhaps use RealSrcSpan in HieName?
    
    775 772
       compare (LocalName a b) (LocalName c d) = compare a c S.<> leftmost_smallest b d
    
    776 773
         -- TODO (int-index): Perhaps use RealSrcSpan in HieName?
    
    777
    -  compare (KnownKeyName a) (KnownKeyName b) = nonDetCmpUnique a b
    
    778
    -    -- Not actually non deterministic as it is a KnownKey
    
    779 774
       compare ExternalName{} _ = LT
    
    780 775
       compare LocalName{} ExternalName{} = GT
    
    781
    -  compare LocalName{} _ = LT
    
    782
    -  compare KnownKeyName{} _ = GT
    
    783 776
     
    
    784 777
     instance Outputable HieName where
    
    785 778
       ppr (ExternalName m n sp) = text "ExternalName" <+> ppr m <+> ppr n <+> ppr sp
    
    786 779
       ppr (LocalName n sp) = text "LocalName" <+> ppr n <+> ppr sp
    
    787
    -  ppr (KnownKeyName u) = text "KnownKeyName" <+> ppr u
    
    788 780
     
    
    789 781
     hieNameOcc :: HieName -> OccName
    
    790 782
     hieNameOcc (ExternalName _ occ _) = occ
    
    791 783
     hieNameOcc (LocalName occ _) = occ
    
    792
    -hieNameOcc (KnownKeyName u) =
    
    793
    -  case lookupKnownKeyName u of
    
    794
    -    Just n -> nameOccName n
    
    795
    -    Nothing -> pprPanic "hieNameOcc:unknown known-key unique"
    
    796
    -                        (ppr u)
    
    797 784
     
    
    798 785
     toHieName :: Name -> HieName
    
    799
    -toHieName name
    
    800
    -  | isKnownKeyName name = KnownKeyName (nameUnique name)
    
    801
    -  | isExternalName name = ExternalName (nameModule name)
    
    802
    -                                       (nameOccName name)
    
    803
    -                                       (removeBufSpan $ nameSrcSpan name)
    
    804
    -  | otherwise = LocalName (nameOccName name) (removeBufSpan $ nameSrcSpan name)
    
    786
    +toHieName name =
    
    787
    +  case nameModule_maybe name of
    
    788
    +    Nothing -> LocalName occName span
    
    789
    +    Just m -> ExternalName m occName span
    
    790
    +  where
    
    791
    +    occName :: OccName
    
    792
    +    occName = nameOccName name
    
    793
    +
    
    794
    +    span :: SrcSpan
    
    795
    +    span = removeBufSpan $ nameSrcSpan name
    
    805 796
     
    
    806 797
     
    
    807 798
     {- Note [Capture Entity Information]
    

  • compiler/GHC/Iface/Tidy/StaticPtrTable.hs
    ... ... @@ -17,18 +17,18 @@
    17 17
     -- > static void hs_hpc_init_Main(void) {
    
    18 18
     -- >
    
    19 19
     -- >   static StgWord64 k0[2] = {16252233372134256ULL,7370534374096082ULL};
    
    20
    --- >   extern StgPtr Main_r2wb_closure;
    
    20
    +-- >   extern StgClosure Main_r2wb_closure;
    
    21 21
     -- >   hs_spt_insert(k0, &Main_r2wb_closure);
    
    22 22
     -- >
    
    23 23
     -- >   static StgWord64 k1[2] = {12545634534567898ULL,5409674567544151ULL};
    
    24
    --- >   extern StgPtr Main_r2wc_closure;
    
    24
    +-- >   extern StgClosure Main_r2wc_closure;
    
    25 25
     -- >   hs_spt_insert(k1, &Main_r2wc_closure);
    
    26 26
     -- >
    
    27 27
     -- > }
    
    28 28
     --
    
    29 29
     -- where the constants are fingerprints produced from the static forms.
    
    30 30
     --
    
    31
    --- The linker must find the definitions matching the @extern StgPtr <name>@
    
    31
    +-- The linker must find the definitions matching the @extern StgClosure <name>@
    
    32 32
     -- declarations. For this to work, the identifiers of static pointers need to be
    
    33 33
     -- exported. This is done in 'GHC.Core.Opt.SetLevels.newLvlVar'.
    
    34 34
     --
    
    ... ... @@ -263,7 +263,7 @@ sptModuleInitCode platform this_mod entries
    263 263
             -- CLabel. Regardless, MayHaveCafRefs/NoCafRefs wouldn't make
    
    264 264
             -- any difference here, they would pretty-print to the same
    
    265 265
             -- foreign stub content.
    
    266
    -        $$ text "extern StgPtr "
    
    266
    +        $$ text "extern StgClosure "
    
    267 267
                <> (pprCLabel platform $ mkClosureLabel n MayHaveCafRefs) <> semi
    
    268 268
             $$ text "hs_spt_insert" <> parens
    
    269 269
                  (hcat $ punctuate comma
    

  • compiler/GHC/Types/Name/Cache.hs
    ... ... @@ -101,9 +101,14 @@ OrigNameCache at all? Good question; after all,
    101 101
       3) Loading of interface files encodes names via Uniques, as detailed in
    
    102 102
          Note [Symbol table representation of names] in GHC.Iface.Binary
    
    103 103
     
    
    104
    -It turns out that we end up looking up built-in syntax in the cache when we
    
    105
    -generate Haddock documentation. E.g. if we don't find tuple data constructors
    
    106
    -there, hyperlinks won't work as expected. Test case: haddockHtmlTest (Bug923.hs)
    
    104
    +
    
    105
    +However note that:
    
    106
    +  1) It turns out that we end up looking up built-in syntax in the cache when
    
    107
    +     we generate Haddock documentation. E.g. if we don't find tuple data
    
    108
    +     constructors there, hyperlinks won't work as expected. Test case:
    
    109
    +     haddockHtmlTest (Bug923.hs)
    
    110
    +  2) HIE de-serialization relies on wired-in names, including built-in syntax,
    
    111
    +     being present in the OrigNameCache.
    
    107 112
     -}
    
    108 113
     
    
    109 114
     -- | The NameCache makes sure that there is just one Unique assigned for
    

  • libraries/base/changelog.md
    1 1
     # Changelog for [`base` package](http://hackage.haskell.org/package/base)
    
    2 2
     
    
    3 3
     ## 4.23.0.0 *TBA*
    
    4
    +  * Remove deprecated, unstable heap representation details from `GHC.Exts` ([CLC proposal #212](https://github.com/haskell/core-libraries-committee/issues/212))
    
    4 5
       * Add `Data.List.NonEmpty.mapMaybe`. ([CLC proposal #337](https://github.com/haskell/core-libraries-committee/issues/337))
    
    5 6
       * Fix issues with toRational for types capable to represent infinite and not-a-number values ([CLC proposal #338](https://github.com/haskell/core-libraries-committee/issues/338))
    
    6 7
       * Modify the implementation of `Data.List.sortOn` to use `(>)` instead of `compare`. ([CLC proposal #332](https://github.com/haskell/core-libraries-committee/issues/332))
    

  • libraries/base/src/GHC/Exts.hs
    ... ... @@ -26,12 +26,6 @@ module GHC.Exts
    26 26
          -- **  Legacy interface for arrays of arrays
    
    27 27
          module GHC.Internal.ArrayArray,
    
    28 28
          -- *  Primitive operations
    
    29
    -     {-# DEPRECATED ["The BCO, mkApUpd0#, and newBCO# re-exports from GHC.Exts have been deprecated and will be removed in 9.14", "These symbols should be imported from ghc-internal instead if needed."] #-}
    
    30
    -     Prim.BCO,
    
    31
    -     {-# DEPRECATED ["The BCO, mkApUpd0#, and newBCO# re-exports from GHC.Exts have been deprecated and will be removed in 9.14", "These symbols should be imported from ghc-internal instead if needed."] #-}
    
    32
    -     Prim.mkApUpd0#,
    
    33
    -     {-# DEPRECATED ["The BCO, mkApUpd0#, and newBCO# re-exports from GHC.Exts have been deprecated and will be removed in 9.14", "These symbols should be imported from ghc-internal instead if needed."] #-}
    
    34
    -     Prim.newBCO#,
    
    35 29
          module GHC.Prim,
    
    36 30
          module GHC.Prim.Ext,
    
    37 31
          -- **  Running 'RealWorld' state thread
    
    ... ... @@ -130,9 +124,6 @@ import GHC.Prim hiding
    130 124
       , whereFrom#
    
    131 125
       , isByteArrayWeaklyPinned#, isMutableByteArrayWeaklyPinned#
    
    132 126
     
    
    133
    -  -- deprecated
    
    134
    -  , BCO, mkApUpd0#, newBCO#
    
    135
    -
    
    136 127
       -- Don't re-export vector FMA instructions
    
    137 128
       , fmaddFloatX4#
    
    138 129
       , fmsubFloatX4#
    
    ... ... @@ -255,8 +246,6 @@ import GHC.Prim hiding
    255 246
       , minWord8X32#
    
    256 247
       , minWord8X64#
    
    257 248
       )
    
    258
    -import qualified GHC.Prim as Prim
    
    259
    -  ( BCO, mkApUpd0#, newBCO# )
    
    260 249
     
    
    261 250
     import GHC.Prim.Ext
    
    262 251
     
    

  • libraries/ghci/GHCi/CreateBCO.hs
    ... ... @@ -6,10 +6,6 @@
    6 6
     {-# LANGUAGE UnboxedTuples #-}
    
    7 7
     {-# LANGUAGE RecordWildCards #-}
    
    8 8
     {-# LANGUAGE CPP #-}
    
    9
    -{-# OPTIONS_GHC -Wno-warnings-deprecations #-}
    
    10
    --- TODO We want to import GHC.Internal.Base (BCO, mkApUpd0#, newBCO#) instead
    
    11
    --- of from GHC.Exts when we can require of the bootstrap compiler to have
    
    12
    --- ghc-internal.
    
    13 9
     
    
    14 10
     --
    
    15 11
     --  (c) The University of Glasgow 2002-2006
    
    ... ... @@ -30,7 +26,8 @@ import Data.Array.Base
    30 26
     import Foreign hiding (newArray)
    
    31 27
     import Unsafe.Coerce (unsafeCoerce)
    
    32 28
     import GHC.Arr          ( Array(..) )
    
    33
    -import GHC.Exts
    
    29
    +import GHC.Exts   hiding ( BCO, mkApUpd0#, newBCO# )
    
    30
    +import GHC.Internal.Base ( BCO, mkApUpd0#, newBCO# )
    
    34 31
     import GHC.IO
    
    35 32
     import Control.Exception ( ErrorCall(..) )
    
    36 33
     
    

  • libraries/ghci/GHCi/TH.hs
    1 1
     {-# LANGUAGE ScopedTypeVariables, StandaloneDeriving, DeriveGeneric,
    
    2 2
         TupleSections, RecordWildCards, InstanceSigs, CPP #-}
    
    3 3
     {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
    
    4
    -{-# OPTIONS_GHC -Wno-warnings-deprecations #-}
    
    5
    --- TODO We want to import GHC.Internal.Desugar instead of GHC.Desugar when we
    
    6
    --- can require of the bootstrap compiler to have ghc-internal.
    
    7 4
     
    
    8 5
     -- |
    
    9 6
     -- Running TH splices
    
    ... ... @@ -112,7 +109,7 @@ import Data.IORef
    112 109
     import Data.Map (Map)
    
    113 110
     import qualified Data.Map as M
    
    114 111
     import Data.Maybe
    
    115
    -import GHC.Desugar (AnnotationWrapper(..))
    
    112
    +import GHC.Internal.Desugar (AnnotationWrapper(..))
    
    116 113
     import qualified GHC.Boot.TH.Syntax as TH
    
    117 114
     import Unsafe.Coerce
    
    118 115
     
    

  • libraries/ghci/ghci.cabal.in
    ... ... @@ -86,11 +86,7 @@ library
    86 86
             rts,
    
    87 87
             array            == 0.5.*,
    
    88 88
             base             >= 4.8 && < 4.23,
    
    89
    -        -- ghc-internal     == @ProjectVersionForLib@.*
    
    90
    -        -- TODO: Use GHC.Internal.Desugar and GHC.Internal.Base from
    
    91
    -        -- ghc-internal instead of ignoring the deprecation warning in GHCi.TH
    
    92
    -        -- and GHCi.CreateBCO when we require ghc-internal of the bootstrap
    
    93
    -        -- compiler
    
    89
    +        ghc-internal     >= 9.1001.0 && <=@ProjectVersionForLib@.0,
    
    94 90
             ghc-prim         >= 0.5.0 && < 0.14,
    
    95 91
             binary           == 0.8.*,
    
    96 92
             bytestring       >= 0.10 && < 0.13,
    

  • rts/Disassembler.c
    ... ... @@ -89,7 +89,7 @@ disInstr ( StgBCO *bco, int pc )
    89 89
              p1           = BCO_GET_LARGE_ARG;
    
    90 90
              info_mod     = BCO_GET_LARGE_ARG;
    
    91 91
              info_unit_id = BCO_GET_LARGE_ARG;
    
    92
    -         info_wix     = BCO_NEXT;
    
    92
    +         info_wix     = BCO_READ_NEXT_32;
    
    93 93
              np           = BCO_GET_LARGE_ARG;
    
    94 94
              debugBelch ("BRK_FUN " );  printPtr( ptrs[p1] );
    
    95 95
              debugBelch("%" FMT_Word, literals[info_mod] );
    

  • rts/Interpreter.c
    ... ... @@ -720,7 +720,7 @@ interpretBCO (Capability* cap)
    720 720
                 arg1_brk_array      = BCO_GET_LARGE_ARG;
    
    721 721
                 /* info_mod_name = */ BCO_GET_LARGE_ARG;
    
    722 722
                 /* info_mod_id   = */ BCO_GET_LARGE_ARG;
    
    723
    -            arg4_info_index     = BCO_NEXT;
    
    723
    +            arg4_info_index     = BCO_READ_NEXT_32;
    
    724 724
     
    
    725 725
                 StgPtr* ptrs = (StgPtr*)(&bco->ptrs->payload[0]);
    
    726 726
                 StgArrBytes* breakPoints = (StgArrBytes *) BCO_PTR(arg1_brk_array);
    
    ... ... @@ -1542,7 +1542,7 @@ run_BCO:
    1542 1542
                 arg1_brk_array      = BCO_GET_LARGE_ARG;
    
    1543 1543
                 arg2_info_mod_name  = BCO_GET_LARGE_ARG;
    
    1544 1544
                 arg3_info_mod_id    = BCO_GET_LARGE_ARG;
    
    1545
    -            arg4_info_index     = BCO_NEXT;
    
    1545
    +            arg4_info_index     = BCO_READ_NEXT_32;
    
    1546 1546
     #if defined(PROFILING)
    
    1547 1547
                 arg5_cc             = BCO_GET_LARGE_ARG;
    
    1548 1548
     #else
    

  • testsuite/tests/module/T21752.stderr deleted
    1
    -T21752A.hs:4:5: warning: [GHC-68441] [-Wdeprecations (in -Wextended-warnings)]
    
    2
    -    In the use of ‘newBCO#’ (imported from GHC.Exts):
    
    3
    -    Deprecated: "The BCO, mkApUpd0#, and newBCO# re-exports from GHC.Exts have been deprecated and will be removed in 9.14
    
    4
    -                 These symbols should be imported from ghc-internal instead if needed."
    
    5
    -
    
    6
    -T21752A.hs:4:5: warning: [GHC-68441] [-Wdeprecations (in -Wextended-warnings)]
    
    7
    -    In the use of ‘newBCO#’ (imported from GHC.Exts):
    
    8
    -    Deprecated: "The BCO, mkApUpd0#, and newBCO# re-exports from GHC.Exts have been deprecated and will be removed in 9.14
    
    9
    -                 These symbols should be imported from ghc-internal instead if needed."
    
    10
    -
    
    11
    -T21752A.hs:4:5: warning: [GHC-68441] [-Wdeprecations (in -Wextended-warnings)]
    
    12
    -    In the use of ‘mkApUpd0#’ (imported from GHC.Exts):
    
    13
    -    Deprecated: "The BCO, mkApUpd0#, and newBCO# re-exports from GHC.Exts have been deprecated and will be removed in 9.14
    
    14
    -                 These symbols should be imported from ghc-internal instead if needed."
    
    15
    -
    
    16
    -T21752A.hs:4:5: warning: [GHC-68441] [-Wdeprecations (in -Wextended-warnings)]
    
    17
    -    In the use of ‘mkApUpd0#’ (imported from GHC.Exts):
    
    18
    -    Deprecated: "The BCO, mkApUpd0#, and newBCO# re-exports from GHC.Exts have been deprecated and will be removed in 9.14
    
    19
    -                 These symbols should be imported from ghc-internal instead if needed."
    
    20
    -
    
    21
    -T21752A.hs:4:5: warning: [GHC-68441] [-Wdeprecations (in -Wextended-warnings)]
    
    22
    -    In the use of type constructor or class ‘BCO’
    
    23
    -    (imported from GHC.Exts):
    
    24
    -    Deprecated: "The BCO, mkApUpd0#, and newBCO# re-exports from GHC.Exts have been deprecated and will be removed in 9.14
    
    25
    -                 These symbols should be imported from ghc-internal instead if needed."
    
    26
    -
    
    27
    -T21752A.hs:4:5: warning: [GHC-68441] [-Wdeprecations (in -Wextended-warnings)]
    
    28
    -    In the use of type constructor or class ‘BCO’
    
    29
    -    (imported from GHC.Exts):
    
    30
    -    Deprecated: "The BCO, mkApUpd0#, and newBCO# re-exports from GHC.Exts have been deprecated and will be removed in 9.14
    
    31
    -                 These symbols should be imported from ghc-internal instead if needed."
    
    32
    -

  • utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs
    ... ... @@ -229,10 +229,7 @@ writeInterfaceFile filename iface = do
    229 229
       return ()
    
    230 230
     
    
    231 231
     freshNameCache :: IO NameCache
    
    232
    -freshNameCache =
    
    233
    -  initNameCache
    
    234
    -    'a' -- ??
    
    235
    -    []
    
    232
    +freshNameCache = newNameCache
    
    236 233
     
    
    237 234
     -- | Read a Haddock (@.haddock@) interface file. Return either an
    
    238 235
     -- 'InterfaceFile' or an error message.