This commit is contained in:
ryndubei 2024-09-12 13:18:16 +00:00 committed by GitHub
commit 3da1bc492a
No known key found for this signature in database
GPG Key ID: B5690EEEBB952194
6 changed files with 80 additions and 0 deletions

View File

@ -0,0 +1,6 @@
main: test/Spec/TemplateHaskell/TH.hs:22:1: threeQ
main: test/Spec/TemplateHaskell/TH.hs:25:1: intQQ
main: test/Spec/TemplateHaskell/TH.hs:33:1: zero1
main: test/Spec/TemplateHaskell/TH.hs:36:1: zero2
main: test/Spec/TemplateHaskell/TH.hs:39:1: zero3
main: test/Spec/TemplateHaskell/TH.hs:42:1: zero4

View File

View File

@ -0,0 +1,7 @@
roots = [ "Spec.TemplateHaskell.User.root" ]
type-class-roots = false
unused-types = false
root-instances = []

View File

@ -0,0 +1,42 @@
module Spec.TemplateHaskell.TH (intQQ, oneQ, twoQ, two, three, threeQ) where
import Language.Haskell.TH
import Language.Haskell.TH.Quote
oneQ :: Q Exp
oneQ = pure . LitE $ IntegerL one
one :: Integer
one = 1
two :: Int
two = 2
twoQ :: Q Exp
twoQ = pure . VarE $ mkName "two"
three :: Int
three = 3
threeQ :: Q [Dec]
threeQ = pure [ValD (VarP $ mkName "three'") (NormalB . VarE $ mkName "three") []]
intQQ :: QuasiQuoter
intQQ = QuasiQuoter
{ quoteExp = pure . LitE . IntegerL . (zero1 +) . read
, quotePat = pure . LitP . IntegerL . (zero2 +) . read
, quoteType = pure . LitT . NumTyLit . (zero3 +) . read
, quoteDec = pure . pure . (\i -> ValD (VarP $ mkName "quote") (NormalB $ LitE $ IntegerL i) []) . (zero4 +) . read
}
zero1 :: Integer
zero1 = 0
zero2 :: Integer
zero2 = 0
zero3 :: Integer
zero3 = 0
zero4 :: Integer
zero4 = 0

View File

@ -0,0 +1,22 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
module Spec.TemplateHaskell.User where
import Spec.TemplateHaskell.TH
import GHC.TypeLits (Nat)
$(threeQ)
newtype T (a :: Nat) = T Int
root :: T [intQQ|1|]
root = T $ $(oneQ) + [intQQ|1|] + quote + f (1 :: Int) + $(twoQ) + three'
where
f [intQQ|1|] = 1
f _ = 1
quote :: Int
[intQQ|2|]

View File

@ -77,6 +77,7 @@ test-suite weeder-test
, tasty
, tasty-hunit-compat
, tasty-golden
, template-haskell
, text
, toml-reader
, weeder
@ -110,6 +111,8 @@ test-suite weeder-test
Spec.RangeEnum.RangeEnum
Spec.RootClasses.RootClasses
Spec.StandaloneDeriving.StandaloneDeriving
Spec.TemplateHaskell.TH
Spec.TemplateHaskell.User
Spec.TypeAliasGADT.TypeAliasGADT
Spec.TypeDataDecl.TypeDataDecl
Spec.Types.Types