[GHC] #13799: -ddump-splices prints out declarations in the wrong order
GHC
ghc-devs at haskell.org
Wed Jun 14 18:51:29 UTC 2017
#13799: -ddump-splices prints out declarations in the wrong order
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Template Haskell | Version: 8.0.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Debugging | Unknown/Multiple
information is incorrect | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by RyanGlScott):
More generally, GHC seems to be pretty cavalier in modifying the
quasiquoted declarations before pretty-printing them. Here's another
example:
{{{#!hs
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeOperators #-}
{-# OPTIONS_GHC -ddump-splices #-}
module Bug where
$([d| infixr 5 :*:
data a :*: b = a :*: b
|])
}}}
{{{
$ /opt/ghc/8.2.1/bin/runghc Bug.hs
Bug.hs:(6,3)-(8,6): Splicing declarations
[d| infixr 5 :*:_a1pB, :*:_a1pA
data a_a1pC :*:_a1pA b_a1pD = a_a1pC :*:_a1pB b_a1pD |]
======>
infixr 5 :*:_a4aj
infixr 5 :*:_a4ai
data (:*:_a4ai) a_a4ak b_a4al = a_a4ak :*:_a4aj b_a4al
Bug.hs:6:3: error:
Multiple fixity declarations for ‘:*:_a4aj’
also at Bug.hs:(6,3)-(8,6)
|
6 | $([d| infixr 5 :*:
| ^^^^^^^^^^^^^^^^...
}}}
Because `(:*:)` is used in both the type and value namespace, GHC seems to
be creating //two// `newName`s for `:*:` behind the hood, and changing the
data/fixity declarations accordingly. (Notice that the fixity declaration
has two identifiers now!) It then proceeds to fail to compile due to
#13054, but that's a separate issue. The issue at hand is that `-ddump-
splices` is printing out internal details in the quasiquoted `[d| ... |]`
declarations, when it really needn't.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13799#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list