Strange kind error when using Lens.traverseOf

I have this simplified module: module Ganeti.LensPlain where import Control.Lens (LensLike, traverseOf) import Data.Functor.Compose (Compose(..)) traverseOf2 :: LensLike (Compose f g) s t a b -> (a -> f (g b)) -> s -> f (g t) traverseOf2 k f = getCompose . traverseOf k (Compose . f) With ghc-9.2 and later I get this kind error: src/Ganeti/LensPlain.hs:8:32: error: [GHC-25897] • Couldn't match kind ‘k2’ with ‘*’ When matching types Compose f g0 :: * -> * Compose f g :: k2 -> * Expected: s -> Compose f g t Actual: s -> Compose f g0 t0 ‘k2’ is a rigid type variable bound by the type signature for: traverseOf2 :: forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) s (t :: k2) a (b :: k2). LensLike (Compose f g) s t a b -> (a -> f (g b)) -> s -> f (g t) at src/Ganeti/LensPlain.hs:7:1-79 • In the second argument of ‘(.)’, namely ‘traverseOf k (Compose . f)’ In the expression: getCompose . traverseOf k (Compose . f) In an equation for ‘traverseOf2’: traverseOf2 k f = getCompose . traverseOf k (Compose . f) • Relevant bindings include f :: a -> f (g b) (bound at src/Ganeti/LensPlain.hs:8:15) k :: LensLike (Compose f g) s t a b (bound at src/Ganeti/LensPlain.hs:8:13) traverseOf2 :: LensLike (Compose f g) s t a b -> (a -> f (g b)) -> s -> f (g t) (bound at src/Ganeti/LensPlain.hs:8:1) | 8 | traverseOf2 k f = getCompose . traverseOf k (Compose . f) | ^^^^^^^^^^^^^^^^^^^^^^^^^^ GHC-9.0 accepts the code. Also GHC-9.2 accepts it when the module is compiled as part of a larger Cabal project! I thought that (.) would cause the problem, but manually inlining it does not help. I compiled with: $ ghc-9.6.6 -package lens -c src/Ganeti/LensPlain.hs

On Tue, Jul 23, 2024 at 04:51:34PM +0200, Henning Thielemann wrote:
I have this simplified module: [...] src/Ganeti/LensPlain.hs:8:32: error: [GHC-25897] • Couldn't match kind ‘k2’ with ‘*’
GHC-9.0 accepts the code. Also GHC-9.2 accepts it when the module is compiled as part of a larger Cabal project! [...] I compiled with:
$ ghc-9.6.6 -package lens -c src/Ganeti/LensPlain.hs
A major difference between 9.0 and 9.2 is that GHC2021 is enabled by default in 9.2. GHC2021 enables PolyKinds, and presumably what used to be assumed to be * (Type) is now generalized to k2. The simplest solution is probably just to put {-# LANGUAGE NoPolyKinds #-} at the top of LensPlain.hs. The reason it works as part of a Cabal project is that Cabal does not turn on GHC2021 by default. Tom

On Tue, 23 Jul 2024, Tom Ellis wrote:
On Tue, Jul 23, 2024 at 04:51:34PM +0200, Henning Thielemann wrote:
I compiled with:
$ ghc-9.6.6 -package lens -c src/Ganeti/LensPlain.hs
A major difference between 9.0 and 9.2 is that GHC2021 is enabled by default in 9.2. GHC2021 enables PolyKinds, and presumably what used to be assumed to be * (Type) is now generalized to k2.
The simplest solution is probably just to put
{-# LANGUAGE NoPolyKinds #-}
at the top of LensPlain.hs. The reason it works as part of a Cabal project is that Cabal does not turn on GHC2021 by default.
Perfect! That solves the problem and explains everything. I guess I could be surprised for some more weeks.
participants (2)
-
Henning Thielemann
-
Tom Ellis