[GHC] #13199: TH-spliced class instances are pretty-printed incorrectly post-#3384
GHC
ghc-devs at haskell.org
Sat Jan 28 16:08:26 UTC 2017
#13199: TH-spliced class instances are pretty-printed incorrectly post-#3384
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: alanz
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by RyanGlScott):
Ah, so GHC will only print parentheses around types is an explicit
`HsParTy` is used? In that case, I believe I know what the real culprit
is. If you dig down deep enough to the code that `runMetaD` is running,
you'll eventually come to
[http://git.haskell.org/ghc.git/blob/de78ee6fb77e7505160ab23e6e1b4e66dc87f698:/compiler/hsSyn/Convert.hs#l257
the part] in `Convert` that coverts a Template Haskell `InstanceD` to a
`ClsInstDecl`:
{{{#!hs
cvtDec (InstanceD o ctxt ty decs)
= do { let doc = text "an instance declaration"
; (binds', sigs', fams', ats', adts') <- cvt_ci_decs doc decs
; unless (null fams') (failWith (mkBadDecMsg doc fams'))
; ctxt' <- cvtContext ctxt
; L loc ty' <- cvtType ty
; let inst_ty' = mkHsQualTy ctxt loc ctxt' $ L loc ty'
; returnJustL $ InstD $ ClsInstD $
ClsInstDecl { cid_poly_ty = mkLHsSigType inst_ty'
, cid_binds = binds'
, cid_sigs = Hs.mkClassOpSigs sigs'
, cid_tyfam_insts = ats', cid_datafam_insts = adts'
, cid_overlap_mode = fmap (L loc . overlap) o } }
}}}
In particular, if you trace the value of `ty'` when you run the program
above, it'll give you `instance C a_a4m5 Maybe b_a4m6`. That's because the
original Template Haskell AST for this is:
{{{
λ> import Language.Haskell.TH
λ> putStrLn $([d| instance C a (Maybe b) |] >>= stringE . show)
[InstanceD Nothing [] (AppT (AppT (ConT Bug.C) (VarT
a_6989586621679027494)) (AppT (ConT GHC.Base.Maybe) (VarT
b_6989586621679027495))) []]
}}}
That is, there are no AST nodes to indicate parentheses. That's because
when we originally quoted this declaration earlier, `repTy` (located
[http://git.haskell.org/ghc.git/blob/de78ee6fb77e7505160ab23e6e1b4e66dc87f698:/compiler/deSugar/DsMeta.hs#l1035
here] in `DsMeta`) turns the `HsType` into a Template Haskell `Type`. And
`repTy` has this as one of its cases:
{{{#!hs
repTy (HsParTy t) = repLTy t
}}}
`repTy` strips away all parentheses, and this is by design, according to
[http://git.haskell.org/ghc.git/blob/de78ee6fb77e7505160ab23e6e1b4e66dc87f698:/libraries
/template-haskell/Language/Haskell/TH/Syntax.hs#l1441 this note]:
{{{#!hs
--- * Quoted expressions such as
---
--- > [| a * b + c |] :: Q Exp
--- > [p| a : b : c |] :: Q Pat
--- > [t| T + T |] :: Q Type
---
--- will never contain 'UInfixE', 'UInfixP', 'UInfixT', 'InfixT',
'ParensE',
--- 'ParensP', or 'ParensT' constructors.
}}}
So I believe the proper fix here is //not// to make `repTy` turn an
`HsParTy` into a `ParensT`, but rather to change `cvtType` so that it
inserts `HsParTy`s appropriately as it converts from a TH AST back to an
`HsType`, right?
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13199#comment:5>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list