[GHC] #13642: GHCi 8.2 simply ignores TH splice using datatype with a forall'd kind signature
GHC
ghc-devs at haskell.org
Wed May 3 20:21:51 UTC 2017
#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
More information about the ghc-tickets
mailing list