[GHC] #11785: Merge types and kinds in Template Haskell (was: Kinds should be treated like types in TcSplice)
GHC
ghc-devs at haskell.org
Mon Jul 17 19:10:12 UTC 2017
#11785: Merge types and kinds in Template Haskell
-------------------------------------+-------------------------------------
Reporter: goldfire | Owner: (none)
Type: task | Status: new
Priority: normal | Milestone:
Component: Template Haskell | Version: 8.1
Resolution: | Keywords: TypeInType
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, there's another way to go about this. Instead of making more
things pure, we could make more things monadic. This can be accomplished
with the following combinator:
{{{#!hs
bindCore :: DsM (Core (TH.Q a)) -> (Core a -> DsM (Core (TH.Q b)))
-> DsM (Core (TH.Q b))
bindCore dsma f
= do { cqa@(MkC qa) <- dsma
; loc <- getSrcSpanDs
; a_name <- newNameAt (mkVarOccFS (fsLit "a")) loc
; let [a_ty] = tcTyConAppArgs (exprType qa)
; let a_id = mkLocalId (localiseName a_name) a_ty
ca = MkC (Var a_id)
; MkC qb <- f ca
; let [b_ty] = tcTyConAppArgs (exprType qb)
; repBindQ a_ty b_ty cqa (MkC (Lam a_id qb)) }
}}}
With `bindCore`, we can retrofit existing uses of `repLKind` with
`repLTy`. Here's one example:
{{{#!diff
diff --git a/compiler/deSugar/DsMeta.hs b/compiler/deSugar/DsMeta.hs
index c679981..8acc6eb 100644
--- a/compiler/deSugar/DsMeta.hs
+++ b/compiler/deSugar/DsMeta.hs
@@ -1043,8 +1044,9 @@ repTy (HsEqTy t1 t2) = do
repTapps eq [t1', t2']
repTy (HsKindSig t k) = do
t1 <- repLTy t
- k1 <- repLKind k
- repTSig t1 k1
+ bindCore (repLTy k) $ repTSig t1
+ -- k1 <- repLKind k
+ -- repTSig t1 k1
repTy (HsSpliceTy splice _) = repSplice splice
repTy (HsExplicitListTy _ _ tys) = do
tys1 <- repLTys tys
}}}
It's somewhat unsavory, but it prevents us from having to change a
truckload of combinators in `Language.Haskell.TH.Lib` to take `KindQ` as
an argument instead of `Kind`.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11785#comment:4>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list