summaryrefslogtreecommitdiff
path: root/testsuite/tests/printer
diff options
context:
space:
mode:
Diffstat (limited to 'testsuite/tests/printer')
-rw-r--r--testsuite/tests/printer/T22488.script5
-rw-r--r--testsuite/tests/printer/T22488.stdout4
-rw-r--r--testsuite/tests/printer/T22488_docHead.hs38
-rw-r--r--testsuite/tests/printer/all.T3
4 files changed, 50 insertions, 0 deletions
diff --git a/testsuite/tests/printer/T22488.script b/testsuite/tests/printer/T22488.script
new file mode 100644
index 0000000000..7e4d10a4c1
--- /dev/null
+++ b/testsuite/tests/printer/T22488.script
@@ -0,0 +1,5 @@
+:set -XDataKinds
+type T = '[ 'x' ]
+:kind! T
+type T = '( 'x', 'y' )
+:kind! T \ No newline at end of file
diff --git a/testsuite/tests/printer/T22488.stdout b/testsuite/tests/printer/T22488.stdout
new file mode 100644
index 0000000000..44e0bd9932
--- /dev/null
+++ b/testsuite/tests/printer/T22488.stdout
@@ -0,0 +1,4 @@
+T :: [Char]
+= '[ 'x']
+T :: (Char, Char)
+= '( 'x', 'y')
diff --git a/testsuite/tests/printer/T22488_docHead.hs b/testsuite/tests/printer/T22488_docHead.hs
new file mode 100644
index 0000000000..7fbc89aa08
--- /dev/null
+++ b/testsuite/tests/printer/T22488_docHead.hs
@@ -0,0 +1,38 @@
+{-# LANGUAGE MagicHash #-}
+
+module Main where
+
+import Prelude hiding ((<>))
+import Data.Foldable (for_, traverse_)
+import Control.Monad (unless)
+import Data.Maybe (listToMaybe)
+import GHC.Data.FastString
+import GHC.Utils.Ppr
+
+check_docHead :: Doc -> IO ()
+check_docHead d = do
+ let str = renderStyle style{mode = LeftMode} d
+ unless (fst (docHead d) == listToMaybe str) $
+ putStrLn $ "Fail: " ++ show str
+
+main :: IO ()
+main =
+ traverse_ check_docHead $
+ units ++ pairs ++ triples ++ misc
+ where
+ units = [id, nest 4] <*> [empty, text "", char 'x']
+ ops = [(<>), (<+>), ($$), ($+$), \a b -> hang a 4 b]
+ pairs = [id, nest 4] <*> (ops <*> units <*> units)
+ triples =
+ (ops <*> pairs <*> units) ++
+ (ops <*> units <*> pairs)
+ misc =
+ [
+ text "xString",
+ ftext (fsLit "xFastString"),
+ ftext (fsLit "") <> char 'x',
+ ztext (zEncodeFS (fsLit "xFastZString")),
+ ztext (zEncodeFS (fsLit "")) <> char 'x',
+ ptext (mkPtrString# "xPtrString"#),
+ ptext (mkPtrString# ""#)
+ ] \ No newline at end of file
diff --git a/testsuite/tests/printer/all.T b/testsuite/tests/printer/all.T
index 29e64f096a..5acd8867ab 100644
--- a/testsuite/tests/printer/all.T
+++ b/testsuite/tests/printer/all.T
@@ -181,3 +181,6 @@ test('Test20315', normal, compile_fail, [''])
test('Test20846', [ignore_stderr, req_ppr_deps], makefile_test, ['Test20846'])
test('Test21355', [ignore_stderr, req_ppr_deps], makefile_test, ['Test21355'])
test('Test21805', [ignore_stderr, req_ppr_deps], makefile_test, ['Test21805'])
+
+test('T22488', normal, ghci_script, ['T22488.script'])
+test('T22488_docHead', normal, compile_and_run, ['-package ghc']) \ No newline at end of file