Gating against old GHC in Cabal files

This link has advice about gating against older GHC versions in Cabal files, with this example:

if impl(ghc < 8.4)
  buildable: false
else
  build-depends: base

An example in the wild is the package description for the memory-0.18.0 package (extract):

if impl(ghc < 8.8)
    buildable: False
  else
    build-depends:   base
Build-Depends:     bytestring
                 , memory
                 , basement >= 0.0.7
                 , foundation

What I don’t follow is the use of the else limb in the gate. Why not just:

if impl(ghc < 8.8)
  buildable: false
<description, if buildable>

Is there a substantive reason for the form with the else branch, or can it be understood as a stylistic choice?

1 Like

I hardly see how this is any better than simple build-depends: base > 4.X. Or potentially

if impl(ghc < 8.8)
    build-depends: base < 0

The semantics of buildable IIRC serves different purposes: it prohibits building, but does not force Cabal solver to backtrack and search for another combination of packages. This is useful in certain scenarios, but generally handicaps Cabal.

4 Likes

I don’t know but there’s been a lot ot discussions around this sort of issue in Cabal and Hackage bug trackers over the years and recently. Here’s some links:

1 Like

Thanks for the advice and the links.

I see that one consideration for different approaches is what messages a user might experience during building. I have been experimenting with toy application:

{-# LANGUAGE LexicalNegation #-} -- GHC >= 9.0.1

module Main ( main ) where

main :: IO ()
main = print -1

With no gating, GHC 8.10.7 reports:

> stack --compiler ghc-8.10.7 build
testGate> build (exe) with ghc-8.10.7
Preprocessing executable 'testGate' for testGate-0.1.0.0..
Building executable 'testGate' for testGate-0.1.0.0..

app\Main.hs:1:14: error: Unsupported extension: LexicalNegation
  |
1 | {-# LANGUAGE LexicalNegation #-} -- GHC >= 9.0.1
  |              ^^^^^^^^^^^^^^^

With buildable: false, there is no warning from Cabal (the library) or GHC:

❯ stack --compiler ghc-8.10.7 build
testGate> configure
testGate> Configuring testGate-0.1.0.0...
testGate> build with ghc-8.10.7
testGate> Building testGate-0.1.0.0..

With base < 0, the build tool can warn (in my case, Stack) but the user would need to investigate further why base < 0 has been specified (perhaps by using --allow-newer):

❯ stack --compiler ghc-8.10.7 build

Error: [S-4804]
       Stack failed to construct a build plan.

       While constructing the build plan, Stack encountered the following errors. The
       'Stack configuration' refers to the set of package versions specified by the
       snapshot (after any dropped packages, or pruned GHC boot packages; if a boot
       package is replaced, Stack prunes all other such packages that depend on it)
       and any extra-deps:

       In the dependencies for testGate-0.1.0.0:
         * base must match <0, but base-4.14.3.0 is in the Stack configuration (no
           matching package and version found. Perhaps there is an error in the
           specification of a package's dependencies or build-tools (Hpack) or
           build-depends, build-tools or build-tool-depends (Cabal file) or an
           omission from the packages list in
           D:\Users\mike\Code\Haskell\testGate\stack.yaml (project-level
           configuration).)
       The above is/are needed since testGate is a build target.

       Some different approaches to resolving some or all of this:

         * To ignore all version constraints and build anyway, pass --allow-newer,
           or, in D:\sr\config.yaml (global configuration) or
           D:\Users\mike\Code\Haskell\testGate\stack.yaml (project-level
           configuration), set allow-newer: true.

         * To ignore certain version constraints and build anyway, also add these
           package names under allow-newer-deps: testGate.

Language extensions are supposed to be gated using other-extensions field in Cabal file. In such case building with cabal-install results in

conflict: requires LexicalNegation which is not supported

and stack says

The package requires the following language extensions which are not supported 
by ghc-8.10: LexicalNegation
4 Likes

Thanks for the reference to other-extensions. It seems I should be making greater use of it, as it has that specific gating role.

That Stack message is Stack passing on Cabal’s Distribution.Simple.Error.exceptionMessage UnsupportedLanguageExtension.

I wondered if other-languages would be to default-language as other-extensions is to default-extensions but I found that:

  • other-extensions: while configuring, Cabal outputs a warning (Distribution.PackageDescription.Check.Warning.ppExplanation (UnknownExtensions unknownExtensions)) and then throws the exception.

  • other-languages: while configuring, Cabal outputs a warning (Distribution.PackageDescription.Check.Warning.ppExplanation (UnknownLanguages unknownLanguages)) and then ploughs on to the building step regardless.