{-# LANGUAGE GADTs, TemplateHaskell #-}moduleMain(main)whereimportLanguage.Haskell.THtypeS=TdataTawhereMkT::SInt$(return[])main::IO()main=putStrLn$(reify''T>>=stringE.pprint)
gives the following result:
data Main.T (a_0 :: *) where Main.MkT :: Main.T GHC.Types.Int
Shouldn't the return type be Main.S GHC.Types.Int instead?
Trac metadata
Trac field
Value
Version
8.1
Type
Bug
TypeOfFailure
OtherFailure
Priority
normal
Resolution
Unresolved
Component
Template Haskell
Test case
Differential revisions
BlockedBy
Related
Blocking
CC
jstolarek
Operating system
Architecture
To upload designs, you'll need to enable LFS and have an admin enable hashed storage. More information
Child items
0
Show closed items
No child items are currently assigned. Use child items to break down this issue into smaller parts.
The bug might even be deeper than that. If I try using a more complex type synonym:
{-# LANGUAGE GADTs, TemplateHaskell #-}moduleMain(main)whereimportLanguage.Haskell.THtypeSa=TdataTawhereMkT::SCharInt$(return[])main::IO()main=putStrLn$(reify''T>>=stringE.pprint)
then it doesn't tell you that the type indices are both Char and Int:
data Main.T (a_0 :: *) where Main.MkT :: Main.T GHC.Types.Int
The same thing is outputted even when the GADT return type appears as a "type index":
{-# LANGUAGE GADTs, TemplateHaskell #-}moduleMain(main)whereimportLanguage.Haskell.THtypeIda=atypeSa=TdataTawhereMkT::Id(SCharInt)$(return[])main::IO()main=putStrLn$(reify''T>>=stringE.pprint)
That brings up an interesting design question. Is the third field of Gadt (a Name) intended to be the outermost type application, and the fourth field (a [Type]) intended to be the types that to which the Name is applied? If so, then the "type index" returned in the above example is just S Char Int, so how should a Template Haskell programmer know that a is being refined to Int? Presumably, you'd have to do some tricky type arithmetic, which doesn't sit right to me. Perhaps it would be better to change GadtC to this:
dataCon=...|GadtC[Name][BangType]Type[Type]
where the third field contains the return type as written in the source code (in the above example, Id (S Char Int)) and the fourth field contains the type indices after expanding type synonyms (in the above example, Int). Similarly for RecGadtC.
Currently reifying a GADT data constructor tells us "what the user meant", not "what the user wrote", ie. type synonyms are expanded.
I think the most important question is what should the GADT data constructor representation look like. I believe that TH should represent source code syntax. That said, your third example shows that the current representation is not sufficient. So I would propose to represent GADT data constructor as:
dataCon=...|GadtC[Name][StrictType]Type
Where Type is the result type written by the user. In TcSplice.reifyDataCon we have access to dcOrigResTy field of a DataCon, which should allow us to reify original result type.
dataTawhereMkT::a->Ta
Note that by result type of MkT I mean T a, not a -> T a. (I believe dcOrigResTy stores the latter).
In this setting I don't think it is a good idea to store indices inside GadtC. This would duplicate information already stored inside the constructor and make it possible to create inconsistent data constructors.
In this setting I don't think it is a good idea to store indices inside GadtC. This would duplicate information already stored inside the constructor and make it possible to create inconsistent data constructors.
That's a good point I hadn't thought of. We definitely don't want users to be able to splice in type indices that don't match up with the actual return type. I suppose the real type indices can always be found out through something like expand in th-desugar.
That's a good point I hadn't thought of. We definitely don't want users to be able to splice in type indices that don't match up with the actual return type.
Just to be clear: TH syntax tree already allows to write all sorts of silliness that we have to catch later on in the pipeline. This would be another such thing. I just fear that the check would not be trivial. I also think that in most cases GADT result type simply includes indexed type constructor and having to duplicate the indices will be painful.
I suppose the real type indices can always be found out through something like expand in th-desugar.
In such corner cases that you've demonstrated indices might be very hard (impossible?) to recover. But I think that's acceptable.
I just fear that the check would not be trivial. I also think that in most cases GADT result type simply includes indexed type constructor and having to duplicate the indices will be painful.
I agree with you here fully. Also, I hope there's never a case where where a GADT result type isn't an instance of the parent type (modulo type synonyms)—that would be strange indeed!
In such corner cases that you've demonstrated indices might be very hard (impossible?) to recover. But I think that's acceptable.
Again, I wouldn't think there's any case in which you couldn't recover the type indices. The only case where th-desugar's expand function can choke is with type families, but GHC doesn't attempt to expand type families in a GADT definition anyway, so there's nothing to worry about:
$ ghciGHCi, version 7.10.3: http://www.haskell.org/ghc/ :? for helpλ> :set -XTypeFamilies -XGADTsλ> type family Id a where Id a = aλ> data Wat a where Wat :: a -> Id (Wat a)<interactive>:4:18: Data constructor ‘Wat’ returns type ‘Id (Wat a)’ instead of an instance of its parent type ‘Wat a’ In the definition of data constructor ‘Wat’ In the data declaration for ‘Wat’