/testsuite/tests/showIface/DocsInHiFileTH.hs

https://github.com/bgamari/ghc · Haskell · 218 lines · 146 code · 47 blank · 25 comment · 0 complexity · 0bd044f79c8f4716ff292d6534525ba4 MD5 · raw file

  1. {-# LANGUAGE TemplateHaskell, FlexibleInstances, TypeFamilies, DataKinds #-}
  2. {-# LANGUAGE MultiParamTypeClasses, StandaloneKindSignatures, PolyKinds #-}
  3. {-# LANGUAGE PatternSynonyms #-}
  4. -- |This is the module header
  5. module DocInHiFilesTH where
  6. import Language.Haskell.TH
  7. import Language.Haskell.TH.Syntax
  8. import DocsInHiFileTHExternal
  9. f :: Int
  10. f = 42
  11. $(putDoc (DeclDoc 'f) "The meaning of life" >> pure [])
  12. -- |A data type
  13. data Foo =
  14. -- |A constructor
  15. Foo
  16. do
  17. Just "A data type" <- getDoc (DeclDoc ''Foo)
  18. Just "A constructor" <- getDoc (DeclDoc 'Foo)
  19. putDoc (DeclDoc ''Foo) "A new data type"
  20. putDoc (DeclDoc 'Foo) "A new constructor"
  21. Just "A new constructor" <- getDoc (DeclDoc 'Foo)
  22. Just "A new data type" <- getDoc (DeclDoc ''Foo)
  23. pure []
  24. -- |Some documentation
  25. g :: String
  26. g = "Hello world"
  27. do
  28. Just "Some documentation" <- getDoc (DeclDoc 'g)
  29. pure []
  30. -- Testing module headers
  31. do
  32. Just "This is the module header" <- getDoc ModuleDoc
  33. putDoc ModuleDoc "This is the new module header"
  34. Just "This is the new module header" <- getDoc ModuleDoc
  35. pure []
  36. -- Testing argument documentation
  37. h :: Int -- ^Your favourite number
  38. -> Bool -- ^Your favourite element in the Boolean algebra
  39. -> String -- ^A return value
  40. h _ _ = "Hello world"
  41. do
  42. Just "Your favourite number" <- getDoc (ArgDoc 'h 0)
  43. Just "Your favourite element in the Boolean algebra" <- getDoc (ArgDoc 'h 1)
  44. Just "A return value" <- getDoc (ArgDoc 'h 2)
  45. Nothing <- getDoc (ArgDoc 'h 3)
  46. putDoc (ArgDoc 'h 1) "Your least favourite Boolean"
  47. Just "Your least favourite Boolean" <- getDoc (ArgDoc 'h 1)
  48. pure []
  49. -- Testing classes and instances
  50. -- |A fancy class
  51. class C a where
  52. -- |A fancy instance
  53. instance C Int where
  54. instance C String where
  55. class D a where
  56. -- |Another fancy instance
  57. instance D a where
  58. -- |A type family
  59. type family E a
  60. -- |A type family instance
  61. type instance E Bool = Int
  62. i :: E Bool
  63. i = 42
  64. do
  65. Just "A fancy class" <- getDoc (DeclDoc ''C)
  66. Just "A fancy instance" <- getDoc . InstDoc =<< [t| C Int |]
  67. Just "Another fancy instance" <- getDoc (InstDoc (AppT (ConT ''D) (VarT (mkName "a"))))
  68. Just "Another fancy instance" <- getDoc (InstDoc (AppT (ConT ''D) (VarT (mkName "b"))))
  69. Nothing <- getDoc . InstDoc =<< [t| C String |]
  70. putDoc (DeclDoc ''C) "A new class"
  71. putDoc (InstDoc (AppT (ConT ''C) (ConT ''Int))) "A new instance"
  72. putDoc (InstDoc (AppT (ConT ''C) (ConT ''String))) "Another new instance"
  73. putDoc (InstDoc (AppT (ConT ''D) (VarT (mkName "a")))) "Another new instance"
  74. Just "A new class" <- getDoc (DeclDoc ''C)
  75. Just "A new instance" <- getDoc . InstDoc =<< [t| C Int |]
  76. Just "Another new instance" <- getDoc . InstDoc =<< [t| C String |]
  77. Just "Another new instance" <- getDoc (InstDoc (AppT (ConT ''D) (VarT (mkName "a"))))
  78. Just "A type family" <- getDoc (DeclDoc ''E)
  79. -- Doesn't work just yet. See T18241
  80. -- https://gitlab.haskell.org/ghc/ghc/issues/18241
  81. Just "A type family instance" <- getDoc . InstDoc =<< [t| E Bool |]
  82. pure []
  83. -- Testing documentation from external modules
  84. do
  85. Just "This is an external function" <- getDoc (DeclDoc 'externalFunc)
  86. Just "Some integer" <- getDoc (ArgDoc 'externalFunc 0)
  87. Just "This is an external class" <- getDoc (DeclDoc ''ExternalClass)
  88. Just "This is an external instance" <-
  89. getDoc . InstDoc =<< [t| ExternalClass Int |]
  90. pure []
  91. data family WD11 a
  92. type family WD13 a
  93. wd8 = ()
  94. class F
  95. -- Testing combinators
  96. withDecsDoc "1" [d| wd1 x = () |]
  97. withDecsDoc "2" [d| wd2 = () |]
  98. withDecsDoc "3" [d| data WD3 = WD3 |]
  99. withDecsDoc "4" [d| newtype WD4 = WD4 () |]
  100. withDecsDoc "5" [d| type WD5 = () |]
  101. withDecsDoc "6" [d| class WD6 a where |]
  102. withDecsDoc "7" [d| instance C Foo where |]
  103. do
  104. d <- withDecDoc "8" $ sigD 'wd8 [t| () |]
  105. pure [d]
  106. -- this gives 'Illegal variable name: ‘WD9’' when splicing
  107. -- withDoc "9" [sigD ''WD9 [t| Type -> Type |]]
  108. withDecsDoc "10" [d| data family WD10 a|]
  109. withDecsDoc "11" [d| data instance WD11 Foo = WD11Foo |]
  110. withDecsDoc "12" [d| type family WD12 a |]
  111. withDecsDoc "13" [d| type instance WD13 Foo = Int |]
  112. -- testing nullary classes here
  113. withDecsDoc "14" [d| instance F |]
  114. withDecsDoc "15" [d| foreign import ccall "math.h sin" sin :: Double -> Double |]
  115. -- this gives 'Foreign export not (yet) handled by Template Haskell'
  116. -- withDecsDoc "16" [d| foreign export ccall "addInt" (+) :: Int -> Int -> Int |]
  117. wd17 = 42
  118. do
  119. d <- withDecDoc "17" (sigD 'wd17 [t| Int |])
  120. pure [d]
  121. do
  122. let nm = mkName "wd18"
  123. d' <- withDecDoc "18" $ sigD nm [t| Int |]
  124. d <- withDecDoc "19" $ valD (varP nm) (normalB [| 42 |]) []
  125. pure [d, d']
  126. -- Doing this to test that wd20 is documented as "20" and not "2020"
  127. withDecsDoc "20" [d|
  128. wd20 :: Int
  129. wd20 = 42
  130. |]
  131. do
  132. let defBang = bang noSourceUnpackedness noSourceStrictness
  133. patSynVarName <- newName "a"
  134. sequenceA
  135. [ funD_doc (mkName "qux") [clause [ [p| a |], [p| b |] ] (normalB [e| () |]) []]
  136. (Just "This is qux") [Just "Arg uno", Just "Arg dos"]
  137. , dataD_doc (cxt []) (mkName "Quux") [] Nothing
  138. [ ( normalC (mkName "Quux1") [bangType defBang (reifyType ''Int)]
  139. , Just "This is Quux1", [Just "I am an integer"])
  140. , ( normalC (mkName "Quux2")
  141. [ bangType defBang (reifyType ''String)
  142. , bangType defBang (reifyType ''Bool)
  143. ]
  144. , Just "This is Quux2", map Just ["I am a string", "I am a bool"])
  145. ] [] (Just "This is Quux")
  146. , dataD_doc (cxt []) (mkName "Quuz") [] Nothing
  147. [ ( recC (mkName "Quuz") [varBangType (mkName "quuz1_a") (bangType defBang (reifyType ''String))]
  148. , Just "This is a record constructor", [Just "This is the record constructor's argument"])
  149. ] [] (Just "This is a record type")
  150. , newtypeD_doc (cxt []) (mkName "Corge") [] Nothing
  151. ( recC (mkName ("Corge")) [varBangType (mkName "runCorge") (bangType defBang [t| Int |])]
  152. , Just "This is a newtype record constructor", [Just "This is the newtype record constructor's argument"]
  153. ) [] (Just "This is a record newtype")
  154. , dataInstD_doc (cxt []) Nothing [t| WD11 Int |] Nothing
  155. [ ( normalC (mkName "WD11Int") [bangType defBang [t| Int |]]
  156. , Just "This is a data instance constructor", [Just "This is a data instance constructor argument"])
  157. ] [] (Just "This is a data instance")
  158. , newtypeInstD_doc (cxt []) Nothing [t| WD11 Bool |] Nothing
  159. (normalC (mkName "WD11Bool") [bangType defBang [t| Bool |]]
  160. , Just "This is a newtype instance constructor", [Just "This is a newtype instance constructor argument"])
  161. [] (Just "This is a newtype instance")
  162. , patSynD_doc (mkName "Tup2") (prefixPatSyn [patSynVarName]) unidir
  163. [p| ($(varP patSynVarName), $(varP patSynVarName)) |]
  164. (Just "Matches a tuple of (a, a)") [Just "The thing to match twice"]
  165. , withDecDoc "My cool class" $ do
  166. tyVar <- newName "a"
  167. classD (cxt []) (mkName "Pretty") [plainTV tyVar] []
  168. [ withDecDoc "Prettily prints the object" $
  169. sigD (mkName "prettyPrint") [t| $(varT tyVar) -> String |]
  170. ]
  171. ]