RequiredTypeArguments: application of infix type fails when combined with TemplateHaskell
I am using the master
branch of GHC on commit da2a10ce. That includes a fix for #24570 (closed), so this program now typechecks:
{-# LANGUAGE GHC2024 #-}
{-# LANGUAGE RequiredTypeArguments #-}
{-# LANGUAGE TemplateHaskell #-}
module Foo where
import Language.Haskell.TH
idee :: forall a -> a -> a
idee _ x = x
type (!@#) = Bool
f :: Bool -> Bool
f = idee (!@#)
Surprisingly, however, this variation of f
does not typecheck:
g :: Bool -> Bool
g = $([| idee (!@#) |])
~/Software/ghc/_build/stage1/bin/ghc Foo.hs
[1 of 1] Compiling Foo ( Foo.hs, Foo.o )
Foo.hs:17:6: error: [GHC-55017]
• Illegal data constructor name: ‘!@#’
When splicing a TH expression: Foo.idee (Foo.!@#)
• In the untyped splice: $([| idee (!@#) |])
|
17 | g = $([| idee (!@#) |])
| ^^^^^^^^^^^^^^^^^^
Why is GHC complaining about a data constructor name when (!@#)
is a type name? If you compile this program with -ddump-simpl
, you'll see:
$ ~/Software/ghc/_build/stage1/bin/ghc Foo.hs -ddump-simpl
[1 of 1] Compiling Foo ( Foo.hs, Foo.o )
==================== Simplified expression ====================
Language.Haskell.TH.Lib.Internal.appE
@Language.Haskell.TH.Syntax.Q
Language.Haskell.TH.Syntax.$fQuoteQ
(Language.Haskell.TH.Lib.Internal.varE
@Language.Haskell.TH.Syntax.Q
Language.Haskell.TH.Syntax.$fQuoteQ
(Language.Haskell.TH.Syntax.mkNameG_v
(GHC.CString.unpackCString# "main"#)
(GHC.CString.unpackCString# "Foo"#)
(GHC.CString.unpackCString# "idee"#)))
(Language.Haskell.TH.Lib.Internal.conE
@Language.Haskell.TH.Syntax.Q
Language.Haskell.TH.Syntax.$fQuoteQ
(Language.Haskell.TH.Syntax.mkNameG_tc
(GHC.CString.unpackCString# "main"#)
(GHC.CString.unpackCString# "Foo"#)
(GHC.CString.unpackCString# "!@#"#)))
Which reveals that GHC is desugaring g
to something like this:
g :: Bool -> Bool
g = $(varE 'idee `appE` conE ''(!@#))
I believe conE
is the culprit here. If you look into how conE
is desugared, you'll find that it calls cName
:
cName n = cvtName OccName.dataName n
Where cvtName
is defined as:
cvtName :: OccName.NameSpace -> TH.Name -> CvtM RdrName
cvtName ctxt_ns (TH.Name occ flavour)
| not (okOcc ctxt_ns occ_str) = failWith (IllegalOccName ctxt_ns occ_str)
| otherwise
= do { loc <- getL
; let rdr_name = thRdrName loc ctxt_ns occ_str flavour
; force rdr_name
; return rdr_name }
where
occ_str = TH.occString occ
Note the not (okOcc ctxt_ns occ_str)
check. When calling cName
, ctxt_ns
is dataName
, so this check will only succeed if the supplied Name
is a valid data constructor. ''(!@#)
isn't a valid data constructor Name
, so it fails this check.
Two possible ways of fixing this include:
- Relaxing this check. (I'm not sure what the consequences of this would be.)
- Change the way
RequiredTypeArguments
applications are desugared so that[| idee (!@#) |]
is desugared tovarE 'idee `appE` typeE (conT ''(!@#))
instead. This would have the downside that[| idee (!@#) |]
would be indistinguishable from[| idee (type (!@#$)) |]
after desugaring, however.