GHC 9.0 no longer typechecks a program involving overloaded labels and type applications
In the program that follows, I specify the type of a label by using a visible type application.
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RebindableSyntax #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
module Labels where
-- base
import Prelude
import Data.Kind
( Type )
import GHC.TypeLits
( Symbol, KnownSymbol )
--------------------------------------------------------------------------
data Label (k :: Symbol) (a :: Type) = Label
class IsLabel k a v | v -> a, v -> k where
fromLabel :: v
instance KnownSymbol k => IsLabel k a (Label k a) where
fromLabel = Label @k @a
foo :: Label k a -> ()
foo _ = ()
test :: ()
test = foo ( #label @Bool )
The point of this program is that the label #label
is polymorphic:
#label :: forall (a :: Type). Label "label" a
and I am able to instantiate the type variable a
with a type application.
This program compiles fine on GHC 8.10 (and previous GHC versions), but fails to compile on GHC 9.0 (rc1) with the following error:
Labels.hs:35:14: error:
* Cannot apply expression of type `v0'
to a visible type argument `Bool'
* In the first argument of `foo', namely `(#label @Bool)'
In the expression: foo (#label @Bool)
In an equation for `test': test = foo (#label @Bool)
|
35 | test = foo ( #label @Bool )
| ^^^^^
Can someone enlighten me about what's going on? I found it quite useful to be able to pass further arguments to an overloaded label in this way, whereas I now have to write something like
test :: ()
test = foo ( #label :: Label _ Bool )
to specify a
, which defeats the purpose of the overloaded labels syntax. At that point I might as well just write:
foo ( Label @"label" @Bool )
Edited by sheaf