[Git][ghc/ghc][wip/az/epa-hsdocty] EPA: exact print HsDocTy

Alan Zimmerman (@alanz) gitlab at gitlab.haskell.org
Sat Jan 7 16:29:56 UTC 2023



Alan Zimmerman pushed to branch wip/az/epa-hsdocty at Glasgow Haskell Compiler / GHC


Commits:
9f18df76 by Alan Zimmerman at 2023-01-07T16:29:41+00:00
EPA: exact print HsDocTy

To match ghc-exactprint
https://github.com/alanz/ghc-exactprint/pull/121

- - - - -


5 changed files:

- + testsuite/tests/printer/HsDocTy.hs
- testsuite/tests/printer/Makefile
- testsuite/tests/printer/all.T
- utils/check-exact/ExactPrint.hs
- utils/check-exact/Main.hs


Changes:

=====================================
testsuite/tests/printer/HsDocTy.hs
=====================================
@@ -0,0 +1,6 @@
+{-# OPTIONS_GHC -haddock #-}
+module HsDocTy where
+
+class C1 a where
+  f1 :: a -> Int
+    -- ^ comment on Int


=====================================
testsuite/tests/printer/Makefile
=====================================
@@ -769,3 +769,9 @@ Test21355:
 Test21805:
 	$(CHECK_PPR)   $(LIBDIR) Test21805.hs
 	$(CHECK_EXACT) $(LIBDIR) Test21805.hs
+
+.PHONY: HsDocTy
+HsDocTy:
+	# See comment on pprWithDocString, this won't round trip
+	# $(CHECK_PPR)   $(LIBDIR) HsDocTy.hs
+	$(CHECK_EXACT) $(LIBDIR) HsDocTy.hs


=====================================
testsuite/tests/printer/all.T
=====================================
@@ -185,4 +185,5 @@ 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'])
 test('T20531', extra_files(['T20531_defs.hs']), ghci_script, ['T20531.script'])
-test('T20531_red_ticks', extra_files(['T20531_defs.hs']), ghci_script, ['T20531_red_ticks.script'])
\ No newline at end of file
+test('T20531_red_ticks', extra_files(['T20531_defs.hs']), ghci_script, ['T20531_red_ticks.script'])
+test('HsDocTy', [ignore_stderr, req_ppr_deps], makefile_test, ['HsDocTy'])
\ No newline at end of file


=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -3898,6 +3898,10 @@ instance ExactPrint (HsType GhcPs) where
   exact (HsSpliceTy a splice) = do
     splice' <- markAnnotated splice
     return (HsSpliceTy a splice')
+  exact (HsDocTy an ty doc) = do
+    ty' <- markAnnotated ty
+    doc' <- markAnnotated doc
+    return (HsDocTy an ty' doc')
   exact (HsBangTy an (HsSrcBang mt up str) ty) = do
     an0 <-
       case mt of


=====================================
utils/check-exact/Main.hs
=====================================
@@ -59,7 +59,7 @@ _tt = testOneFile changers "/home/alanz/mysrc/git.haskell.org/worktree/master/_b
  -- "../../testsuite/tests/ghc-api/exactprint/AddDecl2.hs" (Just changeAddDecl2)
  -- "../../testsuite/tests/ghc-api/exactprint/AddDecl3.hs" (Just changeAddDecl3)
  -- "../../testsuite/tests/ghc-api/exactprint/LocalDecls.hs" (Just changeLocalDecls)
- "../../testsuite/tests/ghc-api/exactprint/LocalDecls2.hs" (Just changeLocalDecls2)
+ -- "../../testsuite/tests/ghc-api/exactprint/LocalDecls2.hs" (Just changeLocalDecls2)
  -- "../../testsuite/tests/ghc-api/exactprint/WhereIn3a.hs" (Just changeWhereIn3a)
  -- "../../testsuite/tests/ghc-api/exactprint/WhereIn3b.hs" (Just changeWhereIn3b)
  -- "../../testsuite/tests/ghc-api/exactprint/AddLocalDecl1.hs" (Just addLocaLDecl1)
@@ -203,6 +203,7 @@ _tt = testOneFile changers "/home/alanz/mysrc/git.haskell.org/worktree/master/_b
  -- "../../testsuite/tests/ghc-api/exactprint/Test20239.hs" Nothing
  -- "../../testsuite/tests/printer/PprArrowLambdaCase.hs" Nothing
  -- "../../testsuite/tests/printer/Test16279.hs" Nothing
+ "../../testsuite/tests/printer/HsDocTy.hs" Nothing
 
 -- cloneT does not need a test, function can be retired
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9f18df76f6e61b72205eb40b97f8debc2949b831

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9f18df76f6e61b72205eb40b97f8debc2949b831
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/20230107/bf5f55bf/attachment-0001.html>


More information about the ghc-commits mailing list