[GHC] #13199: TH-spliced class instances are pretty-printed incorrectly post-#3384

#13199: TH-spliced class instances are pretty-printed incorrectly post-#3384 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The HsSyn prettyprinter tests patch 499e43824bda967546ebf95ee33ec1f84a114a7c broke the pretty-printing of Template Haskell-spliced class instances. You can see this for yourself by compiling this code with GHC HEAD: {{{#!hs {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TemplateHaskell #-} {-# OPTIONS_GHC -ddump-splices #-} module Bug where class C a b $([d| instance C a (Maybe b) |]) }}} {{{ $ ~/Software/ghc3/inplace/bin/ghc-stage2 --interactive Bug.hs GHCi, version 8.1.20170126: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:(9,3)-(10,6): Splicing declarations [d| instance C a_a1eC (Maybe b_a1eD) |] ======> instance C a_a4m5 Maybe b_a4m6 }}} Note the nonsensical `instance C a_a4m5 Maybe b_a4m6`. For comparison, here is how it should be pretty-printed: {{{ $ /opt/ghc/8.0.2/bin/ghci Bug.hs GHCi, version 8.0.2: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:(9,3)-(10,6): Splicing declarations [d| instance C a_a13N (Maybe b_a13O) |] ======> instance C a_a3Ju (Maybe b_a3Jv) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13199 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13199: TH-spliced class instances are pretty-printed incorrectly post-#3384 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: 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): This change was triggered by [http://git.haskell.org/ghc.git/blobdiff/83d69dca896c7df1f2a36268d5b45c928398... this modification] in `HsTypes`: {{{#!diff diff --git a/compiler/hsSyn/HsTypes.hs b/compiler/hsSyn/HsTypes.hs index 6d82f92..e3e5246 100644 (file) --- a/compiler/hsSyn/HsTypes.hs +++ b/compiler/hsSyn/HsTypes.hs @@ -1279,13 +1313,11 @@ ppr_mono_ty ctxt_prec (HsEqTy ty1 ty2) = maybeParen ctxt_prec TyOpPrec $ ppr_mono_lty TyOpPrec ty1 <+> char '~' <+> ppr_mono_lty TyOpPrec ty2 -ppr_mono_ty ctxt_prec (HsAppsTy tys) - = maybeParen ctxt_prec TyConPrec $ - hsep (map (ppr_app_ty TopPrec . unLoc) tys) +ppr_mono_ty _ctxt_prec (HsAppsTy tys) + = hsep (map (ppr_app_ty TopPrec . unLoc) tys) -ppr_mono_ty ctxt_prec (HsAppTy fun_ty arg_ty) - = maybeParen ctxt_prec TyConPrec $ - hsep [ppr_mono_lty FunPrec fun_ty, ppr_mono_lty TyConPrec arg_ty] +ppr_mono_ty _ctxt_prec (HsAppTy fun_ty arg_ty) + = hsep [ppr_mono_lty FunPrec fun_ty, ppr_mono_lty TyConPrec arg_ty] }}} Adding back the `maybeParen ctxt_prec TyConPrec` part in the `HsAppTy` case fixes the issue for me. However, I suspect you made this change for a reason, alanz - do you know what's going on here? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13199#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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: | -------------------------------------+------------------------------------- Changes (by alanz): * owner: => alanz Comment: I will take a look -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13199#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 alanz): I think this is related to point 3 in the description of https://phabricator.haskell.org/D2752 Basically `HsParTy` appears everywhere it needs to in the `ParsedSource`, but it somehow disappears through the renamer. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13199#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 alanz): Tracing it through, the problem comes inside `runRnSplice`, where we end up (using `showAstData`) with `zonked_q_expr` passing {{{ ... ({ T13199.hs:9:16-28 } (HsAppTy ({ T13199.hs:9:16-18 } (HsAppTy ({ T13199.hs:9:16 } (HsTyVar (NotPromoted) ({ T13199.hs:9:16 }{Name: main:Bug.C{tc row}}))) ({ T13199.hs:9:18 } (HsTyVar (NotPromoted) ({ T13199.hs:9:18 }{Name: a{tv aqF}}))))) ({ T13199.hs:9:20-28 } (HsParTy ({ T13199.hs:9:21-27 } (HsAppTy ({ T13199.hs:9:21-25 } (HsTyVar (NotPromoted) ({ T13199.hs:9:21-25 }{Name: base:GHC.Base.Maybe{(w) tc 3Q}}))) ({ T13199.hs:9:27 } (HsTyVar (NotPromoted) ({ T13199.hs:9:27 }{Name: b{tv aqG}}))))))))) ... }}} to {{{#!hs ; result <- setStage (RunSplice mod_finalizers_ref) $ run_meta zonked_q_expr }}} giving {{{ ... ({ T13199.hs:(9,3)-(10,6) } (HsAppTy ({ T13199.hs:(9,3)-(10,6) } (HsAppTy ({ T13199.hs:(9,3)-(10,6) } (HsTyVar (NotPromoted) ({ <no location info> } (Orig ({abstract:Module}) {OccName: C})))) ({ T13199.hs:(9,3)-(10,6) } (HsTyVar (NotPromoted) ({ T13199.hs:(9,3)-(10,6) } (Exact {Name: a_a3Ub{tv}})))))) ({ T13199.hs:(9,3)-(10,6) } (HsAppTy ({ T13199.hs:(9,3)-(10,6) } (HsTyVar (NotPromoted) ({ <no location info> } (Orig ({abstract:Module}) {OccName: Maybe})))) ({ T13199.hs:(9,3)-(10,6) } (HsTyVar (NotPromoted) ({ T13199.hs:(9,3)-(10,6) } (Exact {Name: b_a3Uc{tv}})))))))) ... }}} So something happening via the `run_meta` process is discarding the `HsParTy`. And in this instance `run_meta` is {{{#!hs runMetaD :: LHsExpr Id -- Of type Q [Dec] -> TcM [LHsDecl RdrName] }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13199#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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... 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... 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... /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

#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): Phab:D3043 Wiki Page: | -------------------------------------+------------------------------------- Changes (by alanz): * differential: => Phab:D3043 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13199#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13199: TH-spliced class instances are pretty-printed incorrectly post-#3384 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: alanz Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3043 Wiki Page: | -------------------------------------+------------------------------------- Changes (by alanz): * status: new => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13199#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC