#5454: reify seems to needlessly remove kind ascriptions from type synonym RHSs
---------------------------------+------------------------------------------
    Reporter:  nicolas.frisby    |       Owner:                  
        Type:  feature request   |      Status:  new             
    Priority:  normal            |   Component:  Template Haskell
     Version:  7.2.1             |    Keywords:                  
    Testcase:                    |   Blockedby:                  
          Os:  Unknown/Multiple  |    Blocking:                  
Architecture:  Unknown/Multiple  |     Failure:  None/Unknown    
---------------------------------+------------------------------------------
 I haven't managed to pin down where it happens in the GHC source, but it
 seems that using `TH.reify` to query a type synonym's declaration strips
 out kind ascriptions.

 This smells a bit like
 [http://www.haskell.org/ghc/docs/latest/html/users_guide/data-type-
 extensions.html#type-synonyms LiberalTypeSynonyms ].

 {{{
 {-# LANGUAGE TemplateHaskell, KindSignatures #-}
 module Test where
 import Language.Haskell.TH
 type T x = ((,,) :: * -> * -> * -> *) x x
 reify ''T >>= \x -> runIO (print x) >> return []
 }}}

 emits

 {{{
 TyConI (TySynD Test.T [PlainTV x_1628626975] (AppT (AppT (TupleT 2) (VarT
 x_1628626975)) (VarT x_1628626975)))
 }}}

 upon :loading in ghci 7.0.3.

 My motivation for retaining those kind ascriptions is ticket:5452. I've
 written a TH workaround in order to avoid patching GHC. Adjusting
 `TupleT`s in the head of the unconstrained RHS of a type synonym is
 understandably impossible, but even if I include kind ascriptions in that
 type synonym, the kind inference fails. I tinkered and finally noticed
 that the Info returned by `TH.reify ''T` simply omits the `SigT`.

 Is this an intended behavior? It seems like the TH user could easily strip
 out the `SigT`s if they so wished, and otherwise might want to see them
 (as I do). A show-stopper scenario for this feature request, I imagine, is
 that GHC sheds these ascriptions earlier in its pipeline for some
 terrifyingly clever reason.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5454>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler

_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to