[Git][ghc/ghc][master] Add tests for #23973 and #26565
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 08bbc028 by Rodrigo Mesquita at 2025-11-20T17:33:54-05:00 Add tests for #23973 and #26565 These were fixed by 4af4f0f070f83f948e49ad5d7835fd91b8d3f0e6 in !10417 - - - - - 7 changed files: - + testsuite/tests/bytecode/T23973.hs - + testsuite/tests/bytecode/T23973.script - + testsuite/tests/bytecode/T23973.stdout - + testsuite/tests/bytecode/T26565.hs - + testsuite/tests/bytecode/T26565.script - + testsuite/tests/bytecode/T26565.stdout - testsuite/tests/bytecode/all.T Changes: ===================================== testsuite/tests/bytecode/T23973.hs ===================================== @@ -0,0 +1,17 @@ +{-# LANGUAGE GADTs #-} +{-# LANGUAGE LinearTypes #-} + +module Main (main) where + +data Ur a where + Ur :: a -> Ur a + +unur :: Ur a -> a +unur (Ur a) = a + +segvGHCi :: Ur () +segvGHCi = Ur $ () + +main :: IO () +main = print (unur segvGHCi) + ===================================== testsuite/tests/bytecode/T23973.script ===================================== @@ -0,0 +1,2 @@ +:l T23973.hs +main ===================================== testsuite/tests/bytecode/T23973.stdout ===================================== @@ -0,0 +1 @@ +() ===================================== testsuite/tests/bytecode/T26565.hs ===================================== @@ -0,0 +1,6 @@ +{-# LANGUAGE LinearTypes #-} +module Test where + +data Ur a where + Ur :: a -> Ur a + ===================================== testsuite/tests/bytecode/T26565.script ===================================== @@ -0,0 +1,3 @@ +:l T26565 +Ur y = (\x -> Ur $ replicate 5 'a') 3 +y ===================================== testsuite/tests/bytecode/T26565.stdout ===================================== @@ -0,0 +1 @@ +"aaaaa" ===================================== testsuite/tests/bytecode/all.T ===================================== @@ -6,6 +6,8 @@ test('T25975', extra_ways(ghci_ways), compile_and_run, # Some of the examples work more robustly with these flags ['-fno-break-points -fno-full-laziness']) +test('T26565', extra_files(["T26565.hs"]), ghci_script, ['T26565.script']) +test('T23973', extra_files(["T23973.hs"]), ghci_script, ['T23973.script']) + # Nullary data constructors test('T26216', extra_files(["T26216_aux.hs"]), ghci_script, ['T26216.script']) - View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/08bbc0287aa215732e07330f29efb563... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/08bbc0287aa215732e07330f29efb563... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Marge Bot (@marge-bot)