#3600: Template Haskell mis-coverting empty list to empty string
-------------------------------+--------------------------------------------
Reporter: simonpj | Owner:
Type: bug | Status: new
Priority: normal | Milestone: 6.12.1
Component: Template Haskell | Version: 6.10.4
Severity: normal | Keywords:
Difficulty: Unknown | Testcase:
Os: Unknown/Multiple | Architecture: Unknown/Multiple
-------------------------------+--------------------------------------------
Antoine Latter [email protected] writes: the program Demo.hs compiles on
6.10, but not on 6.12rc1. The output --ddump-splices for 6.10:
{{{
Demo.hs:1:0:
Demo.hs:1:0: Splicing declarations
test
======>
Demo.hs:6:2-5
myFunction[aLQ] = Demo2.testFun []
Ok, modules loaded: Demo2, Main.
}}}
In 6.12rc1:
{{{
Demo.hs:1:0:
Demo.hs:1:0: Splicing declarations
test
======>
Demo.hs:6:2-5
myFunction[aNX] = testFun ""
Demo.hs:6:2:
Couldn't match expected type `[Char]' against inferred type `Char'
Expected type: [String]
Inferred type: [Char]
In the first argument of `testFun', namely `""'
In the expression: testFun ""
Failed, modules loaded: Demo2.
}}}
The code is short:
{{{
---------- Demo.hs ---------------
{-# LANGUAGE TemplateHaskell #-}
module Demo where
import Demo2
$(test)
---------- Demo2.hs ---------------
{-# LANGUAGE TemplateHaskell #-}
module Demo2 where
import Language.Haskell.TH
test :: Q [Dec]
test = do
let args = [] :: [String]
body = [| testFun args |]
decNm <- newName "myFunction"
(:[]) `fmap` funD decNm [clause [] (normalB body) []]
testFun :: [String] -> String
testFun _ = "hello"
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3600>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs