#4126: Order of members reversed when a template haskell instance declaration
quotation is pretty-printed
---------------------------------+------------------------------------------
Reporter: lilac | Owner:
Type: bug | Status: new
Priority: normal | Component: Template Haskell
Version: 6.12.2 | Keywords:
Os: Unknown/Multiple | Testcase:
Architecture: Unknown/Multiple | Failure: None/Unknown
---------------------------------+------------------------------------------
This broken file:
{{{
{-# LANGUAGE TemplateHaskell #-}
(+1) [d| instance Monad ((,) a) where return = (,) undefined; (a,x) >>= f
= f x |]
}}}
Gives the following error:
{{{
No instance for (Num
(Language.Haskell.TH.Syntax.Q
[Language.Haskell.TH.Syntax.Dec]))
arising from the literal `1' at test.hs:2:2
Possible fix:
add an instance declaration for
(Num
(Language.Haskell.TH.Syntax.Q [Language.Haskell.TH.Syntax.Dec]))
In the second argument of `(+)', namely `1'
In the expression:
(+ 1)
[d|
instance Monad ((,) a) where
{ (a, x) >>= f = f x
return = (,) undefined } |]
}}}
The error has reversed the order of members in the declaration. However,
if I inspect the AST generated from the quotation, they are in the correct
order. Hence I suspect the pretty-printer is reversing them.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4126>
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