-
Notifications
You must be signed in to change notification settings - Fork 5
/
Copy pathGraphSpec.hs
70 lines (61 loc) · 1.67 KB
/
GraphSpec.hs
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
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
{-# language QuasiQuotes #-}
module GraphSpec where
import Data.String.Interpolate
import GHC
import Test.Hspec
import Graph
import Helper
import Ast
getDeadNames :: IO [String]
getDeadNames = do
ast <- eitherToError $ parse ["Foo.hs"]
let graph = usedTopLevelNames ast
roots <- eitherToError $ return $
findExports ast [mkModuleName "Foo"]
return $ fmap showName $ deadNames graph roots
spec :: Spec
spec = do
describe "deadNames" $ do
it "detects unused top-level names" $ do
withFoo [i|
module Foo (foo) where
foo = ()
bar = ()
|] $ do
getDeadNames `shouldReturn` ["Foo.bar"]
it "allows to specify multiple roots" $ do
withFoo [i|
module Foo (r1, r2) where
r1 = foo
r2 = bar
foo = ()
bar = ()
baz = ()
|] $ do
getDeadNames `shouldReturn` ["Foo.baz"]
it "detects usage of names in instance methods" $ do
withFoo [i|
module Foo () where
data A = A
instance Show A where
show A = foo
foo = "foo"
|] $ do
getDeadNames `shouldReturn` []
it "returns dead names in topological order" $ do
withFoo [i|
module Foo () where
b = c
a = b
c = ()
|] $ do
getDeadNames `shouldReturn` (words "Foo.a Foo.b Foo.c")
it "finds used names in default implementations of methods in class declarations" $ do
withFoo [i|
module Foo () where
class A a where
a :: a -> String
a _ = foo
foo = "foo"
|] $ do
getDeadNames `shouldReturn` []