#3899: -ddump-splices missing parentheses in pattern
---------------------------------+------------------------------------------
Reporter: guest | Owner:
Type: bug | Status: new
Priority: normal | Component: Template Haskell
Version: 6.12.1 | Keywords:
Os: Unknown/Multiple | Testcase:
Architecture: Unknown/Multiple | Failure: None/Unknown
---------------------------------+------------------------------------------
'''Main.hs'''
{{{
{-# LANGUAGE TemplateHaskell #-}
import Language.Haskell.TH
import Control.Monad
data Cons a b = Cons a b
data Nil = Nil
nestedTuple n = do
xs <- replicateM n (newName "x")
return $ LamE [foldr (\v prev -> ConP 'Cons [VarP v,prev]) (ConP 'Nil
[]) xs]
(TupE $ map VarE xs)
}}}
'''Load Main into ghci:'''
{{{
*Main> :set -XTemplateHaskell
*Main> :set -ddump-splices
*Main> :t $(nestedTuple 3)
<interactive>:1:2:
<interactive>:1:2-14: Splicing expression
nestedTuple 3
======>
\ Cons x[aYQ] Cons x[aYR] Cons x[aYS] Nil
-> (x[aYQ], x[aYR], x[aYS])
In the expression: $(nestedTuple 3)
$(nestedTuple 3) :: Cons t (Cons t1 (Cons t2 Nil)) -> (t, t1, t2)
}}}
However the inferred type and behavior of the function suggests that the
Cons constructors are associated to the right.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3899>
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