Skip to content

Commit 9ed4610

Browse files
committed
Add test skeleton & rerename function
1 parent f49d0fe commit 9ed4610

File tree

4 files changed

+144
-0
lines changed

4 files changed

+144
-0
lines changed

extensible-data.cabal

Lines changed: 23 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -106,3 +106,26 @@ executable lam
106106
hs-source-dirs: examples/lam
107107
main-is: Lam.hs
108108
other-modules: LamBase, Typed, DeBruijn
109+
110+
111+
test-suite test-extensible-data
112+
import: deps
113+
type: exitcode-stdio-1.0
114+
hs-source-dirs: test
115+
main-is: tests.hs
116+
other-modules:
117+
Rerename, TestRerename
118+
build-depends:
119+
extensible-data,
120+
containers ^>= 0.6.2.1,
121+
mtl ^>= 2.2.2,
122+
tasty ^>= 1.3.1,
123+
tasty-hunit ^>= 0.10.0.2
124+
default-extensions:
125+
TemplateHaskell, TypeFamilies, PatternSynonyms, ConstraintKinds,
126+
StandaloneDeriving, FlexibleContexts, UndecidableInstances
127+
ghc-options:
128+
-Wno-unused-top-binds
129+
-Wno-missing-pattern-synonym-signatures
130+
-Wno-unused-imports
131+
-Werror=incomplete-patterns

test/Rerename.hs

Lines changed: 73 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,73 @@
1+
{-# LANGUAGE LambdaCase, RecordWildCards #-}
2+
module Rerename
3+
(rerename, rerename', eqTH, neqTH, assertEqTH, assertNeqTH, assertEqTHSelf)
4+
where
5+
6+
import Language.Haskell.TH
7+
import Language.Haskell.TH.Syntax
8+
import Generics.SYB
9+
import Control.Monad.State
10+
import Data.Map.Strict (Map)
11+
import qualified Data.Map.Strict as Map
12+
import Test.Tasty.HUnit
13+
14+
15+
type Rerename = MonadState RerenameState
16+
17+
data RerenameState =
18+
RS { nameMap :: Map Name Name, lastIndex :: Map OccName Int }
19+
20+
-- | Replaces the name suffixes from 'newName' or TH quotes in a deterministic
21+
-- way.
22+
--
23+
-- The name bases are still kept so this doesn't make e.g.
24+
-- @\\x -> x@ and @\\y -> y@ equal! But the result of two different instances
25+
-- of @'newName' \"a\"@ or @[|\\x -> x|]@ will be.
26+
rerename :: Data a => a -> a
27+
rerename x = evalState (rerename' x) (RS Map.empty Map.empty)
28+
29+
rerename' :: (Data a, Rerename m) => a -> m a
30+
rerename' = everywhereM $ mkM rerename1
31+
32+
rerename1 :: Rerename m => Name -> m Name
33+
rerename1 n@(Name b (NameU _)) = do -- from newName or [|...|]
34+
RS {..} <- get
35+
case Map.lookup n nameMap of
36+
Just n' -> pure n'
37+
Nothing -> do
38+
case Map.lookup b lastIndex of
39+
Just i -> do
40+
let n' = mkName $ occString b ++ show i
41+
modify $ \r -> r {nameMap = Map.insert n n' nameMap}
42+
pure n'
43+
Nothing -> do
44+
let n' = mkName $ occString b
45+
put $ RS {nameMap = Map.insert n n' nameMap,
46+
lastIndex = Map.insert b 0 lastIndex}
47+
pure n'
48+
rerename1 n = pure n
49+
50+
infix 4 `eqTH`, `neqTH` -- same as ==, /=
51+
eqTH, neqTH :: (Eq a, Data a) => a -> a -> Bool
52+
x `eqTH` y = rerename x == rerename y
53+
x `neqTH` y = not $ x `eqTH` y
54+
55+
assertEqTHSelf :: (Data a, Eq a, Ppr a) => Q a -> Assertion
56+
assertEqTHSelf x = assertEqTH x x
57+
58+
assertEqTH, assertNeqTH :: (Eq a, Data a, Ppr a)
59+
=> Q a -> Q a -> Assertion
60+
assertEqTH = assertEqTH' "expected" "but got" eqTH
61+
assertNeqTH = assertEqTH' "first" "second" neqTH
62+
63+
assertEqTH' :: Ppr a
64+
=> String -> String -> (a -> a -> Bool)
65+
-> Q a -> Q a -> Assertion
66+
assertEqTH' mx my p qx qy = do
67+
x <- runQ qx; y <- runQ qy
68+
let msg = mx ++ ":\n" ++ indent (pprint x) ++ "\n" ++
69+
my ++ ":\n" ++ indent (pprint y)
70+
assertBool msg (x `p` y)
71+
72+
indent :: String -> String
73+
indent = concatMap $ \case '\n' -> "\n "; c -> [c]

test/TestRerename.hs

Lines changed: 40 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,40 @@
1+
{-# OPTIONS_GHC -Wno-name-shadowing -Wno-unused-matches #-}
2+
{-# LANGUAGE RankNTypes #-}
3+
module TestRerename (tests) where
4+
5+
import Rerename
6+
import Language.Haskell.TH
7+
import Test.Tasty
8+
import Test.Tasty.HUnit
9+
10+
tests :: TestTree
11+
tests = testGroup "Rerename" $
12+
[testCase "newName \"x\"" $ assertEqTHSelf $ newName "x",
13+
testCase "two (newName \"x\")s" $
14+
assertEqTHSelf $
15+
[|($(VarE <$> newName "x"), $(VarE <$> newName "x"))|],
16+
testCase "11" $ assertEqTHSelf [|11|],
17+
testCase "Nothing" $ assertEqTHSelf [|Nothing|],
18+
testCase "id" $ assertEqTHSelf [|id|],
19+
testCase "\\x -> x" $ assertEqTHSelf [|\x -> x|],
20+
testCase "\\x -> x ≠ \\y -> y" $
21+
assertNeqTH [|\x -> x|] [|\y -> y|],
22+
testCase "\\x -> \\x -> x" $
23+
assertEqTHSelf [|\x -> \x -> x|],
24+
25+
testCase "x [pattern]" $ assertEqTHSelf [p|x|],
26+
testCase "Just (x, y) [pattern]" $ assertEqTHSelf [p|Just (x, y)|],
27+
28+
testCase "Either" $ assertEqTHSelf [t|Either|],
29+
testCase "forall a b. Either a b" $
30+
assertEqTHSelf [t|forall a b. Either a b|],
31+
32+
testCase "f x y = (y, x, x)" $
33+
assertEqTHSelf [d|f x y = (y, x, x)|],
34+
testCase "id2 :: a -> a; id2 x = x" $
35+
-- can't have just a type signature by itself :(
36+
assertEqTHSelf [d|id2 :: a -> a; id2 x = x|],
37+
38+
testCase "data Pair a b = Pair a b deriving Eq" $ do
39+
assertEqTHSelf [d|data Pair a b = Pair a b deriving Eq|]
40+
]

test/tests.hs

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,8 @@
1+
module Main (main) where
2+
3+
import Test.Tasty
4+
import qualified TestRerename
5+
6+
main :: IO ()
7+
main = defaultMain $ testGroup "Tests" $
8+
[TestRerename.tests]

0 commit comments

Comments
 (0)