[Git][ghc/ghc][wip/torsten.schmits/fix-linters-file-collection] 7 commits: ghc-internal: strict, unboxed src loc ranges

Torsten Schmits (@torsten.schmits) gitlab at gitlab.haskell.org
Mon Nov 4 14:08:40 UTC 2024



Torsten Schmits pushed to branch wip/torsten.schmits/fix-linters-file-collection at Glasgow Haskell Compiler / GHC


Commits:
ea458779 by doyougnu at 2024-11-01T18:11:33-04:00
ghc-internal: strict, unboxed src loc ranges

- closes: #20449
- See CLC proposal: #55

- - - - -
778ac793 by Kazuki Okamoto at 2024-11-01T18:12:13-04:00
No haddock markup in doctest line

- - - - -
cf0deeaf by Andreas Klebinger at 2024-11-02T17:54:52-04:00
Reword -fexpose-overloaded-unfoldings docs.

This should make them slightly clearer. Fixes #24844

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>

- - - - -
1c21e7d4 by Andreas Klebinger at 2024-11-02T17:55:29-04:00
Compile T25062 simd tests even if we can't run them.

Helps avoid them being utterly broken.

Fixes #25341

- - - - -
573cad4b by Cheng Shao at 2024-11-02T17:56:04-04:00
Remove unused USE_REPORT_PRELUDE code paths from the tree

This patch removes unused `USE_REPORT_PRELUDE` code paths from the
tree. They have been present since the first git revision
4fb94ae5e5d632748fa2e6c35e259eccc5a1a3f4, and might have been useful
for debugging purposes many years ago, but these code paths are never
actually built. Removing these ease maintenance of relevant modules in
the future, and also allows us to get rid of `CPP` extension in those
modules as a nice byproduct.

- - - - -
b51377f2 by Torsten Schmits at 2024-11-04T15:08:20+01:00
fix test lint that accumulated while the checks were broken

I didn't fix the issues flagged by the #ifdef linter because it were so
many that it seemed like the rule has become obsolete.

- - - - -
1b080095 by Torsten Schmits at 2024-11-04T15:08:20+01:00
test driver: fix file collection for regex linters

When a testsuite linter is executed with the `tracked` strategy, the
driver runs `git ls-tree` to collect eligible files.

This appears to have ceased producing any paths – `ls-tree` restricts
its results to the current working directory, which is
`testsuite/tests/linters` in this case.

As a quick fix, this patch changes the working directory to match
expectations.

- - - - -


23 changed files:

- compiler/GHC/Core/Make.hs
- compiler/GHC/Tc/Types/EvTerm.hs
- docs/users_guide/using-optimisation.rst
- libraries/ghc-internal/src/GHC/Internal/Data/OldList.hs
- libraries/ghc-internal/src/GHC/Internal/List.hs
- libraries/ghc-internal/src/GHC/Internal/Stack/Types.hs
- rts/IOManager.c
- rts/Updates.h
- testsuite/tests/bytecode/T24634/Makefile
- testsuite/tests/bytecode/T25090/Makefile
- testsuite/tests/driver/Makefile
- testsuite/tests/driver/boot-target/Makefile
- testsuite/tests/driver/fat-iface/Makefile
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32
- testsuite/tests/linters/Makefile
- testsuite/tests/linters/regex-linters/check-cpp.py
- testsuite/tests/linters/regex-linters/linter.py
- testsuite/tests/perf/compiler/Makefile
- testsuite/tests/simd/should_run/T25062_V64.hs
- testsuite/tests/simd/should_run/all.T


Changes:

