[GHC] #13642: GHCi 8.2 simply ignores TH splice using datatype with a forall'd kind signature

#13642: GHCi 8.2 simply ignores TH splice using datatype with a forall'd kind signature -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template | Version: 8.2.1-rc1 Haskell | 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: -------------------------------------+------------------------------------- This is a pretty bizarre behavior I've noticed recently that only happens in GHC 8.2 or later. If you try to use a Template Haskell splice with a very particular feature (a datatype whose kind uses `forall`) in GHCi, then GHCi will flat-out ignore it! {{{ $ /opt/ghc/8.2.1/bin/ghci GHCi, version 8.2.0.20170427: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci λ> :set -XGADTs -XTypeInType -XTemplateHaskell -XRankNTypes λ> import Language.Haskell.TH (stringE, pprint) λ> import Data.Kind (Type) λ> $([d| data Foo :: forall a. a -> Type where MkFoo :: Foo Int |] >>= stringE . pprint) λ> print (5 + length $([d| data Foo :: forall a. a -> Type where MkFoo :: Foo Int |] >>= stringE . pprint)) λ> 5 5 λ> it 5 λ> $([d| data Foo :: forall a. a -> Type where MkFoo :: Foo Int |] >>= stringE . pprint) λ> it 5 }}} Notice how none of my attempts to use the splice seemed to register with GHCi. This isn't really a regression //per se//, since GHC 8.0.1 nor 8.0.2 even allowed you to get that far: {{{ $ /opt/ghc/8.0.2/bin/ghci GHCi, version 8.0.2: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci λ> :set -XGADTs -XTypeInType -XTemplateHaskell -XRankNTypes λ> import Language.Haskell.TH (stringE, pprint) λ> import Data.Kind (Type) λ> $([d| data Foo :: forall a. a -> Type where MkFoo :: Foo Int |] >>= stringE . pprint) <interactive>:4:3: error: Exotic form of kind not (yet) handled by Template Haskell forall a. a -> Type }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13642 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13642: GHCi 8.2 simply ignores TH splice using datatype with a forall'd kind signature -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.2.1-rc1 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): Actually, it extends even beyond GHCi! If you put this into a module: {{{#!hs {-# LANGUAGE GADTs, TypeInType, TemplateHaskell, RankNTypes #-} module Bug where import Data.Kind (Type) import Language.Haskell.TH (stringE, pprint) main :: IO () main = putStrLn $([d| data Foo :: forall a. a -> Type where MkFoo :: Foo Int |] >>= string E . pprint) }}} Then some interesting things happen if you try to compile this. If you try to load it into GHCi, you get this: {{{ $ /opt/ghc/8.2.1/bin/ghci Bug.hs GHCi, version 8.2.0.20170427: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Failed, modules loaded: none. }}} Apparently the module fails to compile, despite the fact that no errors were emitted during compilation. Something similar happens if you directly invoke `ghc` on it: {{{ $ /opt/ghc/8.2.1/bin/ghc Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) $ echo $? 1 }}} Again, no errors are emitted, but compilation definitely fails, since no `.hi` or `.o` files are emitted, and you get an error return code of 1. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13642#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13642: GHCi 8.2 simply ignores TH splice using datatype with a forall'd kind signature -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.2.1-rc1 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): Huh, the culprit is commit ae6e63aa858d663952b67cc9969fd14782d307bb (Fix #12709 by not building bad applications). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13642#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13642: GHCi 8.2 simply ignores TH splice using datatype with a forall'd kind signature -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.2.1-rc1 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 RyanGlScott): * cc: goldfire (added) Comment: After some digging, the function responsible for suppressing the error message appears to be `dsWhenNoErrs`: {{{#!hs dsWhenNoErrs :: DsM a -> (a -> CoreExpr) -> DsM CoreExpr dsWhenNoErrs thing_inside mk_expr = do { (result, no_errs) <- askNoErrsDs thing_inside ; return $ if no_errs then mk_expr result else unitExpr } }}} For whatever reason, `askNoErrsDs` does not appear to be propagating the error message correctly. There's also similar issues with splicing in any other features which Template Haskell doesn't support. For example, you could just as well use `[d| id x = x {-# SCC id #-} |]` in the example above. goldfire, do you have an idea of what's going on here? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13642#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13642: GHCi 8.2 simply ignores TH splice using datatype with a forall'd kind signature -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.2.1-rc1 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 simonpj): I'm on this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13642#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13642: GHCi 8.2 simply ignores TH splice using datatype with a forall'd kind
signature
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Template Haskell | Version: 8.2.1-rc1
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 Simon Peyton Jones

#13642: GHCi 8.2 simply ignores TH splice using datatype with a forall'd kind signature -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: Component: Template Haskell | Version: 8.2.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: th/T13642.hs Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => merge * testcase: => th/T13642.hs Comment: Good stuff. Fixed. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13642#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13642: GHCi 8.2 simply ignores TH splice using datatype with a forall'd kind signature -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Template Haskell | Version: 8.2.1-rc1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: th/T13642.hs Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed * milestone: => 8.2.1 Comment: Merged with c7642debda55509d805036c28c9804f6c587d44b. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13642#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC