Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
-
350d26d2
by Ben Gamari at 2025-05-08T00:10:36-04:00
-
43396402
by Ben Gamari at 2025-05-08T00:10:36-04:00
-
4dbf5b41
by sheaf at 2025-05-08T00:10:41-04:00
-
0c7147d2
by Ryan Hendrickson at 2025-05-08T00:10:45-04:00
-
3b5267fd
by Cheng Shao at 2025-05-08T00:10:46-04:00
11 changed files:
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/CmmToLlvm/Base.hs
- compiler/GHC/CmmToLlvm/Data.hs
- compiler/GHC/HsToCore/Binds.hs
- + testsuite/tests/typecheck/should_run/T25998.hs
- + testsuite/tests/typecheck/should_run/T25998.stdout
- testsuite/tests/typecheck/should_run/all.T
- utils/haddock/haddock-library/src/Documentation/Haddock/Parser.hs
- utils/haddock/haddock-library/test/Documentation/Haddock/ParserSpec.hs
Changes:
| ... | ... | @@ -1322,6 +1322,7 @@ cross_jobs = [ |
| 1322 | 1322 | modifyJobs
|
| 1323 | 1323 | ( -- See Note [Testing wasm ghci browser mode]
|
| 1324 | 1324 | setVariable "FIREFOX_LAUNCH_OPTS" "{\"browser\":\"firefox\",\"executablePath\":\"/usr/bin/firefox\"}"
|
| 1325 | + . setVariable "CHROME_LAUNCH_OPTS" "{\"browser\":\"chrome\",\"protocol\":\"webDriverBiDi\",\"executablePath\":\"/usr/bin/chromium\",\"args\":[\"--no-sandbox\"]}"
|
|
| 1325 | 1326 | . setVariable "HADRIAN_ARGS" "--docs=no-sphinx-pdfs --docs=no-sphinx-man"
|
| 1326 | 1327 | . delVariable "INSTALL_CONFIGURE_ARGS"
|
| 1327 | 1328 | )
|
| ... | ... | @@ -1786,6 +1786,7 @@ |
| 1786 | 1786 | "BIGNUM_BACKEND": "gmp",
|
| 1787 | 1787 | "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_20-wasm-cross_wasm32-wasi-release+host_fully_static+text_simdutf",
|
| 1788 | 1788 | "BUILD_FLAVOUR": "release+host_fully_static+text_simdutf",
|
| 1789 | + "CHROME_LAUNCH_OPTS": "{\"browser\":\"chrome\",\"protocol\":\"webDriverBiDi\",\"executablePath\":\"/usr/bin/chromium\",\"args\":[\"--no-sandbox\"]}",
|
|
| 1789 | 1790 | "CONFIGURE_ARGS": "--with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check",
|
| 1790 | 1791 | "CROSS_TARGET": "wasm32-wasi",
|
| 1791 | 1792 | "FIREFOX_LAUNCH_OPTS": "{\"browser\":\"firefox\",\"executablePath\":\"/usr/bin/firefox\"}",
|
| ... | ... | @@ -1851,6 +1852,7 @@ |
| 1851 | 1852 | "BIGNUM_BACKEND": "native",
|
| 1852 | 1853 | "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_20-wasm-int_native-cross_wasm32-wasi-release+host_fully_static+text_simdutf",
|
| 1853 | 1854 | "BUILD_FLAVOUR": "release+host_fully_static+text_simdutf",
|
| 1855 | + "CHROME_LAUNCH_OPTS": "{\"browser\":\"chrome\",\"protocol\":\"webDriverBiDi\",\"executablePath\":\"/usr/bin/chromium\",\"args\":[\"--no-sandbox\"]}",
|
|
| 1854 | 1856 | "CONFIGURE_ARGS": "--with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check",
|
| 1855 | 1857 | "CROSS_TARGET": "wasm32-wasi",
|
| 1856 | 1858 | "FIREFOX_LAUNCH_OPTS": "{\"browser\":\"firefox\",\"executablePath\":\"/usr/bin/firefox\"}",
|
| ... | ... | @@ -1916,6 +1918,7 @@ |
| 1916 | 1918 | "BIGNUM_BACKEND": "gmp",
|
| 1917 | 1919 | "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_20-wasm-unreg-cross_wasm32-wasi-release+host_fully_static+text_simdutf",
|
| 1918 | 1920 | "BUILD_FLAVOUR": "release+host_fully_static+text_simdutf",
|
| 1921 | + "CHROME_LAUNCH_OPTS": "{\"browser\":\"chrome\",\"protocol\":\"webDriverBiDi\",\"executablePath\":\"/usr/bin/chromium\",\"args\":[\"--no-sandbox\"]}",
|
|
| 1919 | 1922 | "CONFIGURE_ARGS": "--enable-unregisterised --with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check",
|
| 1920 | 1923 | "CROSS_TARGET": "wasm32-wasi",
|
| 1921 | 1924 | "FIREFOX_LAUNCH_OPTS": "{\"browser\":\"firefox\",\"executablePath\":\"/usr/bin/firefox\"}",
|
| ... | ... | @@ -6031,6 +6034,7 @@ |
| 6031 | 6034 | "BIGNUM_BACKEND": "gmp",
|
| 6032 | 6035 | "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_20-wasm-cross_wasm32-wasi-release+host_fully_static+text_simdutf",
|
| 6033 | 6036 | "BUILD_FLAVOUR": "release+host_fully_static+text_simdutf",
|
| 6037 | + "CHROME_LAUNCH_OPTS": "{\"browser\":\"chrome\",\"protocol\":\"webDriverBiDi\",\"executablePath\":\"/usr/bin/chromium\",\"args\":[\"--no-sandbox\"]}",
|
|
| 6034 | 6038 | "CONFIGURE_ARGS": "--with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check",
|
| 6035 | 6039 | "CROSS_TARGET": "wasm32-wasi",
|
| 6036 | 6040 | "FIREFOX_LAUNCH_OPTS": "{\"browser\":\"firefox\",\"executablePath\":\"/usr/bin/firefox\"}",
|
| ... | ... | @@ -6096,6 +6100,7 @@ |
| 6096 | 6100 | "BIGNUM_BACKEND": "native",
|
| 6097 | 6101 | "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_20-wasm-int_native-cross_wasm32-wasi-release+host_fully_static+text_simdutf",
|
| 6098 | 6102 | "BUILD_FLAVOUR": "release+host_fully_static+text_simdutf",
|
| 6103 | + "CHROME_LAUNCH_OPTS": "{\"browser\":\"chrome\",\"protocol\":\"webDriverBiDi\",\"executablePath\":\"/usr/bin/chromium\",\"args\":[\"--no-sandbox\"]}",
|
|
| 6099 | 6104 | "CONFIGURE_ARGS": "--with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check",
|
| 6100 | 6105 | "CROSS_TARGET": "wasm32-wasi",
|
| 6101 | 6106 | "FIREFOX_LAUNCH_OPTS": "{\"browser\":\"firefox\",\"executablePath\":\"/usr/bin/firefox\"}",
|
| ... | ... | @@ -6161,6 +6166,7 @@ |
| 6161 | 6166 | "BIGNUM_BACKEND": "gmp",
|
| 6162 | 6167 | "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_20-wasm-unreg-cross_wasm32-wasi-release+host_fully_static+text_simdutf",
|
| 6163 | 6168 | "BUILD_FLAVOUR": "release+host_fully_static+text_simdutf",
|
| 6169 | + "CHROME_LAUNCH_OPTS": "{\"browser\":\"chrome\",\"protocol\":\"webDriverBiDi\",\"executablePath\":\"/usr/bin/chromium\",\"args\":[\"--no-sandbox\"]}",
|
|
| 6164 | 6170 | "CONFIGURE_ARGS": "--enable-unregisterised --with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check",
|
| 6165 | 6171 | "CROSS_TARGET": "wasm32-wasi",
|
| 6166 | 6172 | "FIREFOX_LAUNCH_OPTS": "{\"browser\":\"firefox\",\"executablePath\":\"/usr/bin/firefox\"}",
|
| ... | ... | @@ -245,7 +245,7 @@ basicKnownKeyNames |
| 245 | 245 | typeRepIdName,
|
| 246 | 246 | mkTrTypeName,
|
| 247 | 247 | mkTrConName,
|
| 248 | - mkTrAppName,
|
|
| 248 | + mkTrAppCheckedName,
|
|
| 249 | 249 | mkTrFunName,
|
| 250 | 250 | typeSymbolTypeRepName, typeNatTypeRepName, typeCharTypeRepName,
|
| 251 | 251 | trGhcPrimModuleName,
|
| ... | ... | @@ -1356,7 +1356,7 @@ typeableClassName |
| 1356 | 1356 | , someTypeRepDataConName
|
| 1357 | 1357 | , mkTrTypeName
|
| 1358 | 1358 | , mkTrConName
|
| 1359 | - , mkTrAppName
|
|
| 1359 | + , mkTrAppCheckedName
|
|
| 1360 | 1360 | , mkTrFunName
|
| 1361 | 1361 | , typeRepIdName
|
| 1362 | 1362 | , typeNatTypeRepName
|
| ... | ... | @@ -1371,7 +1371,7 @@ someTypeRepDataConName = dcQual gHC_INTERNAL_TYPEABLE_INTERNAL (fsLit "SomeTypeR |
| 1371 | 1371 | typeRepIdName = varQual gHC_INTERNAL_TYPEABLE_INTERNAL (fsLit "typeRep#") typeRepIdKey
|
| 1372 | 1372 | mkTrTypeName = varQual gHC_INTERNAL_TYPEABLE_INTERNAL (fsLit "mkTrType") mkTrTypeKey
|
| 1373 | 1373 | mkTrConName = varQual gHC_INTERNAL_TYPEABLE_INTERNAL (fsLit "mkTrCon") mkTrConKey
|
| 1374 | -mkTrAppName = varQual gHC_INTERNAL_TYPEABLE_INTERNAL (fsLit "mkTrApp") mkTrAppKey
|
|
| 1374 | +mkTrAppCheckedName = varQual gHC_INTERNAL_TYPEABLE_INTERNAL (fsLit "mkTrAppChecked") mkTrAppCheckedKey
|
|
| 1375 | 1375 | mkTrFunName = varQual gHC_INTERNAL_TYPEABLE_INTERNAL (fsLit "mkTrFun") mkTrFunKey
|
| 1376 | 1376 | typeNatTypeRepName = varQual gHC_INTERNAL_TYPEABLE_INTERNAL (fsLit "typeNatTypeRep") typeNatTypeRepKey
|
| 1377 | 1377 | typeSymbolTypeRepName = varQual gHC_INTERNAL_TYPEABLE_INTERNAL (fsLit "typeSymbolTypeRep") typeSymbolTypeRepKey
|
| ... | ... | @@ -2499,7 +2499,7 @@ proxyHashKey = mkPreludeMiscIdUnique 502 |
| 2499 | 2499 | mkTyConKey
|
| 2500 | 2500 | , mkTrTypeKey
|
| 2501 | 2501 | , mkTrConKey
|
| 2502 | - , mkTrAppKey
|
|
| 2502 | + , mkTrAppCheckedKey
|
|
| 2503 | 2503 | , mkTrFunKey
|
| 2504 | 2504 | , typeNatTypeRepKey
|
| 2505 | 2505 | , typeSymbolTypeRepKey
|
| ... | ... | @@ -2509,7 +2509,7 @@ mkTyConKey |
| 2509 | 2509 | mkTyConKey = mkPreludeMiscIdUnique 503
|
| 2510 | 2510 | mkTrTypeKey = mkPreludeMiscIdUnique 504
|
| 2511 | 2511 | mkTrConKey = mkPreludeMiscIdUnique 505
|
| 2512 | -mkTrAppKey = mkPreludeMiscIdUnique 506
|
|
| 2512 | +mkTrAppCheckedKey = mkPreludeMiscIdUnique 506
|
|
| 2513 | 2513 | typeNatTypeRepKey = mkPreludeMiscIdUnique 507
|
| 2514 | 2514 | typeSymbolTypeRepKey = mkPreludeMiscIdUnique 508
|
| 2515 | 2515 | typeCharTypeRepKey = mkPreludeMiscIdUnique 509
|
| ... | ... | @@ -526,10 +526,10 @@ generateExternDecls = do |
| 526 | 526 | modifyEnv $ \env -> env { envAliases = emptyUniqSet }
|
| 527 | 527 | return (concat defss, [])
|
| 528 | 528 | |
| 529 | --- | Is a variable one of the special @$llvm@ globals?
|
|
| 529 | +-- | Is a variable one of the special @\@llvm@ globals?
|
|
| 530 | 530 | isBuiltinLlvmVar :: LlvmVar -> Bool
|
| 531 | 531 | isBuiltinLlvmVar (LMGlobalVar lbl _ _ _ _ _) =
|
| 532 | - "$llvm" `isPrefixOf` unpackFS lbl
|
|
| 532 | + "llvm." `isPrefixOf` unpackFS lbl
|
|
| 533 | 533 | isBuiltinLlvmVar _ = False
|
| 534 | 534 | |
| 535 | 535 | -- | Here we take a global variable definition, rename it with a
|
| ... | ... | @@ -125,7 +125,7 @@ genGlobalLabelArray var_nm clbls = do |
| 125 | 125 | prio = LMStaticLit $ LMIntLit 0xffff i32
|
| 126 | 126 | in LMStaticStrucU [prio, fn, null] entry_ty
|
| 127 | 127 | |
| 128 | - arr_var = LMGlobalVar var_nm arr_ty Internal Nothing Nothing Global
|
|
| 128 | + arr_var = LMGlobalVar var_nm arr_ty Appending Nothing Nothing Global
|
|
| 129 | 129 | mkFunTy lbl = LMFunction $ LlvmFunctionDecl lbl ExternallyVisible CC_Ccc LMVoid FixedArgs [] Nothing
|
| 130 | 130 | entry_ty = LMStructU [i32, LMPointer $ mkFunTy $ fsLit "placeholder", LMPointer i8]
|
| 131 | 131 | arr_ty = LMArray (length clbls) entry_ty
|
| ... | ... | @@ -1850,14 +1850,14 @@ ds_ev_typeable ty (EvTypeableTyApp ev1 ev2) |
| 1850 | 1850 | | Just (t1,t2) <- splitAppTy_maybe ty
|
| 1851 | 1851 | = do { e1 <- getRep ev1 t1
|
| 1852 | 1852 | ; e2 <- getRep ev2 t2
|
| 1853 | - ; mkTrApp <- dsLookupGlobalId mkTrAppName
|
|
| 1854 | - -- mkTrApp :: forall k1 k2 (a :: k1 -> k2) (b :: k1).
|
|
| 1855 | - -- TypeRep a -> TypeRep b -> TypeRep (a b)
|
|
| 1853 | + ; mkTrAppChecked <- dsLookupGlobalId mkTrAppCheckedName
|
|
| 1854 | + -- mkTrAppChecked :: forall k1 k2 (a :: k1 -> k2) (b :: k1).
|
|
| 1855 | + -- TypeRep a -> TypeRep b -> TypeRep (a b)
|
|
| 1856 | 1856 | ; let (_, k1, k2) = splitFunTy (typeKind t1) -- drop the multiplicity,
|
| 1857 | 1857 | -- since it's a kind
|
| 1858 | - ; let expr = mkApps (mkTyApps (Var mkTrApp) [ k1, k2, t1, t2 ])
|
|
| 1858 | + ; let expr = mkApps (mkTyApps (Var mkTrAppChecked) [ k1, k2, t1, t2 ])
|
|
| 1859 | 1859 | [ e1, e2 ]
|
| 1860 | - -- ; pprRuntimeTrace "Trace mkTrApp" (ppr expr) expr
|
|
| 1860 | + -- ; pprRuntimeTrace "Trace mkTrAppChecked" (ppr expr) expr
|
|
| 1861 | 1861 | ; return expr
|
| 1862 | 1862 | }
|
| 1863 | 1863 |
| 1 | +{-# LANGUAGE Haskell2010 #-}
|
|
| 2 | +{-# LANGUAGE KindSignatures #-}
|
|
| 3 | +{-# LANGUAGE ScopedTypeVariables #-}
|
|
| 4 | +{-# LANGUAGE TypeApplications #-}
|
|
| 5 | + |
|
| 6 | +module Main where
|
|
| 7 | + |
|
| 8 | +import Data.Kind
|
|
| 9 | +import Type.Reflection
|
|
| 10 | + |
|
| 11 | +test :: forall (a :: Type) (b :: Type). TypeRep a -> TypeRep b -> String
|
|
| 12 | +test a b = case eqTypeRep a b of
|
|
| 13 | + Just _ -> "Equal!\n"
|
|
| 14 | + Nothing -> "Not equal:\n" <> show a <> "\n" <> show b <> "\n"
|
|
| 15 | + |
|
| 16 | +combine :: forall (t :: Type -> Type -> Type). Typeable t => TypeRep (t Bool Int)
|
|
| 17 | +combine = typeRep
|
|
| 18 | + |
|
| 19 | +main :: IO ()
|
|
| 20 | +main = do
|
|
| 21 | + putStrLn $ test (typeRep @(Bool -> Int)) (combine @(->)) |
| 1 | +Equal!
|
|
| 2 | + |
| ... | ... | @@ -173,6 +173,7 @@ test('T23761', normal, compile_and_run, ['']) |
| 173 | 173 | test('T25529', normal, compile_and_run, [''])
|
| 174 | 174 | test('T23761b', normal, compile_and_run, [''])
|
| 175 | 175 | test('T17594e', normal, compile_and_run, [''])
|
| 176 | +test('T25998', normal, compile_and_run, [''])
|
|
| 176 | 177 | |
| 177 | 178 | # Tests for expanding do before typechecking (Impredicative + RebindableSyntax)
|
| 178 | 179 | test('T18324', normal, compile_and_run, [''])
|
| ... | ... | @@ -795,31 +795,33 @@ stripSpace = fromMaybe <*> mapM strip' |
| 795 | 795 | -- | Parses examples. Examples are a paragraph level entity (separated by an empty line).
|
| 796 | 796 | -- Consecutive examples are accepted.
|
| 797 | 797 | examples :: Parser (DocH mod a)
|
| 798 | -examples = DocExamples <$> (many (try (skipHorizontalSpace *> "\n")) *> go)
|
|
| 798 | +examples = DocExamples <$> (many (try (skipHorizontalSpace *> "\n")) *> go Nothing)
|
|
| 799 | 799 | where
|
| 800 | - go :: Parser [Example]
|
|
| 801 | - go = do
|
|
| 800 | + go :: Maybe Text -> Parser [Example]
|
|
| 801 | + go mbInitialIndent = do
|
|
| 802 | 802 | prefix <- takeHorizontalSpace <* ">>>"
|
| 803 | + initialIndent <- maybe takeHorizontalSpace pure mbInitialIndent
|
|
| 803 | 804 | expr <- takeLine
|
| 804 | - (rs, es) <- resultAndMoreExamples
|
|
| 805 | - return (makeExample prefix expr rs : es)
|
|
| 805 | + (rs, es) <- resultAndMoreExamples (Just initialIndent)
|
|
| 806 | + return (makeExample prefix initialIndent expr rs : es)
|
|
| 807 | + |
|
| 808 | + resultAndMoreExamples :: Maybe Text -> Parser ([Text], [Example])
|
|
| 809 | + resultAndMoreExamples mbInitialIndent = choice' [moreExamples, result, pure ([], [])]
|
|
| 806 | 810 | where
|
| 807 | - resultAndMoreExamples :: Parser ([Text], [Example])
|
|
| 808 | - resultAndMoreExamples = choice' [moreExamples, result, pure ([], [])]
|
|
| 809 | - where
|
|
| 810 | - moreExamples :: Parser ([Text], [Example])
|
|
| 811 | - moreExamples = (,) [] <$> go
|
|
| 811 | + moreExamples :: Parser ([Text], [Example])
|
|
| 812 | + moreExamples = (,) [] <$> go mbInitialIndent
|
|
| 812 | 813 | |
| 813 | - result :: Parser ([Text], [Example])
|
|
| 814 | - result = first . (:) <$> nonEmptyLine <*> resultAndMoreExamples
|
|
| 814 | + result :: Parser ([Text], [Example])
|
|
| 815 | + result = first . (:) <$> nonEmptyLine <*> resultAndMoreExamples Nothing
|
|
| 815 | 816 | |
| 816 | - makeExample :: Text -> Text -> [Text] -> Example
|
|
| 817 | - makeExample prefix expression res =
|
|
| 818 | - Example (T.unpack (T.strip expression)) result
|
|
| 817 | + makeExample :: Text -> Text -> Text -> [Text] -> Example
|
|
| 818 | + makeExample prefix indent expression res =
|
|
| 819 | + Example (T.unpack (tryStripIndent (T.stripEnd expression))) result
|
|
| 819 | 820 | where
|
| 820 | 821 | result = map (T.unpack . substituteBlankLine . tryStripPrefix) res
|
| 821 | 822 | |
| 822 | 823 | tryStripPrefix xs = fromMaybe xs (T.stripPrefix prefix xs)
|
| 824 | + tryStripIndent = liftA2 fromMaybe T.stripStart (T.stripPrefix indent)
|
|
| 823 | 825 | |
| 824 | 826 | substituteBlankLine "<BLANKLINE>" = ""
|
| 825 | 827 | substituteBlankLine xs = xs
|
| ... | ... | @@ -864,6 +864,29 @@ spec = do |
| 864 | 864 | it "accepts unicode in examples" $ do
|
| 865 | 865 | ">>> 灼眼\nシャナ" `shouldParseTo` DocExamples [Example "灼眼" ["シャナ"]]
|
| 866 | 866 | |
| 867 | + it "preserves indentation in consecutive example lines" $ do
|
|
| 868 | + unlines
|
|
| 869 | + [ ">>> line 1"
|
|
| 870 | + , ">>> line 2"
|
|
| 871 | + , ">>> line 3"
|
|
| 872 | + ]
|
|
| 873 | + `shouldParseTo` DocExamples
|
|
| 874 | + [ Example "line 1" []
|
|
| 875 | + , Example " line 2" []
|
|
| 876 | + , Example "line 3" []
|
|
| 877 | + ]
|
|
| 878 | + |
|
| 879 | + it "resets indentation after results" $ do
|
|
| 880 | + unlines
|
|
| 881 | + [ ">>> line 1"
|
|
| 882 | + , "result"
|
|
| 883 | + , ">>> line 2"
|
|
| 884 | + ]
|
|
| 885 | + `shouldParseTo` DocExamples
|
|
| 886 | + [ Example "line 1" ["result"]
|
|
| 887 | + , Example "line 2" []
|
|
| 888 | + ]
|
|
| 889 | + |
|
| 867 | 890 | context "when prompt is prefixed by whitespace" $ do
|
| 868 | 891 | it "strips the exact same amount of whitespace from result lines" $ do
|
| 869 | 892 | unlines
|