[GHC] #11345: Template Haskell's handling of infix GADT constructors is broken
GHC
ghc-devs at haskell.org
Mon Jan 4 02:42:16 UTC 2016
#11345: Template Haskell's handling of infix GADT constructors is broken
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Template | Version: 8.1
Haskell |
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: Incorrect result
Unknown/Multiple | at runtime
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
There are several infelicities in the way that Template Haskell treats
GADT constructors that are declared to be infix. To illustrate:
{{{#!hs
{-# LANGUAGE GADTs #-}
{-# LANGUAGE TemplateHaskell #-}
module Main (main) where
import Language.Haskell.TH
infixr 7 :***:
data GADT a where
Prefix :: Int -> Int -> GADT Int
(:***:) :: Int -> Int -> GADT Int
$(return [])
main :: IO ()
main = do
putStrLn $(reify ''GADT >>= stringE . pprint)
putStrLn ""
putStrLn $(reify ''GADT >>= stringE . show)
}}}
This doesn't print out quite what you'd expect:
{{{
data Main.GADT (a_0 :: *)
= Main.Prefix :: GHC.Types.Int ->
GHC.Types.Int -> Main.GADT GHC.Types.Int
| GHC.Types.Int Main.:***: GHC.Types.Int
TyConI (DataD [] Main.GADT [KindedTV a_1627394505 StarT] Nothing [GadtC
[Main.Prefix] [(Bang NoSourceUnpackedness NoSourceStrictness,ConT
GHC.Types.Int),(Bang NoSourceUnpackedness NoSourceStrictness,ConT
GHC.Types.Int)] Main.GADT [ConT GHC.Types.Int],InfixC (Bang
NoSourceUnpackedness NoSourceStrictness,ConT GHC.Types.Int) Main.:***:
(Bang NoSourceUnpackedness NoSourceStrictness,ConT GHC.Types.Int)] [])
}}}
TH thinks that `GADT` is a Haskell98 data declaration when `pprint`-ing it
because `(:***:)` is converted to an `InfixC` (see
[http://git.haskell.org/ghc.git/blob/04f3524f787b2cbd3f460e058c753529d3f2f7ac:/libraries
/template-haskell/Language/Haskell/TH/Ppr.hs#l362 here] for the relevant
code). This causes the output to be a strange hodgepodge of Haskell98 and
GADT syntax.
Another issue is that even though I can reify `GADT`, I can't splice it
back in! Compiling this:
{{{#!hs
{-# LANGUAGE GADTs #-}
{-# LANGUAGE TemplateHaskell #-}
module Main (main) where
import Language.Haskell.TH
$(do gadtName <- newName "GADT"
prefixName <- newName "Prefix"
infixName <- newName ":***:"
a <- newName "a"
return [DataD [] gadtName [KindedTV a StarT] Nothing [GadtC
[prefixName] [(Bang NoSourceUnpackedness NoSourceStrictness,ConT
''Int),(Bang NoSourceUnpackedness NoSourceStrictness,ConT ''Int)] gadtName
[ConT ''Int],InfixC (Bang NoSourceUnpackedness NoSourceStrictness,ConT
''Int) infixName (Bang NoSourceUnpackedness NoSourceStrictness,ConT
''Int)] []])
$(return [])
main :: IO ()
main = do
putStrLn $(reify ''GADT >>= stringE . pprint)
putStrLn ""
putStrLn $(reify ''GADT >>= stringE . show)
}}}
Results in an error:
{{{
InfixGADT.hs:12:3: error:
Cannot mix GADT constructors with Haskell 98 constructors
When splicing a TH declaration:
data GADT_0 (a_1 :: *)
= Prefix_2 :: GHC.Types.Int ->
GHC.Types.Int -> GADT_0 GHC.Types.Int
| GHC.Types.Int :***:_3 GHC.Types.Int
}}}
[http://git.haskell.org/ghc.git/blob/04f3524f787b2cbd3f460e058c753529d3f2f7ac:/compiler/hsSyn/Convert.hs#l191
This code] is responsible. We have an issue where `InfixC` can be either
Haskell98 or GADT syntax depending on the context, but in that particular
context, there's not a good way to determine it.
I can think of three solutions:
1. Add an `InfixGadtC` constructor. This adds more clutter to `Con`, but
is the most straightforward fix.
2. Subsume infix GADT constructors under `GadtC`/`RecGadtC` (depending on
if it has records), and treat `InfixC` as always being Haskell98. This
wouldn't require any API changes, but it does leave a bit of asymmetry
between the Haskell98 and GADT constructors, since there would be three of
the former but two of the latter.
3. A radical approach (which subsumes option 2) would be to deprecate
`InfixC`, subsume it under `NormalC`/`RecC`, and add an `InfixC` pattern
synonym for compatibility. `InfixC` does seem extraneous anyway since you
can just use `reifyFixity` to determine if a constructor is infix. That
way, you have two Haskell98 and two GADT constructors (but you'd also have
to deprecate `InfixC`).
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11345>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list