diff --git a/testsuite/tests/th/T9022.hs b/testsuite/tests/th/T9022.hs new file mode 100644 index 0000000000000000000000000000000000000000..fc61691da18c973b97f2475e0e68d3de119661f0 --- /dev/null +++ b/testsuite/tests/th/T9022.hs @@ -0,0 +1,20 @@ +module Main where + +import Language.Haskell.TH + +main = putStrLn $ pprint foo + +foo :: Dec +foo = barD + where + barD = FunD ( mkName "bar" ) + [ Clause manyArgs (NormalB barBody) [] ] + + barBody = DoE [letxStmt, retxStmt] + letxStmt = LetS [ ValD (VarP xName) (NormalB $ LitE $ IntegerL 5) [] ] + retxStmt = NoBindS $ AppE returnVarE xVarE + xName = mkName "x" + returnVarE = VarE $ mkName "return" + xVarE = VarE xName + manyArgs = map argP [0..9] + argP n = VarP $ mkName $ "arg" ++ show n diff --git a/testsuite/tests/th/T9022.stdout b/testsuite/tests/th/T9022.stdout new file mode 100644 index 0000000000000000000000000000000000000000..66c6afc9f0e45f45070821e2dca1502df57b28dd --- /dev/null +++ b/testsuite/tests/th/T9022.stdout @@ -0,0 +1,2 @@ +bar arg0 arg1 arg2 arg3 arg4 arg5 arg6 arg7 arg8 arg9 = do {let {x = 5}; + return x} diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 3d040b6e52eda06e9ae118448c088f888c4cca3e..c0c975fd5cc3e6e05276b58216f5a838c76c8363 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -399,3 +399,4 @@ test('T11345', normal, compile_and_run, ['-v0 -dsuppress-uniques']) test('TH_finalizer', normal, compile, ['-v0']) test('T10603', normal, compile, ['-ddump-splices -dsuppress-uniques']) test('T11452', normal, compile_fail, ['-v0']) +test('T9022', normal, compile_and_run, ['-v0'])