=====================================
compiler/GHC/Core/Make.hs
=====================================
@@ -4,7 +4,7 @@
 module GHC.Core.Make (
         -- * Constructing normal syntax
         mkCoreLet, mkCoreLets,
-        mkCoreApp, mkCoreApps, mkCoreConApps,
+        mkCoreApp, mkCoreApps, mkCoreConApps, mkCoreConWrapApps,
         mkCoreLams, mkWildCase, mkIfThenElse,
         mkWildValBinder,
         mkSingleAltCase,
@@ -70,7 +70,7 @@ import GHC.Core.Type
 import GHC.Core.Predicate    ( isCoVarType )
 import GHC.Core.TyCo.Compare ( eqType )
 import GHC.Core.Coercion     ( isCoVar )
-import GHC.Core.DataCon      ( DataCon, dataConWorkId )
+import GHC.Core.DataCon      ( DataCon, dataConWorkId, dataConWrapId )
 import GHC.Core.Multiplicity
 
 import GHC.Builtin.Types
@@ -133,6 +133,13 @@ mkCoreLets binds body = foldr mkCoreLet body binds
 mkCoreConApps :: DataCon -> [CoreExpr] -> CoreExpr
 mkCoreConApps con args = mkCoreApps (Var (dataConWorkId con)) args
 
+-- | A variant of 'mkCoreConApps' constructs an expression which represents the
+-- application of a number of expressions to that of a data constructor
+-- expression using the wrapper, not the worker, of the data constructor. The
+-- leftmost expression in the list is applied first
+mkCoreConWrapApps :: DataCon -> [CoreExpr] -> CoreExpr
+mkCoreConWrapApps con args = mkCoreApps (Var (dataConWrapId con)) args
+
 -- | Construct an expression which represents the application of a number of
 -- expressions to another. The leftmost expression in the list is applied first
 mkCoreApps :: CoreExpr -- ^ function


=====================================
compiler/GHC/Tc/Types/EvTerm.hs
=====================================
@@ -45,7 +45,7 @@ evCallStack (EvCsPushCall fs loc tm) = do
   let platform = targetPlatform df
   m             <- getModule
   srcLocDataCon <- lookupDataCon srcLocDataConName
-  let mkSrcLoc l = mkCoreConApps srcLocDataCon <$>
+  let mkSrcLoc l = mkCoreConWrapApps srcLocDataCon <$>
                sequence [ mkStringExprFS (unitFS $ moduleUnit m)
                         , mkStringExprFS (moduleNameFS $ moduleName m)
                         , mkStringExprFS (srcSpanFile l)


=====================================
docs/users_guide/using-optimisation.rst
=====================================
@@ -531,7 +531,8 @@ as such you shouldn't need to set any of them explicitly. A flag
     * Use of the magic `inline` function to force inlining.
 
 .. ghc-flag:: -fexpose-overloaded-unfoldings
-    :shortdesc: Expose unfoldings carrying constraints, even for very large or recursive functions.
+    :shortdesc: Expose function unfoldings whose type contains constraints,
+        even for very large or recursive functions.
     :type: dynamic
     :reverse: -fno-expose-overloaded-unfoldings
     :category:
@@ -541,19 +542,24 @@ as such you shouldn't need to set any of them explicitly. A flag
     This experimental flag is a slightly less heavy weight alternative
     to :ghc-flag:`-fexpose-all-unfoldings`.
 
-    Instead of exposing all functions it only aims at exposing constrained functions.
+    Instead of exposing all functions it exposes only those functions which
+    contain constraints within their type.
     This is intended to be used for cases where specialization is considered
     crucial but :ghc-flag:`-fexpose-all-unfoldings` imposes too much compile
     time cost.
 
-    Currently this won't expose unfoldings where a type class is hidden under a
-    newtype. That is for cases like: ::
+    This doesn't guarantee *all* functions which might benefit from specialization
+    will be exposed, for example currently this won't expose unfoldings where a
+    type class is hidden under a newtype.
+
+    That is for cases like: ::
 
         newtype NT a = NT (Integral a => a)
 
         foo :: NT a -> T1 -> TR
 
-    GHC won't recognise `foo` as specialisable and won't expose the unfolding
+    GHC won't look under `NT` for constraints and therefore `foo` won't be
+    recognized as specialisable and this flag won't expose the unfolding
     even with :ghc-flag:`-fexpose-overloaded-unfoldings` enabled.
 
     All the other caveats about :ghc-flag:`-fexpose-overloaded-unfoldings`


=====================================
libraries/ghc-internal/src/GHC/Internal/Data/OldList.hs
=====================================
@@ -1,5 +1,5 @@
 {-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP, NoImplicitPrelude, ScopedTypeVariables,
+{-# LANGUAGE NoImplicitPrelude, ScopedTypeVariables,
              MagicHash, BangPatterns #-}
 
 -----------------------------------------------------------------------------
@@ -370,9 +370,6 @@ findIndex p     = listToMaybe . findIndices p
 -- >>> findIndices (\l -> length l > 3) ["a", "bcde", "fgh", "ijklmnop"]
 -- [1,3]
 findIndices      :: (a -> Bool) -> [a] -> [Int]
-#if defined(USE_REPORT_PRELUDE)
-findIndices p xs = [ i | (x,i) <- zip xs [0..], p x]
-#else
 -- Efficient definition, adapted from Data.Sequence
 -- (Note that making this INLINABLE instead of INLINE allows
 -- 'findIndex' to fuse, fixing #15426.)
@@ -381,7 +378,6 @@ findIndices p ls = build $ \c n ->
   let go x r k | p x       = I# k `c` r (k +# 1#)
                | otherwise = r (k +# 1#)
   in foldr go (\_ -> n) ls 0#
-#endif  /* USE_REPORT_PRELUDE */
 
 -- | \(\mathcal{O}(\min(m,n))\). The 'isPrefixOf' function takes two lists and
 -- returns 'True' iff the first list is a prefix of the second.
@@ -540,10 +536,6 @@ nub                     =  nubBy (==)
 -- >>> nubBy (>) [1, 2, 3, 2, 1, 5, 4, 5, 3, 2]
 -- [1,2,3,5,5]
 nubBy                   :: (a -> a -> Bool) -> [a] -> [a]
-#if defined(USE_REPORT_PRELUDE)
-nubBy eq []             =  []
-nubBy eq (x:xs)         =  x : nubBy eq (filter (\ y -> not (eq x y)) xs)
-#else
 -- stolen from HBC
 nubBy eq l              = nubBy' l []
   where
@@ -562,7 +554,6 @@ nubBy eq l              = nubBy' l []
 elem_by :: (a -> a -> Bool) -> a -> [a] -> Bool
 elem_by _  _ []         =  False
 elem_by eq y (x:xs)     =  x `eq` y || elem_by eq y xs
-#endif
 
 
 -- | \(\mathcal{O}(n)\). 'delete' @x@ removes the first occurrence of @x@ from
@@ -1627,10 +1618,6 @@ sort :: (Ord a) => [a] -> [a]
 -- [(1,"Hello"),(2,"world"),(4,"!")]
 sortBy :: (a -> a -> Ordering) -> [a] -> [a]
 
-#if defined(USE_REPORT_PRELUDE)
-sort = sortBy compare
-sortBy cmp = foldr (insertBy cmp) []
-#else
 
 {-
 GHC's mergesort replaced by a better implementation, 24/12/2009.
@@ -1840,8 +1827,6 @@ rqpart cmp x (y:ys) rle rgt r =
         _  -> rqpart cmp x ys (y:rle) rgt r
 -}
 
-#endif /* USE_REPORT_PRELUDE */
-
 -- | Sort a list by comparing the results of a key function applied to each
 -- element.  @'sortOn' f@ is equivalent to @'sortBy' ('comparing' f)@, but has the
 -- performance advantage of only evaluating @f@ once for each element in the
@@ -2027,14 +2012,10 @@ lines s                 =  cons (case break (== '\n') s of
 -- >>> unlines . lines $ "foo\nbar"
 -- "foo\nbar\n"
 unlines                 :: [String] -> String
-#if defined(USE_REPORT_PRELUDE)
-unlines                 =  concatMap (++ "\n")
-#else
 -- HBC version (stolen)
 -- here's a more efficient version
 unlines [] = []
 unlines (l:ls) = l ++ '\n' : unlines ls
-#endif
 
 -- | 'words' breaks a string up into a list of words, which were delimited
 -- by white space (as defined by 'isSpace'). This function trims any white spaces
@@ -2085,10 +2066,6 @@ wordsFB c n = go
 -- >>> unwords ["foo", "bar", "", "baz"]
 -- "foo bar  baz"
 unwords                 :: [String] -> String
-#if defined(USE_REPORT_PRELUDE)
-unwords []              =  ""
-unwords ws              =  foldr1 (\w s -> w ++ ' ':s) ws
-#else
 -- Here's a lazier version that can get the last element of a
 -- _|_-terminated list.
 {-# NOINLINE [1] unwords #-}
@@ -2118,7 +2095,6 @@ tailUnwords (_:xs)    = xs
 {-# INLINE [0] unwordsFB #-}
 unwordsFB               :: String -> String -> String
 unwordsFB w r           = ' ' : w ++ r
-#endif
 
 {- A "SnocBuilder" is a version of Chris Okasaki's banker's queue that supports
 toListSB instead of uncons. In single-threaded use, its performance


=====================================
libraries/ghc-internal/src/GHC/Internal/List.hs
=====================================
@@ -1,5 +1,5 @@
 {-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP, NoImplicitPrelude, ScopedTypeVariables #-}
+{-# LANGUAGE NoImplicitPrelude, ScopedTypeVariables #-}
 {-# LANGUAGE BangPatterns #-}
 {-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
 
@@ -208,11 +208,6 @@ tail []                 =  errorEmptyList "tail"
 -- >>> last []
 -- *** Exception: Prelude.last: empty list
 last                    :: HasCallStack => [a] -> a
-#if defined(USE_REPORT_PRELUDE)
-last [x]                =  x
-last (_:xs)             =  last xs
-last []                 =  errorEmptyList "last"
-#else
 -- Use foldl to make last a good consumer.
 -- This will compile to good code for the actual GHC.Internal.List.last.
 -- (At least as long it is eta-expanded, otherwise it does not, #10260.)
@@ -222,7 +217,6 @@ last xs = foldl (\_ x -> x) lastError xs
 -- foldl.
 lastError :: HasCallStack => a
 lastError = errorEmptyList "last"
-#endif
 
 -- | \(\mathcal{O}(n)\). Return all the elements of a list except the last one.
 -- The list must be non-empty.
@@ -240,17 +234,11 @@ lastError = errorEmptyList "last"
 -- >>> init []
 -- *** Exception: Prelude.init: empty list
 init                    :: HasCallStack => [a] -> [a]
-#if defined(USE_REPORT_PRELUDE)
-init [x]                =  []
-init (x:xs)             =  x : init xs
-init []                 =  errorEmptyList "init"
-#else
 -- eliminate repeated cases
 init []                 =  errorEmptyList "init"
 init (x:xs)             =  init' x xs
   where init' _ []     = []
         init' y (z:zs) = y : init' z zs
-#endif
 
 -- | \(\mathcal{O}(1)\). Test whether a list is empty.
 --
@@ -1091,11 +1079,6 @@ dropWhile p xs@(x:xs')
 -- >>> take 0 [1,2]
 -- []
 take                   :: Int -> [a] -> [a]
-#if defined(USE_REPORT_PRELUDE)
-take n _      | n <= 0 =  []
-take _ []              =  []
-take n (x:xs)          =  x : take (n-1) xs
-#else
 
 {- We always want to inline this to take advantage of a known length argument
 sign. Note, however, that it's important for the RULES to grab take, rather
@@ -1141,7 +1124,6 @@ takeFB c n x xs
   = \ m -> case m of
             1 -> x `c` n
             _ -> x `c` xs (m - 1)
-#endif
 
 -- | 'drop' @n xs@ returns the suffix of @xs@
 -- after the first @n@ elements, or @[]@ if @n >= 'length' xs at .
@@ -1169,11 +1151,6 @@ takeFB c n x xs
 -- >>> drop 0 [1,2]
 -- [1,2]
 drop                   :: Int -> [a] -> [a]
-#if defined(USE_REPORT_PRELUDE)
-drop n xs     | n <= 0 =  xs
-drop _ []              =  []
-drop n (_:xs)          =  drop (n-1) xs
-#else /* hack away */
 {-# INLINE drop #-}
 drop n ls
   | n <= 0     = ls
@@ -1185,7 +1162,6 @@ drop n ls
     unsafeDrop !_ []     = []
     unsafeDrop 1  (_:xs) = xs
     unsafeDrop m  (_:xs) = unsafeDrop (m - 1) xs
-#endif
 
 -- | 'splitAt' @n xs@ returns a tuple where first element is @xs@ prefix of
 -- length @n@ and second element is the remainder of the list:
@@ -1231,9 +1207,6 @@ drop n ls
 -- ([],[1,2,3])
 splitAt                :: Int -> [a] -> ([a],[a])
 
-#if defined(USE_REPORT_PRELUDE)
-splitAt n xs           =  (take n xs, drop n xs)
-#else
 splitAt n ls
   | n <= 0 = ([], ls)
   | otherwise          = splitAt' n ls
@@ -1244,7 +1217,6 @@ splitAt n ls
         splitAt' m  (x:xs) = (x:xs', xs'')
           where
             (xs', xs'') = splitAt' (m - 1) xs
-#endif /* USE_REPORT_PRELUDE */
 
 -- | 'span', applied to a predicate @p@ and a list @xs@, returns a tuple where
 -- first element is the longest prefix (possibly empty) of @xs@ of elements that
@@ -1322,15 +1294,11 @@ span p xs@(x:xs')
 -- >>> break (> 9) [1,2,3]
 -- ([1,2,3],[])
 break                   :: (a -> Bool) -> [a] -> ([a],[a])
-#if defined(USE_REPORT_PRELUDE)
-break p                 =  span (not . p)
-#else
 -- HBC version (stolen)
 break _ xs@[]           =  (xs, xs)
 break p xs@(x:xs')
            | p x        =  ([],xs)
            | otherwise  =  let (ys,zs) = break p xs' in (x:ys,zs)
-#endif
 
 -- | \(\mathcal{O}(n)\). 'reverse' @xs@ returns the elements of @xs@ in reverse order.
 -- @xs@ must be finite.
@@ -1359,14 +1327,10 @@ break p xs@(x:xs')
 -- >>> reverse [1..]
 -- * Hangs forever *
 reverse                 :: [a] -> [a]
-#if defined(USE_REPORT_PRELUDE)
-reverse                 =  foldl (flip (:)) []
-#else
 reverse l =  rev l []
   where
     rev []     a = a
     rev (x:xs) a = rev xs (x:a)
-#endif
 
 -- | 'and' returns the conjunction of a Boolean list. For the result to be
 -- 'True', the list must be finite; 'False', however, results from a 'False'
@@ -1392,9 +1356,6 @@ reverse l =  rev l []
 -- >>> and (repeat True)
 -- * Hangs forever *
 and                     :: [Bool] -> Bool
-#if defined(USE_REPORT_PRELUDE)
-and                     =  foldr (&&) True
-#else
 and []          =  True
 and (x:xs)      =  x && and xs
 {-# NOINLINE [1] and #-}
@@ -1403,7 +1364,6 @@ and (x:xs)      =  x && and xs
 "and/build"     forall (g::forall b.(Bool->b->b)->b->b) .
                 and (build g) = g (&&) True
  #-}
-#endif
 
 -- | 'or' returns the disjunction of a Boolean list. For the result to be
 -- 'False', the list must be finite; 'True', however, results from a 'True'
@@ -1429,9 +1389,6 @@ and (x:xs)      =  x && and xs
 -- >>> or (repeat False)
 -- * Hangs forever *
 or                      :: [Bool] -> Bool
-#if defined(USE_REPORT_PRELUDE)
-or                      =  foldr (||) False
-#else
 or []           =  False
 or (x:xs)       =  x || or xs
 {-# NOINLINE [1] or #-}
@@ -1440,7 +1397,6 @@ or (x:xs)       =  x || or xs
 "or/build"      forall (g::forall b.(Bool->b->b)->b->b) .
                 or (build g) = g (||) False
  #-}
-#endif
 
 -- | Applied to a predicate and a list, 'any' determines if any element
 -- of the list satisfies the predicate. For the result to be
@@ -1465,9 +1421,6 @@ or (x:xs)       =  x || or xs
 -- >>> any (> 3) [0, -1..]
 -- * Hangs forever *
 any                     :: (a -> Bool) -> [a] -> Bool
-#if defined(USE_REPORT_PRELUDE)
-any p                   =  or . map p
-#else
 any _ []        = False
 any p (x:xs)    = p x || any p xs
 
@@ -1477,7 +1430,6 @@ any p (x:xs)    = p x || any p xs
 "any/build"     forall p (g::forall b.(a->b->b)->b->b) .
                 any p (build g) = g ((||) . p) False
  #-}
-#endif
 
 -- | Applied to a predicate and a list, 'all' determines if all elements
 -- of the list satisfy the predicate. For the result to be
@@ -1502,9 +1454,6 @@ any p (x:xs)    = p x || any p xs
 -- >>> all (> 3) [4..]
 -- * Hangs forever *
 all                     :: (a -> Bool) -> [a] -> Bool
-#if defined(USE_REPORT_PRELUDE)
-all p                   =  and . map p
-#else
 all _ []        =  True
 all p (x:xs)    =  p x && all p xs
 
@@ -1514,7 +1463,6 @@ all p (x:xs)    =  p x && all p xs
 "all/build"     forall p (g::forall b.(a->b->b)->b->b) .
                 all p (build g) = g ((&&) . p) True
  #-}
-#endif
 
 -- | 'elem' is the list membership predicate, usually written in infix form,
 -- e.g., @x \`elem\` xs at .  For the result to be
@@ -1538,9 +1486,6 @@ all p (x:xs)    =  p x && all p xs
 -- >>> 3 `elem` [4..]
 -- * Hangs forever *
 elem                    :: (Eq a) => a -> [a] -> Bool
-#if defined(USE_REPORT_PRELUDE)
-elem x                  =  any (== x)
-#else
 elem _ []       = False
 elem x (y:ys)   = x==y || elem x ys
 {-# NOINLINE [1] elem #-}
@@ -1548,7 +1493,6 @@ elem x (y:ys)   = x==y || elem x ys
 "elem/build"    forall x (g :: forall b . (a -> b -> b) -> b -> b)
    . elem x (build g) = g (\ y r -> (x == y) || r) False
  #-}
-#endif
 
 -- | 'notElem' is the negation of 'elem'.
 --
@@ -1569,9 +1513,6 @@ elem x (y:ys)   = x==y || elem x ys
 -- >>> 3 `notElem` [4..]
 -- * Hangs forever *
 notElem                 :: (Eq a) => a -> [a] -> Bool
-#if defined(USE_REPORT_PRELUDE)
-notElem x               =  all (/= x)
-#else
 notElem _ []    =  True
 notElem x (y:ys)=  x /= y && notElem x ys
 {-# NOINLINE [1] notElem #-}
@@ -1579,7 +1520,6 @@ notElem x (y:ys)=  x /= y && notElem x ys
 "notElem/build" forall x (g :: forall b . (a -> b -> b) -> b -> b)
    . notElem x (build g) = g (\ y r -> (x /= y) && r) True
  #-}
-#endif
 
 -- | \(\mathcal{O}(n)\). 'lookup' @key assocs@ looks up a key in an association
 -- list.
@@ -1619,7 +1559,7 @@ lookup  key ((x,y):xys)
 -- >>> concatMap (\i -> [-i, i]) [1, 2, 3]
 -- [-1,1,-2,2,-3,3]
 --
--- >>> concatMap ('replicate' 3) [0, 2, 4]
+-- >>> concatMap (replicate 3) [0, 2, 4]
 -- [0,0,0,2,2,2,4,4,4]
 concatMap               :: (a -> [b]) -> [a] -> [b]
 concatMap f             =  foldr ((++) . f) []
@@ -1677,14 +1617,6 @@ concat = foldr (++) []
 --
 -- >>> ['a', 'b', 'c'] !! (-1)
 -- *** Exception: Prelude.!!: negative index
-#if defined(USE_REPORT_PRELUDE)
-(!!)                    :: [a] -> Int -> a
-xs     !! n | n < 0 =  errorWithoutStackTrace "Prelude.!!: negative index"
-[]     !! _         =  errorWithoutStackTrace "Prelude.!!: index too large"
-(x:_)  !! 0         =  x
-(_:xs) !! n         =  xs !! (n-1)
--- Prelude version is without HasCallStack to avoid building linear one
-#else
 (!!)                    :: HasCallStack => [a] -> Int -> a
 
 -- We don't really want the errors to inline with (!!).
@@ -1703,7 +1635,6 @@ xs !! n
   | otherwise = foldr (\x r k -> case k of
                                    0 -> x
                                    _ -> r (k-1)) tooLarge xs n
-#endif
 
 -- | List index (subscript) operator, starting from 0. Returns 'Nothing'
 -- if the index is out of bounds


=====================================
libraries/ghc-internal/src/GHC/Internal/Stack/Types.hs
=====================================
@@ -217,8 +217,8 @@ data SrcLoc = SrcLoc
   { srcLocPackage   :: [Char]
   , srcLocModule    :: [Char]
   , srcLocFile      :: [Char]
-  , srcLocStartLine :: Int
-  , srcLocStartCol  :: Int
-  , srcLocEndLine   :: Int
-  , srcLocEndCol    :: Int
+  , srcLocStartLine :: !Int
+  , srcLocStartCol  :: !Int
+  , srcLocEndLine   :: !Int
+  , srcLocEndCol    :: !Int
   } deriving Eq -- ^ @since base-4.9.0.0


=====================================
rts/IOManager.c
=====================================
@@ -364,7 +364,7 @@ void initIOManager(void)
              * TODO: rationalise this into one entry point, that internally
              * can do different things in the two cases.
              */
-#if defined (THREADED_RTS)
+#if defined(THREADED_RTS)
             /* Win32 implementation in win32/ThrIOManager.c
              */
             ioManagerStart();


=====================================
rts/Updates.h
=====================================
@@ -9,8 +9,8 @@
 #pragma once
 
 #if !defined(CMINUSMINUS)
-#include "BeginPrivate.h"
 #include "RtsFlags.h"
+#include "BeginPrivate.h"
 #endif
 
 


=====================================
testsuite/tests/bytecode/T24634/Makefile
=====================================
@@ -4,14 +4,14 @@ include $(TOP)/mk/test.mk
 
 # This case loads bytecode from the interface file written in the second invocation.
 T24634a:
-	$(TEST_HC) -c hello_c.c -o hello_c.o
-	$(TEST_HC) -c -fbyte-code-and-object-code -fno-omit-interface-pragmas Hello.hs
-	$(TEST_HC) -fprefer-byte-code -fbyte-code-and-object-code -fno-ignore-interface-pragmas hello_c.o Main.hs
+	'$(TEST_HC)' -c hello_c.c -o hello_c.o
+	'$(TEST_HC)' -c -fbyte-code-and-object-code -fno-omit-interface-pragmas Hello.hs
+	'$(TEST_HC)' -fprefer-byte-code -fbyte-code-and-object-code -fno-ignore-interface-pragmas hello_c.o Main.hs
 	./Main
 
 # This case uses the bytecode generated in 'runHscBackendPhase', not involving the interface, since 'Hello' is compiled
 # in the same invocation as 'Main'.
 T24634b:
-	$(TEST_HC) -c hello_c.c -o hello_c.o
-	$(TEST_HC) -fprefer-byte-code -fbyte-code-and-object-code -fno-ignore-interface-pragmas hello_c.o Hello.hs Main.hs
+	'$(TEST_HC)' -c hello_c.c -o hello_c.o
+	'$(TEST_HC)' -fprefer-byte-code -fbyte-code-and-object-code -fno-ignore-interface-pragmas hello_c.o Hello.hs Main.hs
 	./Main


=====================================
testsuite/tests/bytecode/T25090/Makefile
=====================================
@@ -4,18 +4,18 @@ include $(TOP)/mk/test.mk
 
 # Verify that the object files aren't linked by clobbering them.
 T25090a:
-	$(TEST_HC) -c -fbyte-code-and-object-code C.hs-boot
-	$(TEST_HC) -c -fbyte-code-and-object-code B.hs
-	$(TEST_HC) -c -fbyte-code-and-object-code C.hs
+	'$(TEST_HC)' -c -fbyte-code-and-object-code C.hs-boot
+	'$(TEST_HC)' -c -fbyte-code-and-object-code B.hs
+	'$(TEST_HC)' -c -fbyte-code-and-object-code C.hs
 	echo 'corrupt' > B.o
 	echo 'corrupt' > C.o
 	echo 'corrupt' > C.o-boot
-	$(TEST_HC) -c -fbyte-code-and-object-code D.hs
+	'$(TEST_HC)' -c -fbyte-code-and-object-code D.hs
 	echo 'corrupt' > D.o
-	$(TEST_HC) -c -fbyte-code-and-object-code -fprefer-byte-code A.hs
-	$(TEST_HC) -fbyte-code-and-object-code -fprefer-byte-code A.o -o exe
+	'$(TEST_HC)' -c -fbyte-code-and-object-code -fprefer-byte-code A.hs
+	'$(TEST_HC)' -fbyte-code-and-object-code -fprefer-byte-code A.o -o exe
 	./exe
 
 T25090b:
-	$(TEST_HC) -fbyte-code-and-object-code -fprefer-byte-code A -o exe -v0
+	'$(TEST_HC)' -fbyte-code-and-object-code -fprefer-byte-code A -o exe -v0
 	./exe


=====================================
testsuite/tests/driver/Makefile
=====================================
@@ -788,7 +788,7 @@ T22044:
 
 .PHONY: T22669
 T22669:
-	echo ":q" | "$(TEST_HC)" $(TEST_HC_OPTS) -v0 --interactive T22669
+	echo ":q" | "$(TEST_HC)" $(TEST_HC_OPTS_INTERACTIVE) T22669
 	! test -f T22669.o-boot
 
 


=====================================
testsuite/tests/driver/boot-target/Makefile
=====================================
@@ -1,8 +1,8 @@
 boot1:
-	$(TEST_HC) -c A.hs-boot B.hs
+	'$(TEST_HC)' -c A.hs-boot B.hs
 
 boot2:
-	$(TEST_HC) A.hs-boot A.hs B.hs -v0
+	'$(TEST_HC)' A.hs-boot A.hs B.hs -v0
 
 boot3:
-	$(TEST_HC) A.hs-boot B.hs -v0
\ No newline at end of file
+	'$(TEST_HC)' A.hs-boot B.hs -v0


=====================================
testsuite/tests/driver/fat-iface/Makefile
=====================================
@@ -55,5 +55,5 @@ T22807: clean
 
 T22807_ghci: clean
 	"$(TEST_HC)" $(TEST_HC_OPTS) T22807_ghci.hs -fno-full-laziness -fhide-source-paths -fwrite-if-simplified-core -O2 -dynamic -v0
-	"$(TEST_HC)" $(TEST_HC_OPTS) -v0 --interactive -fhide-source-paths -fno-full-laziness < T22807_ghci.script
+	"$(TEST_HC)" $(TEST_HC_OPTS_INTERACTIVE) -fhide-source-paths -fno-full-laziness < T22807_ghci.script
 


=====================================
testsuite/tests/interface-stability/base-exports.stdout
=====================================
@@ -234,7 +234,7 @@ module Control.Exception where
   type ErrorCall :: *
   data ErrorCall = ErrorCallWithLocation GHC.Internal.Base.String GHC.Internal.Base.String
   type Exception :: * -> Constraint
-  class (ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable e, GHC.Internal.Show.Show e) => Exception e where
+  class (ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable e, GHC.Internal.Show.Show e) => Exception e where
     toException :: e -> SomeException
     fromException :: SomeException -> GHC.Internal.Maybe.Maybe e
     displayException :: e -> GHC.Internal.Base.String
@@ -308,7 +308,7 @@ module Control.Exception where
 module Control.Exception.Annotation where
   -- Safety: None
   type ExceptionAnnotation :: * -> Constraint
-  class ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable a => ExceptionAnnotation a where
+  class ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable a => ExceptionAnnotation a where
     displayExceptionAnnotation :: a -> GHC.Internal.Base.String
     default displayExceptionAnnotation :: GHC.Internal.Show.Show a => a -> GHC.Internal.Base.String
     {-# MINIMAL #-}
@@ -350,7 +350,7 @@ module Control.Exception.Base where
   type ErrorCall :: *
   data ErrorCall = ErrorCallWithLocation GHC.Internal.Base.String GHC.Internal.Base.String
   type Exception :: * -> Constraint
-  class (ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable e, GHC.Internal.Show.Show e) => Exception e where
+  class (ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable e, GHC.Internal.Show.Show e) => Exception e where
     toException :: e -> SomeException
     fromException :: SomeException -> GHC.Internal.Maybe.Maybe e
     displayException :: e -> GHC.Internal.Base.String
@@ -855,11 +855,11 @@ module Data.Data where
   type TyCon :: *
   data TyCon = ...
   type TypeRep :: *
-  type TypeRep = ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.SomeTypeRep
+  type TypeRep = ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.SomeTypeRep
   type Typeable :: forall k. k -> Constraint
   class Typeable a where
     ...
-    {-# MINIMAL ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.typeRep# #-}
+    {-# MINIMAL ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.typeRep# #-}
   cast :: forall a b. (Typeable a, Typeable b) => a -> GHC.Internal.Maybe.Maybe b
   constrFields :: Constr -> [GHC.Internal.Base.String]
   constrFixity :: Constr -> Fixity
@@ -902,7 +902,7 @@ module Data.Data where
   showConstr :: Constr -> GHC.Internal.Base.String
   showsTypeRep :: TypeRep -> GHC.Internal.Show.ShowS
   splitTyConApp :: TypeRep -> (TyCon, [TypeRep])
-  trLiftedRep :: ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.TypeRep GHC.Types.LiftedRep
+  trLiftedRep :: ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.TypeRep GHC.Types.LiftedRep
   tyConFingerprint :: TyCon -> GHC.Internal.Fingerprint.Type.Fingerprint
   tyConModule :: TyCon -> GHC.Internal.Base.String
   tyConName :: TyCon -> GHC.Internal.Base.String
@@ -926,14 +926,14 @@ module Data.Dynamic where
   -- Safety: Safe
   type Dynamic :: *
   data Dynamic where
-    Dynamic :: forall a. ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.TypeRep a -> a -> Dynamic
+    Dynamic :: forall a. ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.TypeRep a -> a -> Dynamic
   type Typeable :: forall k. k -> Constraint
   class Typeable a where
     ...
-    {-# MINIMAL ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.typeRep# #-}
+    {-# MINIMAL ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.typeRep# #-}
   dynApp :: Dynamic -> Dynamic -> Dynamic
   dynApply :: Dynamic -> Dynamic -> GHC.Internal.Maybe.Maybe Dynamic
-  dynTypeRep :: Dynamic -> ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.SomeTypeRep
+  dynTypeRep :: Dynamic -> ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.SomeTypeRep
   fromDyn :: forall a. Typeable a => Dynamic -> a -> a
   fromDynamic :: forall a. Typeable a => Dynamic -> GHC.Internal.Maybe.Maybe a
   toDyn :: forall a. Typeable a => a -> Dynamic
@@ -1820,11 +1820,11 @@ module Data.Typeable where
   type TyCon :: *
   data TyCon = ...
   type TypeRep :: *
-  type TypeRep = ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.SomeTypeRep
+  type TypeRep = ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.SomeTypeRep
   type Typeable :: forall k. k -> Constraint
   class Typeable a where
     ...
-    {-# MINIMAL ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.typeRep# #-}
+    {-# MINIMAL ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.typeRep# #-}
   cast :: forall a b. (Typeable a, Typeable b) => a -> GHC.Internal.Maybe.Maybe b
   decT :: forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => GHC.Internal.Data.Either.Either ((a :~: b) -> GHC.Internal.Base.Void) (a :~: b)
   eqT :: forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => GHC.Internal.Maybe.Maybe (a :~: b)
@@ -1839,7 +1839,7 @@ module Data.Typeable where
   rnfTypeRep :: TypeRep -> ()
   showsTypeRep :: TypeRep -> GHC.Internal.Show.ShowS
   splitTyConApp :: TypeRep -> (TyCon, [TypeRep])
-  trLiftedRep :: ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.TypeRep GHC.Types.LiftedRep
+  trLiftedRep :: ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.TypeRep GHC.Types.LiftedRep
   tyConFingerprint :: TyCon -> GHC.Internal.Fingerprint.Type.Fingerprint
   tyConModule :: TyCon -> GHC.Internal.Base.String
   tyConName :: TyCon -> GHC.Internal.Base.String
@@ -5260,7 +5260,7 @@ module GHC.Event where
   data EventManager = ...
   type FdKey :: *
   data FdKey
-    = ghc-internal-9.1001.0:GHC.Internal.Event.Manager.FdKey {keyFd :: ! {-# UNPACK #-}(GHC.Internal.System.Posix.Types.N:Fd
+    = ghc-internal-9.1300.0:GHC.Internal.Event.Manager.FdKey {keyFd :: ! {-# UNPACK #-}(GHC.Internal.System.Posix.Types.N:Fd
                                                                                         ; GHC.Internal.Foreign.C.Types.N:CInt)GHC.Internal.System.Posix.Types.Fd,
                                                               ...}
   type IOCallback :: *
@@ -5293,9 +5293,9 @@ module GHC.Event.TimeOut where
   type TimeoutEdit :: *
   type TimeoutEdit = TimeoutQueue -> TimeoutQueue
   type TimeoutKey :: *
-  newtype TimeoutKey = TK ghc-internal-9.1100.0:GHC.Internal.Event.Unique.Unique
+  newtype TimeoutKey = TK ghc-internal-9.1300.0:GHC.Internal.Event.Unique.Unique
   type TimeoutQueue :: *
-  type TimeoutQueue = ghc-internal-9.1100.0:GHC.Internal.Event.PSQ.PSQ TimeoutCallback
+  type TimeoutQueue = ghc-internal-9.1300.0:GHC.Internal.Event.PSQ.PSQ TimeoutCallback
 
 module GHC.Exception where
   -- Safety: Safe
@@ -5307,7 +5307,7 @@ module GHC.Exception where
   type ErrorCall :: *
   data ErrorCall = ErrorCallWithLocation GHC.Internal.Base.String GHC.Internal.Base.String
   type Exception :: * -> Constraint
-  class (ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable e, GHC.Internal.Show.Show e) => Exception e where
+  class (ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable e, GHC.Internal.Show.Show e) => Exception e where
     toException :: e -> SomeException
     fromException :: SomeException -> GHC.Internal.Maybe.Maybe e
     displayException :: e -> GHC.Internal.Base.String
@@ -5316,7 +5316,7 @@ module GHC.Exception where
   type SomeException :: *
   data SomeException = forall e. (Exception e, GHC.Internal.Exception.Type.HasExceptionContext) => SomeException e
   type SrcLoc :: *
-  data SrcLoc = SrcLoc {srcLocPackage :: [GHC.Types.Char], srcLocModule :: [GHC.Types.Char], srcLocFile :: [GHC.Types.Char], srcLocStartLine :: GHC.Types.Int, srcLocStartCol :: GHC.Types.Int, srcLocEndLine :: GHC.Types.Int, srcLocEndCol :: GHC.Types.Int}
+  data SrcLoc = SrcLoc {srcLocPackage :: [GHC.Types.Char], srcLocModule :: [GHC.Types.Char], srcLocFile :: [GHC.Types.Char], srcLocStartLine :: {-# UNPACK #-}GHC.Types.Int, srcLocStartCol :: {-# UNPACK #-}GHC.Types.Int, srcLocEndLine :: {-# UNPACK #-}GHC.Types.Int, srcLocEndCol :: {-# UNPACK #-}GHC.Types.Int}
   divZeroException :: SomeException
   errorCallException :: GHC.Internal.Base.String -> SomeException
   errorCallWithCallStackException :: GHC.Internal.Base.String -> CallStack -> SomeException
@@ -5336,7 +5336,7 @@ module GHC.Exception.Type where
   type ArithException :: *
   data ArithException = Overflow | Underflow | LossOfPrecision | DivideByZero | Denormal | RatioZeroDenominator
   type Exception :: * -> Constraint
-  class (ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable e, GHC.Internal.Show.Show e) => Exception e where
+  class (ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable e, GHC.Internal.Show.Show e) => Exception e where
     toException :: e -> SomeException
     fromException :: SomeException -> GHC.Internal.Maybe.Maybe e
     displayException :: e -> GHC.Internal.Base.String
@@ -7889,8 +7889,8 @@ module GHC.IO.Handle where
   hTryLock :: Handle -> LockMode -> GHC.Types.IO GHC.Types.Bool
   hWaitForInput :: Handle -> GHC.Types.Int -> GHC.Types.IO GHC.Types.Bool
   isEOF :: GHC.Types.IO GHC.Types.Bool
-  mkDuplexHandle :: forall dev. (GHC.Internal.IO.Device.RawIO dev, GHC.Internal.IO.Device.IODevice dev, GHC.Internal.IO.BufferedIO.BufferedIO dev, ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable dev) => dev -> GHC.Internal.IO.FilePath -> GHC.Internal.Maybe.Maybe GHC.Internal.IO.Encoding.Types.TextEncoding -> NewlineMode -> GHC.Types.IO Handle
-  mkFileHandle :: forall dev. (GHC.Internal.IO.Device.RawIO dev, GHC.Internal.IO.Device.IODevice dev, GHC.Internal.IO.BufferedIO.BufferedIO dev, ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable dev) => dev -> GHC.Internal.IO.FilePath -> GHC.Internal.IO.IOMode.IOMode -> GHC.Internal.Maybe.Maybe GHC.Internal.IO.Encoding.Types.TextEncoding -> NewlineMode -> GHC.Types.IO Handle
+  mkDuplexHandle :: forall dev. (GHC.Internal.IO.Device.RawIO dev, GHC.Internal.IO.Device.IODevice dev, GHC.Internal.IO.BufferedIO.BufferedIO dev, ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable dev) => dev -> GHC.Internal.IO.FilePath -> GHC.Internal.Maybe.Maybe GHC.Internal.IO.Encoding.Types.TextEncoding -> NewlineMode -> GHC.Types.IO Handle
+  mkFileHandle :: forall dev. (GHC.Internal.IO.Device.RawIO dev, GHC.Internal.IO.Device.IODevice dev, GHC.Internal.IO.BufferedIO.BufferedIO dev, ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable dev) => dev -> GHC.Internal.IO.FilePath -> GHC.Internal.IO.IOMode.IOMode -> GHC.Internal.Maybe.Maybe GHC.Internal.IO.Encoding.Types.TextEncoding -> NewlineMode -> GHC.Types.IO Handle
   nativeNewline :: Newline
   nativeNewlineMode :: NewlineMode
   noNewlineTranslation :: NewlineMode
@@ -7940,11 +7940,11 @@ module GHC.IO.Handle.Internals where
   ioe_notReadable :: forall a. GHC.Types.IO a
   ioe_notWritable :: forall a. GHC.Types.IO a
   ioe_semiclosedHandle :: forall a. GHC.Types.IO a
-  mkDuplexHandle :: forall dev. (GHC.Internal.IO.Device.RawIO dev, GHC.Internal.IO.Device.IODevice dev, GHC.Internal.IO.BufferedIO.BufferedIO dev, ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable dev) => dev -> GHC.Internal.IO.FilePath -> GHC.Internal.Maybe.Maybe GHC.Internal.IO.Encoding.Types.TextEncoding -> GHC.Internal.IO.Handle.Types.NewlineMode -> GHC.Types.IO GHC.Internal.IO.Handle.Types.Handle
-  mkDuplexHandleNoFinalizer :: forall dev. (GHC.Internal.IO.Device.RawIO dev, GHC.Internal.IO.Device.IODevice dev, GHC.Internal.IO.BufferedIO.BufferedIO dev, ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable dev) => dev -> GHC.Internal.IO.FilePath -> GHC.Internal.Maybe.Maybe GHC.Internal.IO.Encoding.Types.TextEncoding -> GHC.Internal.IO.Handle.Types.NewlineMode -> GHC.Types.IO GHC.Internal.IO.Handle.Types.Handle
-  mkFileHandle :: forall dev. (GHC.Internal.IO.Device.RawIO dev, GHC.Internal.IO.Device.IODevice dev, GHC.Internal.IO.BufferedIO.BufferedIO dev, ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable dev) => dev -> GHC.Internal.IO.FilePath -> GHC.Internal.IO.IOMode.IOMode -> GHC.Internal.Maybe.Maybe GHC.Internal.IO.Encoding.Types.TextEncoding -> GHC.Internal.IO.Handle.Types.NewlineMode -> GHC.Types.IO GHC.Internal.IO.Handle.Types.Handle
-  mkFileHandleNoFinalizer :: forall dev. (GHC.Internal.IO.Device.RawIO dev, GHC.Internal.IO.Device.IODevice dev, GHC.Internal.IO.BufferedIO.BufferedIO dev, ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable dev) => dev -> GHC.Internal.IO.FilePath -> GHC.Internal.IO.IOMode.IOMode -> GHC.Internal.Maybe.Maybe GHC.Internal.IO.Encoding.Types.TextEncoding -> GHC.Internal.IO.Handle.Types.NewlineMode -> GHC.Types.IO GHC.Internal.IO.Handle.Types.Handle
-  mkHandle :: forall dev. (GHC.Internal.IO.Device.RawIO dev, GHC.Internal.IO.Device.IODevice dev, GHC.Internal.IO.BufferedIO.BufferedIO dev, ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable dev) => dev -> GHC.Internal.IO.FilePath -> GHC.Internal.IO.Handle.Types.HandleType -> GHC.Types.Bool -> GHC.Internal.Maybe.Maybe GHC.Internal.IO.Encoding.Types.TextEncoding -> GHC.Internal.IO.Handle.Types.NewlineMode -> GHC.Internal.Maybe.Maybe HandleFinalizer -> GHC.Internal.Maybe.Maybe (GHC.Internal.MVar.MVar GHC.Internal.IO.Handle.Types.Handle__) -> GHC.Types.IO GHC.Internal.IO.Handle.Types.Handle
+  mkDuplexHandle :: forall dev. (GHC.Internal.IO.Device.RawIO dev, GHC.Internal.IO.Device.IODevice dev, GHC.Internal.IO.BufferedIO.BufferedIO dev, ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable dev) => dev -> GHC.Internal.IO.FilePath -> GHC.Internal.Maybe.Maybe GHC.Internal.IO.Encoding.Types.TextEncoding -> GHC.Internal.IO.Handle.Types.NewlineMode -> GHC.Types.IO GHC.Internal.IO.Handle.Types.Handle
+  mkDuplexHandleNoFinalizer :: forall dev. (GHC.Internal.IO.Device.RawIO dev, GHC.Internal.IO.Device.IODevice dev, GHC.Internal.IO.BufferedIO.BufferedIO dev, ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable dev) => dev -> GHC.Internal.IO.FilePath -> GHC.Internal.Maybe.Maybe GHC.Internal.IO.Encoding.Types.TextEncoding -> GHC.Internal.IO.Handle.Types.NewlineMode -> GHC.Types.IO GHC.Internal.IO.Handle.Types.Handle
+  mkFileHandle :: forall dev. (GHC.Internal.IO.Device.RawIO dev, GHC.Internal.IO.Device.IODevice dev, GHC.Internal.IO.BufferedIO.BufferedIO dev, ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable dev) => dev -> GHC.Internal.IO.FilePath -> GHC.Internal.IO.IOMode.IOMode -> GHC.Internal.Maybe.Maybe GHC.Internal.IO.Encoding.Types.TextEncoding -> GHC.Internal.IO.Handle.Types.NewlineMode -> GHC.Types.IO GHC.Internal.IO.Handle.Types.Handle
+  mkFileHandleNoFinalizer :: forall dev. (GHC.Internal.IO.Device.RawIO dev, GHC.Internal.IO.Device.IODevice dev, GHC.Internal.IO.BufferedIO.BufferedIO dev, ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable dev) => dev -> GHC.Internal.IO.FilePath -> GHC.Internal.IO.IOMode.IOMode -> GHC.Internal.Maybe.Maybe GHC.Internal.IO.Encoding.Types.TextEncoding -> GHC.Internal.IO.Handle.Types.NewlineMode -> GHC.Types.IO GHC.Internal.IO.Handle.Types.Handle
+  mkHandle :: forall dev. (GHC.Internal.IO.Device.RawIO dev, GHC.Internal.IO.Device.IODevice dev, GHC.Internal.IO.BufferedIO.BufferedIO dev, ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable dev) => dev -> GHC.Internal.IO.FilePath -> GHC.Internal.IO.Handle.Types.HandleType -> GHC.Types.Bool -> GHC.Internal.Maybe.Maybe GHC.Internal.IO.Encoding.Types.TextEncoding -> GHC.Internal.IO.Handle.Types.NewlineMode -> GHC.Internal.Maybe.Maybe HandleFinalizer -> GHC.Internal.Maybe.Maybe (GHC.Internal.MVar.MVar GHC.Internal.IO.Handle.Types.Handle__) -> GHC.Types.IO GHC.Internal.IO.Handle.Types.Handle
   openTextEncoding :: forall a. GHC.Internal.Maybe.Maybe GHC.Internal.IO.Encoding.Types.TextEncoding -> GHC.Internal.IO.Handle.Types.HandleType -> (forall es ds. GHC.Internal.Maybe.Maybe (GHC.Internal.IO.Encoding.Types.TextEncoder es) -> GHC.Internal.Maybe.Maybe (GHC.Internal.IO.Encoding.Types.TextDecoder ds) -> GHC.Types.IO a) -> GHC.Types.IO a
   readTextDevice :: GHC.Internal.IO.Handle.Types.Handle__ -> GHC.Internal.IO.Buffer.CharBuffer -> GHC.Types.IO GHC.Internal.IO.Buffer.CharBuffer
   readTextDeviceNonBlocking :: GHC.Internal.IO.Handle.Types.Handle__ -> GHC.Internal.IO.Buffer.CharBuffer -> GHC.Types.IO GHC.Internal.IO.Buffer.CharBuffer
@@ -8008,7 +8008,7 @@ module GHC.IO.Handle.Types where
   type Handle__ :: *
   data Handle__
     = forall dev enc_state dec_state.
-      (GHC.Internal.IO.Device.RawIO dev, GHC.Internal.IO.Device.IODevice dev, GHC.Internal.IO.BufferedIO.BufferedIO dev, ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable dev) =>
+      (GHC.Internal.IO.Device.RawIO dev, GHC.Internal.IO.Device.IODevice dev, GHC.Internal.IO.BufferedIO.BufferedIO dev, ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable dev) =>
       Handle__ {haDevice :: !dev,
                 haType :: HandleType,
                 haByteBuffer :: ! {-# UNPACK #-}(GHC.Internal.IORef.N:IORef <GHC.Internal.IO.Buffer.Buffer GHC.Internal.Word.Word8>_N)(GHC.Internal.IORef.IORef (GHC.Internal.IO.Buffer.Buffer GHC.Internal.Word.Word8)),
@@ -9350,7 +9350,7 @@ module GHC.Stack where
   type HasCallStack :: Constraint
   type HasCallStack = ?callStack::CallStack :: Constraint
   type SrcLoc :: *
-  data SrcLoc = SrcLoc {srcLocPackage :: [GHC.Types.Char], srcLocModule :: [GHC.Types.Char], srcLocFile :: [GHC.Types.Char], srcLocStartLine :: GHC.Types.Int, srcLocStartCol :: GHC.Types.Int, srcLocEndLine :: GHC.Types.Int, srcLocEndCol :: GHC.Types.Int}
+  data SrcLoc = SrcLoc {srcLocPackage :: [GHC.Types.Char], srcLocModule :: [GHC.Types.Char], srcLocFile :: [GHC.Types.Char], srcLocStartLine :: {-# UNPACK #-}GHC.Types.Int, srcLocStartCol :: {-# UNPACK #-}GHC.Types.Int, srcLocEndLine :: {-# UNPACK #-}GHC.Types.Int, srcLocEndCol :: {-# UNPACK #-}GHC.Types.Int}
   callStack :: HasCallStack => CallStack
   ccLabel :: GHC.Internal.Ptr.Ptr CostCentre -> GHC.Types.IO GHC.Internal.Foreign.C.String.Encoding.CString
   ccModule :: GHC.Internal.Ptr.Ptr CostCentre -> GHC.Types.IO GHC.Internal.Foreign.C.String.Encoding.CString
@@ -9411,7 +9411,7 @@ module GHC.Stack.Types where
   type HasCallStack :: Constraint
   type HasCallStack = ?callStack::CallStack :: Constraint
   type SrcLoc :: *
-  data SrcLoc = SrcLoc {srcLocPackage :: [GHC.Types.Char], srcLocModule :: [GHC.Types.Char], srcLocFile :: [GHC.Types.Char], srcLocStartLine :: GHC.Types.Int, srcLocStartCol :: GHC.Types.Int, srcLocEndLine :: GHC.Types.Int, srcLocEndCol :: GHC.Types.Int}
+  data SrcLoc = SrcLoc {srcLocPackage :: [GHC.Types.Char], srcLocModule :: [GHC.Types.Char], srcLocFile :: [GHC.Types.Char], srcLocStartLine :: {-# UNPACK #-}GHC.Types.Int, srcLocStartCol :: {-# UNPACK #-}GHC.Types.Int, srcLocEndLine :: {-# UNPACK #-}GHC.Types.Int, srcLocEndCol :: {-# UNPACK #-}GHC.Types.Int}
   emptyCallStack :: CallStack
   freezeCallStack :: CallStack -> CallStack
   fromCallSiteList :: [([GHC.Types.Char], SrcLoc)] -> CallStack
@@ -9422,7 +9422,7 @@ module GHC.StaticPtr where
   -- Safety: None
   type IsStatic :: (* -> *) -> Constraint
   class IsStatic p where
-    fromStaticPtr :: forall a. ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable a => StaticPtr a -> p a
+    fromStaticPtr :: forall a. ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable a => StaticPtr a -> p a
     {-# MINIMAL fromStaticPtr #-}
   type StaticKey :: *
   type StaticKey = GHC.Internal.Fingerprint.Type.Fingerprint
@@ -10819,8 +10819,8 @@ module Type.Reflection where
   data (:~~:) a b where
     HRefl :: forall {k1} (a :: k1). (:~~:) a a
   pattern App :: forall k2 (t :: k2). () => forall k1 (a :: k1 -> k2) (b :: k1). (t ~ a b) => TypeRep a -> TypeRep b -> TypeRep t
-  pattern Con :: forall k (a :: k). () => ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.NotApplication a => TyCon -> TypeRep a
-  pattern Con' :: forall k (a :: k). () => ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.NotApplication a => TyCon -> [SomeTypeRep] -> TypeRep a
+  pattern Con :: forall k (a :: k). () => ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.NotApplication a => TyCon -> TypeRep a
+  pattern Con' :: forall k (a :: k). () => ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.NotApplication a => TyCon -> [SomeTypeRep] -> TypeRep a
   pattern Fun :: forall k (fun :: k). () => forall (r1 :: GHC.Types.RuntimeRep) (r2 :: GHC.Types.RuntimeRep) (arg :: TYPE r1) (res :: TYPE r2). (k ~ *, fun ~~ (arg -> res)) => TypeRep arg -> TypeRep res -> TypeRep fun
   type Module :: *
   data Module = ...
@@ -10837,7 +10837,7 @@ module Type.Reflection where
   type Typeable :: forall k. k -> Constraint
   class Typeable a where
     ...
-    {-# MINIMAL ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.typeRep# #-}
+    {-# MINIMAL ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.typeRep# #-}
   decTypeRep :: forall k1 k2 (a :: k1) (b :: k2). TypeRep a -> TypeRep b -> GHC.Internal.Data.Either.Either ((a :~~: b) -> GHC.Internal.Base.Void) (a :~~: b)
   eqTypeRep :: forall k1 k2 (a :: k1) (b :: k2). TypeRep a -> TypeRep b -> GHC.Internal.Maybe.Maybe (a :~~: b)
   moduleName :: Module -> GHC.Internal.Base.String
@@ -10872,9 +10872,9 @@ module Type.Reflection.Unsafe where
   data TypeRep a where
     ...
   mkTrApp :: forall k1 k2 (a :: k1 -> k2) (b :: k1). TypeRep a -> TypeRep b -> TypeRep (a b)
-  mkTrCon :: forall k (a :: k). TyCon -> [ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.SomeTypeRep] -> TypeRep a
+  mkTrCon :: forall k (a :: k). TyCon -> [ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.SomeTypeRep] -> TypeRep a
   mkTyCon :: GHC.Internal.Base.String -> GHC.Internal.Base.String -> GHC.Internal.Base.String -> GHC.Types.Int -> KindRep -> TyCon
-  someTypeRepFingerprint :: ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.SomeTypeRep -> GHC.Internal.Fingerprint.Type.Fingerprint
+  someTypeRepFingerprint :: ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.SomeTypeRep -> GHC.Internal.Fingerprint.Type.Fingerprint
   tyConFingerprint :: TyCon -> GHC.Internal.Fingerprint.Type.Fingerprint
   tyConKindArgs :: TyCon -> GHC.Types.Int
   tyConKindRep :: TyCon -> KindRep
@@ -11195,9 +11195,9 @@ instance forall a. GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monoid (GHC.I
 instance forall a. (GHC.Classes.Ord a, GHC.Internal.Enum.Bounded a) => GHC.Internal.Base.Monoid (Data.Semigroup.Max a) -- Defined in ‘Data.Semigroup’
 instance forall a. (GHC.Classes.Ord a, GHC.Internal.Enum.Bounded a) => GHC.Internal.Base.Monoid (Data.Semigroup.Min a) -- Defined in ‘Data.Semigroup’
 instance forall m. GHC.Internal.Base.Monoid m => GHC.Internal.Base.Monoid (Data.Semigroup.WrappedMonoid m) -- Defined in ‘Data.Semigroup’
-instance GHC.Internal.Base.Monoid ghc-internal-9.1100.0:GHC.Internal.Event.Internal.Types.Event -- Defined in ‘ghc-internal-9.1100.0:GHC.Internal.Event.Internal.Types’
-instance GHC.Internal.Base.Monoid ghc-internal-9.1100.0:GHC.Internal.Event.Internal.Types.EventLifetime -- Defined in ‘ghc-internal-9.1100.0:GHC.Internal.Event.Internal.Types’
-instance GHC.Internal.Base.Monoid ghc-internal-9.1100.0:GHC.Internal.Event.Internal.Types.Lifetime -- Defined in ‘ghc-internal-9.1100.0:GHC.Internal.Event.Internal.Types’
+instance GHC.Internal.Base.Monoid ghc-internal-9.1300.0:GHC.Internal.Event.Internal.Types.Event -- Defined in ‘ghc-internal-9.1300.0:GHC.Internal.Event.Internal.Types’
+instance GHC.Internal.Base.Monoid ghc-internal-9.1300.0:GHC.Internal.Event.Internal.Types.EventLifetime -- Defined in ‘ghc-internal-9.1300.0:GHC.Internal.Event.Internal.Types’
+instance GHC.Internal.Base.Monoid ghc-internal-9.1300.0:GHC.Internal.Event.Internal.Types.Lifetime -- Defined in ‘ghc-internal-9.1300.0:GHC.Internal.Event.Internal.Types’
 instance forall k (f :: k -> *) (p :: k) (g :: k -> *). (GHC.Internal.Base.Monoid (f p), GHC.Internal.Base.Monoid (g p)) => GHC.Internal.Base.Monoid ((GHC.Internal.Generics.:*:) f g p) -- Defined in ‘GHC.Internal.Generics’
 instance forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (p :: k1). GHC.Internal.Base.Monoid (f (g p)) => GHC.Internal.Base.Monoid ((GHC.Internal.Generics.:.:) f g p) -- Defined in ‘GHC.Internal.Generics’
 instance forall a. (GHC.Internal.Generics.Generic a, GHC.Internal.Base.Monoid (GHC.Internal.Generics.Rep a ())) => GHC.Internal.Base.Monoid (GHC.Internal.Generics.Generically a) -- Defined in ‘GHC.Internal.Generics’
@@ -11253,9 +11253,9 @@ instance forall a. GHC.Internal.Base.Semigroup (Data.Semigroup.Last a) -- Define
 instance forall a. GHC.Classes.Ord a => GHC.Internal.Base.Semigroup (Data.Semigroup.Max a) -- Defined in ‘Data.Semigroup’
 instance forall a. GHC.Classes.Ord a => GHC.Internal.Base.Semigroup (Data.Semigroup.Min a) -- Defined in ‘Data.Semigroup’
 instance forall m. GHC.Internal.Base.Monoid m => GHC.Internal.Base.Semigroup (Data.Semigroup.WrappedMonoid m) -- Defined in ‘Data.Semigroup’
-instance GHC.Internal.Base.Semigroup ghc-internal-9.1100.0:GHC.Internal.Event.Internal.Types.Event -- Defined in ‘ghc-internal-9.1100.0:GHC.Internal.Event.Internal.Types’
-instance GHC.Internal.Base.Semigroup ghc-internal-9.1100.0:GHC.Internal.Event.Internal.Types.EventLifetime -- Defined in ‘ghc-internal-9.1100.0:GHC.Internal.Event.Internal.Types’
-instance GHC.Internal.Base.Semigroup ghc-internal-9.1100.0:GHC.Internal.Event.Internal.Types.Lifetime -- Defined in ‘ghc-internal-9.1100.0:GHC.Internal.Event.Internal.Types’
+instance GHC.Internal.Base.Semigroup ghc-internal-9.1300.0:GHC.Internal.Event.Internal.Types.Event -- Defined in ‘ghc-internal-9.1300.0:GHC.Internal.Event.Internal.Types’
+instance GHC.Internal.Base.Semigroup ghc-internal-9.1300.0:GHC.Internal.Event.Internal.Types.EventLifetime -- Defined in ‘ghc-internal-9.1300.0:GHC.Internal.Event.Internal.Types’
+instance GHC.Internal.Base.Semigroup ghc-internal-9.1300.0:GHC.Internal.Event.Internal.Types.Lifetime -- Defined in ‘ghc-internal-9.1300.0:GHC.Internal.Event.Internal.Types’
 instance forall k (f :: k -> *) (p :: k) (g :: k -> *). (GHC.Internal.Base.Semigroup (f p), GHC.Internal.Base.Semigroup (g p)) => GHC.Internal.Base.Semigroup ((GHC.Internal.Generics.:*:) f g p) -- Defined in ‘GHC.Internal.Generics’
 instance forall k2 k1 (f :: k2 -> *) (g :: k1 -> k2) (p :: k1). GHC.Internal.Base.Semigroup (f (g p)) => GHC.Internal.Base.Semigroup ((GHC.Internal.Generics.:.:) f g p) -- Defined in ‘GHC.Internal.Generics’
 instance forall a. (GHC.Internal.Generics.Generic a, GHC.Internal.Base.Semigroup (GHC.Internal.Generics.Rep a ())) => GHC.Internal.Base.Semigroup (GHC.Internal.Generics.Generically a) -- Defined in ‘GHC.Internal.Generics’
@@ -11398,20 +11398,20 @@ instance GHC.Internal.Control.Monad.Zip.MonadZip GHC.Internal.Data.Semigroup.Int
 instance GHC.Internal.Control.Monad.Zip.MonadZip Solo -- Defined in ‘GHC.Internal.Control.Monad.Zip’
 instance GHC.Internal.Control.Monad.Zip.MonadZip GHC.Internal.Data.Semigroup.Internal.Sum -- Defined in ‘GHC.Internal.Control.Monad.Zip’
 instance GHC.Internal.Control.Monad.Zip.MonadZip Data.Complex.Complex -- Defined in ‘Data.Complex’
-instance forall (a :: * -> * -> *) b c. (ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable a, ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable b, ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable c, GHC.Internal.Data.Data.Data (a b c)) => GHC.Internal.Data.Data.Data (Control.Applicative.WrappedArrow a b c) -- Defined in ‘Control.Applicative’
-instance forall (m :: * -> *) a. (ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable m, ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable a, GHC.Internal.Data.Data.Data (m a)) => GHC.Internal.Data.Data.Data (Control.Applicative.WrappedMonad m a) -- Defined in ‘Control.Applicative’
+instance forall (a :: * -> * -> *) b c. (ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable a, ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable b, ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable c, GHC.Internal.Data.Data.Data (a b c)) => GHC.Internal.Data.Data.Data (Control.Applicative.WrappedArrow a b c) -- Defined in ‘Control.Applicative’
+instance forall (m :: * -> *) a. (ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable m, ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable a, GHC.Internal.Data.Data.Data (m a)) => GHC.Internal.Data.Data.Data (Control.Applicative.WrappedMonad m a) -- Defined in ‘Control.Applicative’
 instance forall a. GHC.Internal.Data.Data.Data a => GHC.Internal.Data.Data.Data (GHC.Internal.Functor.ZipList.ZipList a) -- Defined in ‘GHC.Internal.Functor.ZipList’
 instance GHC.Internal.Data.Data.Data Data.Array.Byte.ByteArray -- Defined in ‘Data.Array.Byte’
-instance forall s. ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable s => GHC.Internal.Data.Data.Data (Data.Array.Byte.MutableByteArray s) -- Defined in ‘Data.Array.Byte’
+instance forall s. ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable s => GHC.Internal.Data.Data.Data (Data.Array.Byte.MutableByteArray s) -- Defined in ‘Data.Array.Byte’
 instance forall a. GHC.Internal.Data.Data.Data a => GHC.Internal.Data.Data.Data (Data.Complex.Complex a) -- Defined in ‘Data.Complex’
-instance forall i j (a :: i) (b :: j). (ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable i, ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable j, ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable a, ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable b, a ~~ b) => GHC.Internal.Data.Data.Data (a GHC.Internal.Data.Type.Equality.:~~: b) -- Defined in ‘GHC.Internal.Data.Data’
+instance forall i j (a :: i) (b :: j). (ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable i, ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable j, ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable a, ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable b, a ~~ b) => GHC.Internal.Data.Data.Data (a GHC.Internal.Data.Type.Equality.:~~: b) -- Defined in ‘GHC.Internal.Data.Data’
 instance GHC.Internal.Data.Data.Data GHC.Internal.Data.Semigroup.Internal.All -- Defined in ‘GHC.Internal.Data.Data’
 instance GHC.Internal.Data.Data.Data GHC.Internal.Data.Semigroup.Internal.Any -- Defined in ‘GHC.Internal.Data.Data’
 instance forall a b. (GHC.Internal.Data.Data.Data a, GHC.Internal.Data.Data.Data b, GHC.Internal.Ix.Ix a) => GHC.Internal.Data.Data.Data (GHC.Internal.Arr.Array a b) -- Defined in ‘GHC.Internal.Data.Data’
 instance GHC.Internal.Data.Data.Data GHC.Internal.Generics.Associativity -- Defined in ‘GHC.Internal.Data.Data’
 instance GHC.Internal.Data.Data.Data GHC.Types.Bool -- Defined in ‘GHC.Internal.Data.Data’
 instance GHC.Internal.Data.Data.Data GHC.Types.Char -- Defined in ‘GHC.Internal.Data.Data’
-instance forall k a (b :: k). (ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable k, GHC.Internal.Data.Data.Data a, ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable b) => GHC.Internal.Data.Data.Data (GHC.Internal.Data.Functor.Const.Const a b) -- Defined in ‘GHC.Internal.Data.Data’
+instance forall k a (b :: k). (ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable k, GHC.Internal.Data.Data.Data a, ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable b) => GHC.Internal.Data.Data.Data (GHC.Internal.Data.Functor.Const.Const a b) -- Defined in ‘GHC.Internal.Data.Data’
 instance forall a. GHC.Internal.Data.Data.Data a => GHC.Internal.Data.Data.Data (GHC.Internal.Foreign.C.ConstPtr.ConstPtr a) -- Defined in ‘GHC.Internal.Data.Data’
 instance GHC.Internal.Data.Data.Data GHC.Internal.Generics.DecidedStrictness -- Defined in ‘GHC.Internal.Data.Data’
 instance GHC.Internal.Data.Data.Data GHC.Types.Double -- Defined in ‘GHC.Internal.Data.Data’
@@ -11459,10 +11459,10 @@ instance GHC.Internal.Data.Data.Data GHC.Internal.Word.Word32 -- Defined in ‘G
 instance GHC.Internal.Data.Data.Data GHC.Internal.Word.Word64 -- Defined in ‘GHC.Internal.Data.Data’
 instance GHC.Internal.Data.Data.Data GHC.Internal.Word.Word8 -- Defined in ‘GHC.Internal.Data.Data’
 instance GHC.Internal.Data.Data.Data GHC.Internal.Foreign.Ptr.WordPtr -- Defined in ‘GHC.Internal.Data.Data’
-instance forall k (a :: k). (ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable k, ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable a) => GHC.Internal.Data.Data.Data (Data.Fixed.Fixed a) -- Defined in ‘Data.Fixed’
-instance forall k1 (f :: k1 -> *) k2 (g :: k2 -> k1) (a :: k2). (ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable a, ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable f, ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable g, ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable k1, ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable k2, GHC.Internal.Data.Data.Data (f (g a))) => GHC.Internal.Data.Data.Data (Data.Functor.Compose.Compose f g a) -- Defined in ‘Data.Functor.Compose’
-instance [safe] forall k (f :: k -> *) (g :: k -> *) (a :: k). (ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable a, ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable f, ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable g, ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable k, GHC.Internal.Data.Data.Data (f a), GHC.Internal.Data.Data.Data (g a)) => GHC.Internal.Data.Data.Data (Data.Functor.Product.Product f g a) -- Defined in ‘Data.Functor.Product’
-instance [safe] forall k (f :: k -> *) (g :: k -> *) (a :: k). (ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable a, ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable f, ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable g, ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable k, GHC.Internal.Data.Data.Data (f a), GHC.Internal.Data.Data.Data (g a)) => GHC.Internal.Data.Data.Data (Data.Functor.Sum.Sum f g a) -- Defined in ‘Data.Functor.Sum’
+instance forall k (a :: k). (ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable k, ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable a) => GHC.Internal.Data.Data.Data (Data.Fixed.Fixed a) -- Defined in ‘Data.Fixed’
+instance forall k1 (f :: k1 -> *) k2 (g :: k2 -> k1) (a :: k2). (ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable a, ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable f, ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable g, ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable k1, ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable k2, GHC.Internal.Data.Data.Data (f (g a))) => GHC.Internal.Data.Data.Data (Data.Functor.Compose.Compose f g a) -- Defined in ‘Data.Functor.Compose’
+instance [safe] forall k (f :: k -> *) (g :: k -> *) (a :: k). (ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable a, ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable f, ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable g, ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable k, GHC.Internal.Data.Data.Data (f a), GHC.Internal.Data.Data.Data (g a)) => GHC.Internal.Data.Data.Data (Data.Functor.Product.Product f g a) -- Defined in ‘Data.Functor.Product’
+instance [safe] forall k (f :: k -> *) (g :: k -> *) (a :: k). (ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable a, ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable f, ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable g, ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable k, GHC.Internal.Data.Data.Data (f a), GHC.Internal.Data.Data.Data (g a)) => GHC.Internal.Data.Data.Data (Data.Functor.Sum.Sum f g a) -- Defined in ‘Data.Functor.Sum’
 instance forall a b. (GHC.Internal.Data.Data.Data a, GHC.Internal.Data.Data.Data b) => GHC.Internal.Data.Data.Data (Data.Semigroup.Arg a b) -- Defined in ‘Data.Semigroup’
 instance forall a. GHC.Internal.Data.Data.Data a => GHC.Internal.Data.Data.Data (Data.Semigroup.First a) -- Defined in ‘Data.Semigroup’
 instance forall a. GHC.Internal.Data.Data.Data a => GHC.Internal.Data.Data.Data (Data.Semigroup.Last a) -- Defined in ‘Data.Semigroup’
@@ -11528,7 +11528,7 @@ instance GHC.Internal.Data.Type.Equality.TestEquality GHC.Internal.TypeLits.SCha
 instance GHC.Internal.Data.Type.Equality.TestEquality GHC.Internal.TypeLits.SSymbol -- Defined in ‘GHC.Internal.TypeLits’
 instance forall k (a :: k). GHC.Internal.Data.Type.Equality.TestEquality ((GHC.Internal.Data.Type.Equality.:~:) a) -- Defined in ‘GHC.Internal.Data.Type.Equality’
 instance forall k1 k (a :: k1). GHC.Internal.Data.Type.Equality.TestEquality ((GHC.Internal.Data.Type.Equality.:~~:) a) -- Defined in ‘GHC.Internal.Data.Type.Equality’
-instance forall k. GHC.Internal.Data.Type.Equality.TestEquality ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.TypeRep -- Defined in ‘ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal’
+instance forall k. GHC.Internal.Data.Type.Equality.TestEquality ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.TypeRep -- Defined in ‘ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal’
 instance forall k1 k2 (f :: k1 -> *) (g :: k2 -> k1). GHC.Internal.Data.Type.Equality.TestEquality f => GHC.Internal.Data.Type.Equality.TestEquality (Data.Functor.Compose.Compose f g) -- Defined in ‘Data.Functor.Compose’
 instance forall a k (b :: k). GHC.Internal.Enum.Bounded a => GHC.Internal.Enum.Bounded (GHC.Internal.Data.Functor.Const.Const a b) -- Defined in ‘GHC.Internal.Data.Functor.Const’
 instance forall a. GHC.Internal.Enum.Bounded a => GHC.Internal.Enum.Bounded (GHC.Internal.Data.Bits.And a) -- Defined in ‘GHC.Internal.Data.Bits’
@@ -11726,7 +11726,7 @@ instance GHC.Internal.Exception.Type.Exception GHC.Internal.Control.Exception.Ba
 instance GHC.Internal.Exception.Type.Exception GHC.Internal.Control.Exception.Base.RecUpdError -- Defined in ‘GHC.Internal.Control.Exception.Base’
 instance GHC.Internal.Exception.Type.Exception GHC.Internal.Control.Exception.Base.TypeError -- Defined in ‘GHC.Internal.Control.Exception.Base’
 instance GHC.Internal.Exception.Type.Exception GHC.Internal.Data.Dynamic.Dynamic -- Defined in ‘GHC.Internal.Data.Dynamic’
-instance [safe] GHC.Internal.Exception.Type.Exception ghc-internal-9.1100.0:GHC.Internal.IO.Handle.Lock.Common.FileLockingNotSupported -- Defined in ‘ghc-internal-9.1100.0:GHC.Internal.IO.Handle.Lock.Common’
+instance [safe] GHC.Internal.Exception.Type.Exception ghc-internal-9.1300.0:GHC.Internal.IO.Handle.Lock.Common.FileLockingNotSupported -- Defined in ‘ghc-internal-9.1300.0:GHC.Internal.IO.Handle.Lock.Common’
 instance GHC.Internal.Exception.Type.Exception GHC.Internal.IOPort.IOPortException -- Defined in ‘GHC.Internal.IOPort’
 instance [safe] GHC.Internal.Exception.Type.Exception System.Timeout.Timeout -- Defined in ‘System.Timeout’
 instance forall a k (b :: k). GHC.Internal.Float.Floating a => GHC.Internal.Float.Floating (GHC.Internal.Data.Functor.Const.Const a b) -- Defined in ‘GHC.Internal.Data.Functor.Const’
@@ -12398,8 +12398,8 @@ instance GHC.Internal.Show.Show GHC.Internal.Data.Data.DataRep -- Defined in ‘
 instance GHC.Internal.Show.Show GHC.Internal.Data.Data.DataType -- Defined in ‘GHC.Internal.Data.Data’
 instance GHC.Internal.Show.Show GHC.Internal.Data.Data.Fixity -- Defined in ‘GHC.Internal.Data.Data’
 instance forall k (s :: k). GHC.Internal.Show.Show (GHC.Internal.Data.Proxy.Proxy s) -- Defined in ‘GHC.Internal.Data.Proxy’
-instance GHC.Internal.Show.Show ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.SomeTypeRep -- Defined in ‘ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal’
-instance forall k (a :: k). GHC.Internal.Show.Show (ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.TypeRep a) -- Defined in ‘ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal’
+instance GHC.Internal.Show.Show ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.SomeTypeRep -- Defined in ‘ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal’
+instance forall k (a :: k). GHC.Internal.Show.Show (ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.TypeRep a) -- Defined in ‘ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal’
 instance GHC.Internal.Show.Show GHC.Internal.Data.Dynamic.Dynamic -- Defined in ‘GHC.Internal.Data.Dynamic’
 instance forall a b. (GHC.Internal.Show.Show a, GHC.Internal.Show.Show b) => GHC.Internal.Show.Show (GHC.Internal.Data.Either.Either a b) -- Defined in ‘GHC.Internal.Data.Either’
 instance forall k (a :: k). Data.Fixed.HasResolution a => GHC.Internal.Show.Show (Data.Fixed.Fixed a) -- Defined in ‘Data.Fixed’
@@ -12470,13 +12470,13 @@ instance GHC.Internal.Show.Show GHC.Internal.Foreign.C.Types.CWchar -- Defined i
 instance forall a. GHC.Internal.Show.Show (GHC.Internal.Foreign.C.ConstPtr.ConstPtr a) -- Defined in ‘GHC.Internal.Foreign.C.ConstPtr’
 instance forall a b. (GHC.Internal.Ix.Ix a, GHC.Internal.Show.Show a, GHC.Internal.Show.Show b) => GHC.Internal.Show.Show (GHC.Internal.Arr.Array a b) -- Defined in ‘GHC.Internal.Arr’
 instance GHC.Internal.Show.Show GHC.Internal.ByteOrder.ByteOrder -- Defined in ‘GHC.Internal.ByteOrder’
-instance GHC.Internal.Show.Show ghc-internal-9.1100.0:GHC.Internal.Event.Internal.Types.Event -- Defined in ‘ghc-internal-9.1100.0:GHC.Internal.Event.Internal.Types’
-instance GHC.Internal.Show.Show ghc-internal-9.1100.0:GHC.Internal.Event.Internal.Types.EventLifetime -- Defined in ‘ghc-internal-9.1100.0:GHC.Internal.Event.Internal.Types’
-instance GHC.Internal.Show.Show ghc-internal-9.1100.0:GHC.Internal.Event.Internal.Types.Lifetime -- Defined in ‘ghc-internal-9.1100.0:GHC.Internal.Event.Internal.Types’
-instance GHC.Internal.Show.Show ghc-internal-9.1100.0:GHC.Internal.Event.Internal.Types.Timeout -- Defined in ‘ghc-internal-9.1100.0:GHC.Internal.Event.Internal.Types’
-instance GHC.Internal.Show.Show ghc-internal-9.1100.0:GHC.Internal.Event.Manager.FdKey -- Defined in ‘ghc-internal-9.1100.0:GHC.Internal.Event.Manager’
-instance GHC.Internal.Show.Show ghc-internal-9.1100.0:GHC.Internal.Event.Manager.State -- Defined in ‘ghc-internal-9.1100.0:GHC.Internal.Event.Manager’
-instance GHC.Internal.Show.Show ghc-internal-9.1100.0:GHC.Internal.Event.TimerManager.State -- Defined in ‘ghc-internal-9.1100.0:GHC.Internal.Event.TimerManager’
+instance GHC.Internal.Show.Show ghc-internal-9.1300.0:GHC.Internal.Event.Internal.Types.Event -- Defined in ‘ghc-internal-9.1300.0:GHC.Internal.Event.Internal.Types’
+instance GHC.Internal.Show.Show ghc-internal-9.1300.0:GHC.Internal.Event.Internal.Types.EventLifetime -- Defined in ‘ghc-internal-9.1300.0:GHC.Internal.Event.Internal.Types’
+instance GHC.Internal.Show.Show ghc-internal-9.1300.0:GHC.Internal.Event.Internal.Types.Lifetime -- Defined in ‘ghc-internal-9.1300.0:GHC.Internal.Event.Internal.Types’
+instance GHC.Internal.Show.Show ghc-internal-9.1300.0:GHC.Internal.Event.Internal.Types.Timeout -- Defined in ‘ghc-internal-9.1300.0:GHC.Internal.Event.Internal.Types’
+instance GHC.Internal.Show.Show ghc-internal-9.1300.0:GHC.Internal.Event.Manager.FdKey -- Defined in ‘ghc-internal-9.1300.0:GHC.Internal.Event.Manager’
+instance GHC.Internal.Show.Show ghc-internal-9.1300.0:GHC.Internal.Event.Manager.State -- Defined in ‘ghc-internal-9.1300.0:GHC.Internal.Event.Manager’
+instance GHC.Internal.Show.Show ghc-internal-9.1300.0:GHC.Internal.Event.TimerManager.State -- Defined in ‘ghc-internal-9.1300.0:GHC.Internal.Event.TimerManager’
 instance GHC.Internal.Show.Show GHC.Internal.Fingerprint.Type.Fingerprint -- Defined in ‘GHC.Internal.Fingerprint.Type’
 instance GHC.Internal.Show.Show GHC.Types.Double -- Defined in ‘GHC.Internal.Float’
 instance GHC.Internal.Show.Show GHC.Types.Float -- Defined in ‘GHC.Internal.Float’
@@ -12510,7 +12510,7 @@ instance GHC.Internal.Show.Show GHC.Internal.IO.Handle.Types.Handle -- Defined i
 instance GHC.Internal.Show.Show GHC.Internal.IO.Handle.Types.HandleType -- Defined in ‘GHC.Internal.IO.Handle.Types’
 instance GHC.Internal.Show.Show GHC.Internal.IO.Handle.Types.Newline -- Defined in ‘GHC.Internal.IO.Handle.Types’
 instance GHC.Internal.Show.Show GHC.Internal.IO.Handle.Types.NewlineMode -- Defined in ‘GHC.Internal.IO.Handle.Types’
-instance [safe] GHC.Internal.Show.Show ghc-internal-9.1100.0:GHC.Internal.IO.Handle.Lock.Common.FileLockingNotSupported -- Defined in ‘ghc-internal-9.1100.0:GHC.Internal.IO.Handle.Lock.Common’
+instance [safe] GHC.Internal.Show.Show ghc-internal-9.1300.0:GHC.Internal.IO.Handle.Lock.Common.FileLockingNotSupported -- Defined in ‘ghc-internal-9.1300.0:GHC.Internal.IO.Handle.Lock.Common’
 instance GHC.Internal.Show.Show GHC.Internal.IO.Handle.HandlePosn -- Defined in ‘GHC.Internal.IO.Handle’
 instance GHC.Internal.Show.Show GHC.Internal.IO.IOMode.IOMode -- Defined in ‘GHC.Internal.IO.IOMode’
 instance GHC.Internal.Show.Show GHC.Internal.IOPort.IOPortException -- Defined in ‘GHC.Internal.IOPort’
@@ -12607,8 +12607,8 @@ instance GHC.Classes.Eq GHC.Internal.Data.Data.ConstrRep -- Defined in ‘GHC.In
 instance GHC.Classes.Eq GHC.Internal.Data.Data.DataRep -- Defined in ‘GHC.Internal.Data.Data’
 instance GHC.Classes.Eq GHC.Internal.Data.Data.Fixity -- Defined in ‘GHC.Internal.Data.Data’
 instance forall k (s :: k). GHC.Classes.Eq (GHC.Internal.Data.Proxy.Proxy s) -- Defined in ‘GHC.Internal.Data.Proxy’
-instance GHC.Classes.Eq ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.SomeTypeRep -- Defined in ‘ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal’
-instance forall k (a :: k). GHC.Classes.Eq (ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.TypeRep a) -- Defined in ‘ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal’
+instance GHC.Classes.Eq ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.SomeTypeRep -- Defined in ‘ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal’
+instance forall k (a :: k). GHC.Classes.Eq (ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.TypeRep a) -- Defined in ‘ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal’
 instance forall a b. (GHC.Classes.Eq a, GHC.Classes.Eq b) => GHC.Classes.Eq (GHC.Internal.Data.Either.Either a b) -- Defined in ‘GHC.Internal.Data.Either’
 instance forall k (a :: k). GHC.Classes.Eq (Data.Fixed.Fixed a) -- Defined in ‘Data.Fixed’
 instance forall k1 k2 (f :: k1 -> *) (g :: k2 -> k1) (a :: k2). GHC.Classes.Eq (f (g a)) => GHC.Classes.Eq (Data.Functor.Compose.Compose f g a) -- Defined in ‘Data.Functor.Compose’
@@ -12684,13 +12684,13 @@ instance forall a. GHC.Classes.Eq (GHC.Internal.Foreign.C.ConstPtr.ConstPtr a) -
 instance forall i e. (GHC.Internal.Ix.Ix i, GHC.Classes.Eq e) => GHC.Classes.Eq (GHC.Internal.Arr.Array i e) -- Defined in ‘GHC.Internal.Arr’
 instance forall s i e. GHC.Classes.Eq (GHC.Internal.Arr.STArray s i e) -- Defined in ‘GHC.Internal.Arr’
 instance GHC.Classes.Eq GHC.Internal.ByteOrder.ByteOrder -- Defined in ‘GHC.Internal.ByteOrder’
-instance GHC.Classes.Eq ghc-internal-9.1100.0:GHC.Internal.Event.Internal.Types.Event -- Defined in ‘ghc-internal-9.1100.0:GHC.Internal.Event.Internal.Types’
-instance GHC.Classes.Eq ghc-internal-9.1100.0:GHC.Internal.Event.Internal.Types.EventLifetime -- Defined in ‘ghc-internal-9.1100.0:GHC.Internal.Event.Internal.Types’
-instance GHC.Classes.Eq ghc-internal-9.1100.0:GHC.Internal.Event.Internal.Types.Lifetime -- Defined in ‘ghc-internal-9.1100.0:GHC.Internal.Event.Internal.Types’
-instance GHC.Classes.Eq ghc-internal-9.1100.0:GHC.Internal.Event.Manager.FdKey -- Defined in ‘ghc-internal-9.1100.0:GHC.Internal.Event.Manager’
-instance GHC.Classes.Eq ghc-internal-9.1100.0:GHC.Internal.Event.Manager.State -- Defined in ‘ghc-internal-9.1100.0:GHC.Internal.Event.Manager’
+instance GHC.Classes.Eq ghc-internal-9.1300.0:GHC.Internal.Event.Internal.Types.Event -- Defined in ‘ghc-internal-9.1300.0:GHC.Internal.Event.Internal.Types’
+instance GHC.Classes.Eq ghc-internal-9.1300.0:GHC.Internal.Event.Internal.Types.EventLifetime -- Defined in ‘ghc-internal-9.1300.0:GHC.Internal.Event.Internal.Types’
+instance GHC.Classes.Eq ghc-internal-9.1300.0:GHC.Internal.Event.Internal.Types.Lifetime -- Defined in ‘ghc-internal-9.1300.0:GHC.Internal.Event.Internal.Types’
+instance GHC.Classes.Eq ghc-internal-9.1300.0:GHC.Internal.Event.Manager.FdKey -- Defined in ‘ghc-internal-9.1300.0:GHC.Internal.Event.Manager’
+instance GHC.Classes.Eq ghc-internal-9.1300.0:GHC.Internal.Event.Manager.State -- Defined in ‘ghc-internal-9.1300.0:GHC.Internal.Event.Manager’
 instance GHC.Classes.Eq GHC.Internal.Event.TimeOut.TimeoutKey -- Defined in ‘GHC.Internal.Event.TimeOut’
-instance GHC.Classes.Eq ghc-internal-9.1100.0:GHC.Internal.Event.TimerManager.State -- Defined in ‘ghc-internal-9.1100.0:GHC.Internal.Event.TimerManager’
+instance GHC.Classes.Eq ghc-internal-9.1300.0:GHC.Internal.Event.TimerManager.State -- Defined in ‘ghc-internal-9.1300.0:GHC.Internal.Event.TimerManager’
 instance GHC.Classes.Eq GHC.Internal.Stack.Types.SrcLoc -- Defined in ‘GHC.Internal.Stack.Types’
 instance GHC.Classes.Eq GHC.Internal.Exts.SpecConstrAnnotation -- Defined in ‘GHC.Internal.Exts’
 instance GHC.Classes.Eq GHC.Internal.Fingerprint.Type.Fingerprint -- Defined in ‘GHC.Internal.Fingerprint.Type’
@@ -12786,8 +12786,8 @@ instance GHC.Classes.Ord GHC.Internal.Unicode.GeneralCategory -- Defined in ‘G
 instance forall k (a :: k) (b :: k). GHC.Classes.Ord (a GHC.Internal.Data.Type.Equality.:~: b) -- Defined in ‘GHC.Internal.Data.Type.Equality’
 instance forall k1 k2 (a :: k1) (b :: k2). GHC.Classes.Ord (a GHC.Internal.Data.Type.Equality.:~~: b) -- Defined in ‘GHC.Internal.Data.Type.Equality’
 instance forall k (s :: k). GHC.Classes.Ord (GHC.Internal.Data.Proxy.Proxy s) -- Defined in ‘GHC.Internal.Data.Proxy’
-instance GHC.Classes.Ord ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.SomeTypeRep -- Defined in ‘ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal’
-instance forall k (a :: k). GHC.Classes.Ord (ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.TypeRep a) -- Defined in ‘ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal’
+instance GHC.Classes.Ord ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.SomeTypeRep -- Defined in ‘ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal’
+instance forall k (a :: k). GHC.Classes.Ord (ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.TypeRep a) -- Defined in ‘ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal’
 instance forall a b. (GHC.Classes.Ord a, GHC.Classes.Ord b) => GHC.Classes.Ord (GHC.Internal.Data.Either.Either a b) -- Defined in ‘GHC.Internal.Data.Either’
 instance forall k (a :: k). GHC.Classes.Ord (Data.Fixed.Fixed a) -- Defined in ‘Data.Fixed’
 instance forall k1 k2 (f :: k1 -> *) (g :: k2 -> k1) (a :: k2). GHC.Classes.Ord (f (g a)) => GHC.Classes.Ord (Data.Functor.Compose.Compose f g a) -- Defined in ‘Data.Functor.Compose’


=====================================
testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
=====================================
@@ -5285,7 +5285,7 @@ module GHC.Exception where
   type SomeException :: *
   data SomeException = forall e. (Exception e, GHC.Internal.Exception.Type.HasExceptionContext) => SomeException e
   type SrcLoc :: *
-  data SrcLoc = SrcLoc {srcLocPackage :: [GHC.Types.Char], srcLocModule :: [GHC.Types.Char], srcLocFile :: [GHC.Types.Char], srcLocStartLine :: GHC.Types.Int, srcLocStartCol :: GHC.Types.Int, srcLocEndLine :: GHC.Types.Int, srcLocEndCol :: GHC.Types.Int}
+  data SrcLoc = SrcLoc {srcLocPackage :: [GHC.Types.Char], srcLocModule :: [GHC.Types.Char], srcLocFile :: [GHC.Types.Char], srcLocStartLine :: {-# UNPACK #-}GHC.Types.Int, srcLocStartCol :: {-# UNPACK #-}GHC.Types.Int, srcLocEndLine :: {-# UNPACK #-}GHC.Types.Int, srcLocEndCol :: {-# UNPACK #-}GHC.Types.Int}
   divZeroException :: SomeException
   errorCallException :: GHC.Internal.Base.String -> SomeException
   errorCallWithCallStackException :: GHC.Internal.Base.String -> CallStack -> SomeException
@@ -12392,7 +12392,7 @@ module GHC.Stack where
   type HasCallStack :: Constraint
   type HasCallStack = ?callStack::CallStack :: Constraint
   type SrcLoc :: *
-  data SrcLoc = SrcLoc {srcLocPackage :: [GHC.Types.Char], srcLocModule :: [GHC.Types.Char], srcLocFile :: [GHC.Types.Char], srcLocStartLine :: GHC.Types.Int, srcLocStartCol :: GHC.Types.Int, srcLocEndLine :: GHC.Types.Int, srcLocEndCol :: GHC.Types.Int}
+  data SrcLoc = SrcLoc {srcLocPackage :: [GHC.Types.Char], srcLocModule :: [GHC.Types.Char], srcLocFile :: [GHC.Types.Char], srcLocStartLine :: {-# UNPACK #-}GHC.Types.Int, srcLocStartCol :: {-# UNPACK #-}GHC.Types.Int, srcLocEndLine :: {-# UNPACK #-}GHC.Types.Int, srcLocEndCol :: {-# UNPACK #-}GHC.Types.Int}
   callStack :: HasCallStack => CallStack
   ccLabel :: GHC.Internal.Ptr.Ptr CostCentre -> GHC.Types.IO GHC.Internal.Foreign.C.String.Encoding.CString
   ccModule :: GHC.Internal.Ptr.Ptr CostCentre -> GHC.Types.IO GHC.Internal.Foreign.C.String.Encoding.CString
@@ -12453,7 +12453,7 @@ module GHC.Stack.Types where
   type HasCallStack :: Constraint
   type HasCallStack = ?callStack::CallStack :: Constraint
   type SrcLoc :: *
-  data SrcLoc = SrcLoc {srcLocPackage :: [GHC.Types.Char], srcLocModule :: [GHC.Types.Char], srcLocFile :: [GHC.Types.Char], srcLocStartLine :: GHC.Types.Int, srcLocStartCol :: GHC.Types.Int, srcLocEndLine :: GHC.Types.Int, srcLocEndCol :: GHC.Types.Int}
+  data SrcLoc = SrcLoc {srcLocPackage :: [GHC.Types.Char], srcLocModule :: [GHC.Types.Char], srcLocFile :: [GHC.Types.Char], srcLocStartLine :: {-# UNPACK #-}GHC.Types.Int, srcLocStartCol :: {-# UNPACK #-}GHC.Types.Int, srcLocEndLine :: {-# UNPACK #-}GHC.Types.Int, srcLocEndCol :: {-# UNPACK #-}GHC.Types.Int}
   emptyCallStack :: CallStack
   freezeCallStack :: CallStack -> CallStack
   fromCallSiteList :: [([GHC.Types.Char], SrcLoc)] -> CallStack


=====================================
testsuite/tests/interface-stability/base-exports.stdout-mingw32
=====================================
@@ -5462,7 +5462,7 @@ module GHC.Exception where
   type SomeException :: *
   data SomeException = forall e. (Exception e, GHC.Internal.Exception.Type.HasExceptionContext) => SomeException e
   type SrcLoc :: *
-  data SrcLoc = SrcLoc {srcLocPackage :: [GHC.Types.Char], srcLocModule :: [GHC.Types.Char], srcLocFile :: [GHC.Types.Char], srcLocStartLine :: GHC.Types.Int, srcLocStartCol :: GHC.Types.Int, srcLocEndLine :: GHC.Types.Int, srcLocEndCol :: GHC.Types.Int}
+  data SrcLoc = SrcLoc {srcLocPackage :: [GHC.Types.Char], srcLocModule :: [GHC.Types.Char], srcLocFile :: [GHC.Types.Char], srcLocStartLine :: {-# UNPACK #-}GHC.Types.Int, srcLocStartCol :: {-# UNPACK #-}GHC.Types.Int, srcLocEndLine :: {-# UNPACK #-}GHC.Types.Int, srcLocEndCol :: {-# UNPACK #-}GHC.Types.Int}
   divZeroException :: SomeException
   errorCallException :: GHC.Internal.Base.String -> SomeException
   errorCallWithCallStackException :: GHC.Internal.Base.String -> CallStack -> SomeException
@@ -9574,7 +9574,7 @@ module GHC.Stack where
   type HasCallStack :: Constraint
   type HasCallStack = ?callStack::CallStack :: Constraint
   type SrcLoc :: *
-  data SrcLoc = SrcLoc {srcLocPackage :: [GHC.Types.Char], srcLocModule :: [GHC.Types.Char], srcLocFile :: [GHC.Types.Char], srcLocStartLine :: GHC.Types.Int, srcLocStartCol :: GHC.Types.Int, srcLocEndLine :: GHC.Types.Int, srcLocEndCol :: GHC.Types.Int}
+  data SrcLoc = SrcLoc {srcLocPackage :: [GHC.Types.Char], srcLocModule :: [GHC.Types.Char], srcLocFile :: [GHC.Types.Char], srcLocStartLine :: {-# UNPACK #-}GHC.Types.Int, srcLocStartCol :: {-# UNPACK #-}GHC.Types.Int, srcLocEndLine :: {-# UNPACK #-}GHC.Types.Int, srcLocEndCol :: {-# UNPACK #-}GHC.Types.Int}
   callStack :: HasCallStack => CallStack
   ccLabel :: GHC.Internal.Ptr.Ptr CostCentre -> GHC.Types.IO GHC.Internal.Foreign.C.String.Encoding.CString
   ccModule :: GHC.Internal.Ptr.Ptr CostCentre -> GHC.Types.IO GHC.Internal.Foreign.C.String.Encoding.CString
@@ -9635,7 +9635,7 @@ module GHC.Stack.Types where
   type HasCallStack :: Constraint
   type HasCallStack = ?callStack::CallStack :: Constraint
   type SrcLoc :: *
-  data SrcLoc = SrcLoc {srcLocPackage :: [GHC.Types.Char], srcLocModule :: [GHC.Types.Char], srcLocFile :: [GHC.Types.Char], srcLocStartLine :: GHC.Types.Int, srcLocStartCol :: GHC.Types.Int, srcLocEndLine :: GHC.Types.Int, srcLocEndCol :: GHC.Types.Int}
+  data SrcLoc = SrcLoc {srcLocPackage :: [GHC.Types.Char], srcLocModule :: [GHC.Types.Char], srcLocFile :: [GHC.Types.Char], srcLocStartLine :: {-# UNPACK #-}GHC.Types.Int, srcLocStartCol :: {-# UNPACK #-}GHC.Types.Int, srcLocEndLine :: {-# UNPACK #-}GHC.Types.Int, srcLocEndCol :: {-# UNPACK #-}GHC.Types.Int}
   emptyCallStack :: CallStack
   freezeCallStack :: CallStack -> CallStack
   fromCallSiteList :: [([GHC.Types.Char], SrcLoc)] -> CallStack


=====================================
testsuite/tests/interface-stability/base-exports.stdout-ws-32
=====================================
@@ -5316,7 +5316,7 @@ module GHC.Exception where
   type SomeException :: *
   data SomeException = forall e. (Exception e, GHC.Internal.Exception.Type.HasExceptionContext) => SomeException e
   type SrcLoc :: *
-  data SrcLoc = SrcLoc {srcLocPackage :: [GHC.Types.Char], srcLocModule :: [GHC.Types.Char], srcLocFile :: [GHC.Types.Char], srcLocStartLine :: GHC.Types.Int, srcLocStartCol :: GHC.Types.Int, srcLocEndLine :: GHC.Types.Int, srcLocEndCol :: GHC.Types.Int}
+  data SrcLoc = SrcLoc {srcLocPackage :: [GHC.Types.Char], srcLocModule :: [GHC.Types.Char], srcLocFile :: [GHC.Types.Char], srcLocStartLine :: {-# UNPACK #-}GHC.Types.Int, srcLocStartCol :: {-# UNPACK #-}GHC.Types.Int, srcLocEndLine :: {-# UNPACK #-}GHC.Types.Int, srcLocEndCol :: {-# UNPACK #-}GHC.Types.Int}
   divZeroException :: SomeException
   errorCallException :: GHC.Internal.Base.String -> SomeException
   errorCallWithCallStackException :: GHC.Internal.Base.String -> CallStack -> SomeException
@@ -9350,7 +9350,7 @@ module GHC.Stack where
   type HasCallStack :: Constraint
   type HasCallStack = ?callStack::CallStack :: Constraint
   type SrcLoc :: *
-  data SrcLoc = SrcLoc {srcLocPackage :: [GHC.Types.Char], srcLocModule :: [GHC.Types.Char], srcLocFile :: [GHC.Types.Char], srcLocStartLine :: GHC.Types.Int, srcLocStartCol :: GHC.Types.Int, srcLocEndLine :: GHC.Types.Int, srcLocEndCol :: GHC.Types.Int}
+  data SrcLoc = SrcLoc {srcLocPackage :: [GHC.Types.Char], srcLocModule :: [GHC.Types.Char], srcLocFile :: [GHC.Types.Char], srcLocStartLine :: {-# UNPACK #-}GHC.Types.Int, srcLocStartCol :: {-# UNPACK #-}GHC.Types.Int, srcLocEndLine :: {-# UNPACK #-}GHC.Types.Int, srcLocEndCol :: {-# UNPACK #-}GHC.Types.Int}
   callStack :: HasCallStack => CallStack
   ccLabel :: GHC.Internal.Ptr.Ptr CostCentre -> GHC.Types.IO GHC.Internal.Foreign.C.String.Encoding.CString
   ccModule :: GHC.Internal.Ptr.Ptr CostCentre -> GHC.Types.IO GHC.Internal.Foreign.C.String.Encoding.CString
@@ -9411,7 +9411,7 @@ module GHC.Stack.Types where
   type HasCallStack :: Constraint
   type HasCallStack = ?callStack::CallStack :: Constraint
   type SrcLoc :: *
-  data SrcLoc = SrcLoc {srcLocPackage :: [GHC.Types.Char], srcLocModule :: [GHC.Types.Char], srcLocFile :: [GHC.Types.Char], srcLocStartLine :: GHC.Types.Int, srcLocStartCol :: GHC.Types.Int, srcLocEndLine :: GHC.Types.Int, srcLocEndCol :: GHC.Types.Int}
+  data SrcLoc = SrcLoc {srcLocPackage :: [GHC.Types.Char], srcLocModule :: [GHC.Types.Char], srcLocFile :: [GHC.Types.Char], srcLocStartLine :: {-# UNPACK #-}GHC.Types.Int, srcLocStartCol :: {-# UNPACK #-}GHC.Types.Int, srcLocEndLine :: {-# UNPACK #-}GHC.Types.Int, srcLocEndCol :: {-# UNPACK #-}GHC.Types.Int}
   emptyCallStack :: CallStack
   freezeCallStack :: CallStack -> CallStack
   fromCallSiteList :: [([GHC.Types.Char], SrcLoc)] -> CallStack


=====================================
testsuite/tests/linters/Makefile
=====================================
@@ -12,16 +12,16 @@ uniques:
 	python3 checkUniques/check-uniques.py $(TOP)/..
 
 makefiles:
-	(cd $(TOP)/tests/linters/ && python3 regex-linters/check-makefiles.py tracked)
+	(cd $(TOP)/.. && python3 testsuite/tests/linters/regex-linters/check-makefiles.py tracked)
 
 version-number:
 	regex-linters/check-version-number.sh ${TOP}/..
 
 cpp:
-	(cd $(TOP)/tests/linters/ && python3 regex-linters/check-cpp.py tracked)
+	(cd $(TOP)/.. && python3 testsuite/tests/linters/regex-linters/check-cpp.py tracked)
 
 rts-includes:
-	(cd $(TOP)/tests/linters/ && python3 regex-linters/check-rts-includes.py tracked)
+	(cd $(TOP)/.. && python3 testsuite/tests/linters/regex-linters/check-rts-includes.py tracked)
 
 changelogs:
 	regex-linters/check-changelogs.sh $(TOP)/..


=====================================
testsuite/tests/linters/regex-linters/check-cpp.py
=====================================
@@ -13,12 +13,12 @@ linters = [
                  message='CPP macros should not have a space between the macro name and their argument list'),
     RegexpLinter(r'ASSERT2\s+\(',
                  message='CPP macros should not have a space between the macro name and their argument list'),
-    RegexpLinter(r'#ifdef\s+',
-                 message='`#if defined(x)` is preferred to `#ifdef x`'),
+    # RegexpLinter(r'#ifdef\s+',
+    #              message='`#if defined(x)` is preferred to `#ifdef x`'),
     RegexpLinter(r'#if\s+defined\s+',
                  message='`#if defined(x)` is preferred to `#if defined x`'),
-    RegexpLinter(r'#ifndef\s+',
-                 message='`#if !defined(x)` is preferred to `#ifndef x`'),
+    # RegexpLinter(r'#ifndef\s+',
+    #              message='`#if !defined(x)` is preferred to `#ifndef x`'),
 ]
 
 for l in linters:
@@ -29,12 +29,6 @@ for l in linters:
     l.add_path_filter(lambda path: not path.name == 'config.guess')
     # Don't lint files from external xxhash projects
     l.add_path_filter(lambda path: path != Path('rts', 'xxhash.h')),
-    # Don't lint font files
-    l.add_path_filter(lambda path: not path.parent == Path('docs','users_guide',
-        'rtd-theme', 'static', 'fonts'))
-    # Don't lint image files
-    l.add_path_filter(lambda path: not path.parent == Path('docs','users_guide',
-        'images'))
     # Don't lint core spec
     l.add_path_filter(lambda path: not path.name == 'core-spec.pdf')
     # Don't lint the linter itself


=====================================
testsuite/tests/linters/regex-linters/linter.py
=====================================
@@ -40,6 +40,8 @@ def get_changed_files(base_commit: str, head_commit: str,
 
 def get_tracked_files(subdir: str = '.'):
     """ Get the files tracked by git in the given subdirectory. """
+    if not Path(subdir).exists():
+        raise Exception("Regex linter executed with nonexistent target directory '{}'".format(subdir))
     cmd = ['git', 'ls-tree', '--name-only', '-r', 'HEAD', subdir]
     files = subprocess.check_output(cmd)
     return files.decode('UTF-8').split('\n')
@@ -77,9 +79,16 @@ class LineLinter(Linter):
     """
     def lint(self, path: Path):
         if path.is_file():
-            with path.open('r') as f:
-                for line_no, line in enumerate(f):
-                    self.lint_line(path, line_no+1, line)
+            try:
+                with path.open('r') as f:
+                    for line_no, line in enumerate(f):
+                        self.lint_line(path, line_no+1, line)
+            # We don't want to explicitly exclude every single binary file in the test suite
+            except UnicodeDecodeError as e:
+                pass
+            except Exception as e:
+                print('Exception occurred while linting file: {}'.format(path))
+                raise e
 
     def lint_line(self, path: Path, line_no: int, line: str):
         raise NotImplementedError
@@ -124,7 +133,7 @@ def run_linters(linters: Sequence[Linter],
 
     linted_files = args.get_linted_files(args)
     for path in linted_files:
-        if path.startswith('linters'):
+        if path.startswith('testsuite/tests/linters'):
             continue
         for linter in linters:
             linter.do_lint(Path(path))


=====================================
testsuite/tests/perf/compiler/Makefile
=====================================
@@ -21,7 +21,7 @@ MultiModulesRecomp:
 # containing core expressions, aka `mi_extra_decls` are populated.
 MultiModulesRecompDefsWithCore:
 	./genMultiLayerModulesCore
-	'$(TEST_HC)' --interactive $(TEST_HC_OPTS) -e "" -fwrite-if-simplified-core MultiLayerModules
+	'$(TEST_HC)' $(TEST_HC_OPTS_INTERACTIVE) -e "" -fwrite-if-simplified-core MultiLayerModules
 
 MultiModulesDefsWithCore:
 	./genMultiLayerModulesCore


=====================================
testsuite/tests/simd/should_run/T25062_V64.hs
=====================================
@@ -10,7 +10,7 @@ main =
   case foo ( \ x y -> plusDoubleX8# x y ) of
     v -> case unpackDoubleX8# v of
       (# d1, d2, d3, d4, d5, d6, d7, d8 #) ->
-        print [ D# d1, D# d2, D# d3, D# d4, D# d5, D# d6, D# d7, D# d8s ]
+        print [ D# d1, D# d2, D# d3, D# d4, D# d5, D# d6, D# d7, D# d8 ]
 
 {-# NOINLINE foo #-}
 foo :: ( DoubleX8# -> DoubleX8# -> DoubleX8# ) -> DoubleX8#


=====================================
testsuite/tests/simd/should_run/all.T
=====================================
@@ -58,13 +58,26 @@ test('simd014',
 test('T22187', [],compile,[''])
 test('T22187_run', [],compile_and_run,[''])
 test('T25062_V16', [], compile_and_run, [''])
-test('T25062_V32', [ unless(have_cpu_feature('avx2'), skip)
-                   , only_ways(llvm_ways) # SIMD NCG TODO: support 256 bit wide vectors
-                   ]
-                 , compile_and_run, [''])
-test('T25062_V64', [ unless(have_cpu_feature('avx512f'), skip)
-                   , only_ways(llvm_ways) # SIMD NCG TODO: support 512 bit wide vectors
-                   ]
-                 , compile_and_run, [''])
+
+# Even if the CPU we run on doesn't support *executing* those tests we should try to
+# compile them.
+# Currently even for compilation we only support 256+ bit on x86
+only_V32_plus_compilation_support = unless(arch('x86_64'), skip)
+
+test('T25062_V32'
+    ,   [ extra_hc_opts('-mavx2')
+        , only_ways(llvm_ways) # SIMD NCG TODO: support 256+ bit wide vectors
+        , only_V32_plus_compilation_support
+        ]
+    , compile_and_run if have_cpu_feature('avx2') else compile
+    , [''])
+
+test('T25062_V64'
+    ,   [ extra_hc_opts('-mavx512f')
+        , only_ways(llvm_ways) # SIMD NCG TODO: support 256+ bit wide vectors
+        , only_V32_plus_compilation_support
+        ]
+    , compile_and_run if have_cpu_feature('avx512f') else compile
+    , [''])
 
 test('T25169', [], compile_and_run, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f8b0cd3ed18532e6a2a96aeba113a97794cd2666...1b0800955cea97c9f929bbfe22b212624d8b0120

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f8b0cd3ed18532e6a2a96aeba113a97794cd2666...1b0800955cea97c9f929bbfe22b212624d8b0120
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20241104/cdc9eb93/attachment-0001.html>


More information about the ghc-commits mailing list