blob: 98e8bd021918df310a3a38285a91bf9fc730fcba (
plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
|
{-# LANGUAGE PatternGuards #-}
module Main where
import System.IO
import GHC
import MonadUtils
import Outputable
import Bag (filterBag,isEmptyBag)
import System.Directory (removeFile)
import System.Environment( getArgs )
main::IO()
main = do
let c="module Test where\ndata DataT=MkData {name :: String}\n"
writeFile "Test.hs" c
[libdir] <- getArgs
ok<- runGhc (Just libdir) $ do
dflags <- getSessionDynFlags
setSessionDynFlags dflags
let mn =mkModuleName "Test"
addTarget Target { targetId = TargetModule mn, targetAllowObjCode = True, targetContents = Nothing }
load LoadAllTargets
modSum <- getModSummary mn
p <- parseModule modSum
t <- typecheckModule p
d <- desugarModule t
l <- loadModule d
let ts=typecheckedSource l
-- liftIO (putStr (showSDocDebug (ppr ts)))
let fs=filterBag (isDataCon . snd) ts
return $ not $ isEmptyBag fs
removeFile "Test.hs"
print ok
where
isDataCon (L _ (AbsBinds { abs_binds = bs }))
= not (isEmptyBag (filterBag (isDataCon . snd) bs))
isDataCon (L l (f@FunBind {}))
| (MG (m:_) _ _) <- fun_matches f,
(L _ (c@ConPatOut{}):_)<-hsLMatchPats m,
(L l _)<-pat_con c
= isGoodSrcSpan l -- Check that the source location is a good one
isDataCon _
= False
|