Skip to content
This repository has been archived by the owner on Jan 2, 2021. It is now read-only.

Commit

Permalink
Add another TH test
Browse files Browse the repository at this point in the history
  • Loading branch information
maralorn committed Aug 24, 2020
1 parent 370f3fe commit 985268d
Show file tree
Hide file tree
Showing 4 changed files with 34 additions and 0 deletions.
8 changes: 8 additions & 0 deletions test/data/THNewName/A.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,8 @@
{-# LANGUAGE TemplateHaskell #-}

module A (template) where

import Language.Haskell.TH

template :: DecsQ
template = (\consA -> [DataD [] (mkName "A") [] Nothing [NormalC consA []] []]) <$> newName "A"
6 changes: 6 additions & 0 deletions test/data/THNewName/B.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
{-# LANGUAGE TemplateHaskell #-}
module B(A(A)) where

import A

template
6 changes: 6 additions & 0 deletions test/data/THNewName/C.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
{-# OPTIONS_GHC -Wall #-}
{-# LANGUAGE TemplateHaskell #-}
module C where
import B

a = A
14 changes: 14 additions & 0 deletions test/exe/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2274,6 +2274,20 @@ thTests =
_ <- createDoc "A.hs" "haskell" sourceA
_ <- createDoc "B.hs" "haskell" sourceB
expectDiagnostics [ ( "B.hs", [(DsWarning, (4, 0), "Top-level binding with no type signature: main :: IO ()")] ) ]
, testCase "findsTHnewNameConstructor" $ withoutStackEnv $ runWithExtraFiles "THNewName" $ \dir -> do

let cPath = dir </> "C.hs"

-- This test defines a TH value with the meaning "data A = A" in A.hs
-- Loads and export the template in B.hs
-- And checks wether the constructor A can be loaded in C.hs
-- This test does not fail when either A and B get manually loaded before C.hs
-- or when we remove the seemingly unnecessary TH pragma from C.hs
cSource <- liftIO $ readFileUtf8 cPath

_ <- createDoc cPath "haskell" cSource

expectDiagnostics [ ( cPath, [(DsWarning, (5, 0), "Top-level binding with no type signature: a :: A")] ) ]
]

-- | test that TH is reevaluated on typecheck
Expand Down

0 comments on commit 985268d

Please sign in to comment.