To make it short, recent version of GHC broke the very thing we fixed in #11102 (closed) for GHC 8.0. This is utterly frustrating to me. ;-(
Basically, if GHC advertises an extension, it's supposed to work without jumping through hoops if you enable it via {-# LANGUAGE ... #-} or -X-flags. Otherwise this breaks the whole idea of other-extensions and related cabal spec features which use --supported-languages to infer whether e.g. GHC when invoked with -XTemplateHaskell will succeed.
However, consider the Main.hs below
{-# LANGUAGE TemplateHaskell #-}main=$undefined
Unfortuantely now GHC lies unconditionally about supporting TH, thereby undermining the infrastructure we setup in and for #11102 (closed):
$ ghc --supported-languages | grep ^TemplateHaskell$TemplateHaskell$ ghc --make Foo.hs [1 of 1] Compiling Main ( Foo.hs, Foo.o )ghc-stage2: this operation requires -fexternal-interpreter
Trac metadata
Trac field
Value
Version
8.6.3
Type
Bug
TypeOfFailure
OtherFailure
Priority
highest
Resolution
Unresolved
Component
Compiler
Test case
Differential revisions
BlockedBy
Related
Blocking
CC
Operating system
Architecture
To upload designs, you'll need to enable LFS and have an admin enable hashed storage. More information
There are multiple facets that I'm not happy with.
a) GHC is perfectly capable of compiling TH with -fexternal-interpreter (and advertises that this is required for stage1 compiler)
b) Cabal inquires GHC about supported extensions during configure. If we make the response conditional on -fexternal-interpreter, we'll need to pass that flag during configure as well and not just during build.
I could live with the passing of -fexternal-interperter during configure. But GHCs that support TH (via -fexternal-interpreter) to be castrated I'm not so much in favour of. Now 8.6.4 is broken!
Please be very careful with the GHCI define. This does not equate TH support. It means you don't have GHCI only. In a not too distant future we should have stage1 compiler with ghci support. It's almost perfectly doable, although there are some holes. Wormholes to be exact, that will throw it off.
@hvr, what do you think we should do about this? It sounds like either we need to teach Cabal about -fexternal-interpreter or we need to make it the default (which I'm a bit uncomfortable doing since LLVM builds seem to have issues with it).
I think this whole issue is largely overlapping. In #11102 (closed) we said:
For instance, cross-compilers and/or unregisterised GHC builds often don't have TemplateHaskell support. Having support for toggling flags based on availability of -XTemplateHaskell allows cabal to support such environments with less manual intervention.
This however might have been true, but is largely not anymore. GHC is in principle (if one provides an iserv instance) capable of TH. So a stage1 compiler that advertises TemplateHaskell support, is not lying. And as such I would argue the line in this ticket:
Unfortuantely now GHC lies unconditionally about supporting TH
is simply wrong. It's not lying it is capable of TH, but needs an iserv context, which the user needs to supply.
I didn't realize the far reaching consequences if #11102 (closed) and that cabal would then misconfigure the plan and assume I don't have TH, when instead I do have it.
Maybe ghc should not report TemplateHaskell support if invoked with -fno-external-interpreter. That is if I have made a conscious choice not to want -fexternal-interpreter.
Just to add to this. I'm absolutely against this change because it destroys ghc as a TH capable cross compiler from
ghc 8.6.4 onwards, without any option to unbreak it than to reverse this change.
I do understand there are use cases where you don't want TH support, and you'd like Cabal to take some automatic flag configuration based on your GHC.
So previously we claimed to support TH in cross and non-cross settings. This mean that cross compilers could use TH just fine if
they wanted to. That cross compilers are a smaller usecase for GHC right now is a given I assume. Thus the users of cross compilers
can be expected to handle the -fexternal-interpreter requirements themselves. Yes they will not get the same high fidelity experience from Cabal. But they are using cross compilers after all which aren't even that well supported by cabal. They work if the right
wrapper scripts are set up, but otherwise likely wont. The point here is that there is some inherent knowledge required right now to use ghc as a cross compiler with cabal.
At the same time that GHC claimed to support TH, even though the user did not want it to is an annoyance. But did it completely prevent GHC to be used in those cases? Hardly. Sure Cabal failed to do the proper auto-flag configuration, and I see that that is a major annoyance especially after the effort was put in to support this.
Thus I suggest that we add a configure flag to GHC. --disable-template-haskell that will produce a GHC that has absolutely no TH support, and correctly also not advertise this. (We could even auto detect that flag on platforms where we know we don't have any chance of running iserv, that is otuside of linux/bsd/macos/windows with elf/mach-o/pe file formats. We simply don't have the linker on those platforms to even hope to support iserv.
Would it be great if GHC supported some form of "this extension is only supported if you supply -flag -flag -flag"? Sure. Are we there yet? Certainly not.
Back to the topic of iserv. I don't even want cabal to try and auto-setup iserv. I doubt that it can do that in any of the non-trivial cases anyway. What if I need to pass -pgmi... flags and -opti... flags becuse my iserv setup requires that? I doubt cabal can (and should) know these details in those setups.
In the end I don't think ghc should outright kill cross compilation, for the annoyance of wrongfully advertised TempalteHaskell in cases where the intention was to disable TemplateHaskell.
Thus let us please opportunistically advertise TemplateHaskell and provide an option to decidedly disable TemplateHaskell instead of disabling TemplateHaskell outright if it may require an additional flag.
I think we need to step back for a moment and review the state of things since I, for one, am quite lost. Here is my understanding of the background:
--supported-languages is supposed to advertise the set of language extensions unconditionally supported by GHC
TemplateHaskell can be supported via either the internal or external interpreter.
Some platforms (e.g. AIX) support neither the internal interpreter nor the external interpreter; on these platforms TemplateHaskell should be excluded from --supported-languages
Stage1 GHC builds (e.g. as is commonly used for cross-compilation) support the external interpreter but not the internal interpreter; since the external interpreter is only enabled with -fexternal-interpreter, TemplateHaskell is currently excluded from --supported-languages
Moreover, we have two competing philosophies at play:
@angerman argues that in the case of a stage1 cross-compiler TemplateHaskell works just fine; one just needs to pass -fexternal-interpreter. He therefore argues that GHC should advertise TemplateHaskell support.
@hvr articulates Cabal's desire for precise feedback on the capabilities of the compiler as-invoked and on this basis argues that GHC should not advertise TemplateHaskell support (since one would need to pass -fexternal-interpreter to gain use TemplateHaskell).
I see a few ways forward here:
Enable -fexternal-interpreter by default.
Automatically enable -fexternal-interpreter when TemplateHaskell is requested and the internal interpreter is unavailable.
Add a means for GHC to advertise a set of flags which are required for TemplateHaskell support (e.g. add a TemplateHaskell flags field to ghc --info).
While (1) may be a good direction in the long-run I'm a but nervous about doing this in the short term since we have seen external interpreter break on GHCs built with LLVM in the recent past. Moreover, Haskell for Mac apparently has some cases which require the internal interpreter.
This leaves (2) and (3). At the moment I'm leaning towards going with option (2). While it may be slightly surprising to users, (3) seems like a significant amount of work for relatively little payoff.
CPP ambiguity
Somewhat orthogonally, this whole situation is quite muddied by the ambiguous meaning of GHC's GHCI CPP macro:
Most uses within GHC take it to indicate whether the compiler is to include internal interpreter support
Some uses are rather intended to test for whether TemplateHaskell is available; these are wrong since TemplateHaskell may be supported through either the internal or external interpreter
I suggest that we split this into three macros:
HAVE_INTERNAL_INTERPRETER covers whether internal interpreter is supported
HAVE_EXTERNAL_INTERPRETER covers whether the external interpreter is supported
I'm fine with auto-enabling -fexternal-interpreter. And yes the GHCI define becomes less and less useful. Especially as we may soon have stage1 with ghci (given `-fexternal-interpreter), even though only in a limited form for now. I'm all for better/more precise defines.
I have a feeling that (1) and (2) might be the same though. I pass -fexternal-interpreter independent of verifying if the package needs TH or not. If it does not, -fexternal-interpreter has no effect. If it does, it's there. Now we'd probably only want to do that if !defined(HAVE_INTERNAL_INTERPRETER) && defined(HAVE_EXTERNAL_INTERPRETER).