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 #-}moduleLabelswhere-- baseimportPreludeimportData.Kind(Type)importGHC.TypeLits(Symbol,KnownSymbol)--------------------------------------------------------------------------dataLabel(k::Symbol)(a::Type)=LabelclassIsLabelkav|v->a,v->kwherefromLabel::vinstanceKnownSymbolk=>IsLabelka(Labelka)wherefromLabel=Label@k@afoo::Labelka->()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.
Show/hide further context.
This was boiled down from the overloaded label syntax I provide in my shader library, see here.
This added bit of syntax allows users of the library to write shaders in an imperative style, see here for an example.
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:
This is my fault when implementing Quick Look. Should not be hard to fix.
I'm a bit confused by this comment. This is a regression that occurs in 9.0, which lacks Quick Look. How, then, could Quick Look be responsible for this regression?
I'm a bit confused by this comment. This is a regression that occurs in 9.0, which lacks Quick Look.
Ah yes. I think the offending commit is actually this one, which is in 9.0.
commit ffde234854f49dba9ec4735aad74b30fd2deee29Author: Simon Peyton Jones <simonpj@microsoft.com>Date: Wed Apr 8 23:08:12 2020 +0100 Do eager instantation in terms This patch implements eager instantiation, a small but critical change to the type inference engine, #17173. The main change is this:
Anyway it's fixed in HEAD. I suppose we could back-port to 9.0, but I wonder if @trac-sheaf will be content to wait for 9.2?
commit 4196969c53c55191e644d9eb258c14c2bc8467daAuthor: Simon Peyton Jones <simonpj@microsoft.com>Date: Thu Feb 11 14:44:20 2021 +0000 Improve handling of overloaded labels, literals, lists etc When implementing Quick Look I'd failed to remember that overloaded labels, like #foo, should be treated as a "head", so that they can be instantiated with Visible Type Application. This caused #19154. A very similar ticket covers overloaded literals: #19167. This patch fixes both problems, but (annoyingly, albeit temporarily) in two different ways. Overloaded labels I dealt with overloaded labels by buying fully into the Rebindable Syntax approach described in GHC.Hs.Expr Note [Rebindable syntax and HsExpansion]. There is a good overview in GHC.Rename.Expr Note [Handling overloaded and rebindable constructs]. That module contains much of the payload for this patch. Specifically: * Overloaded labels are expanded in the renamer, fixing #19154. See Note [Overloaded labels] in GHC.Rename.Expr. * Left and right sections used to have special code paths in the typechecker and desugarer. Now we just expand them in the renamer. This is harder than it sounds. See GHC.Rename.Expr Note [Left and right sections]. * Infix operator applications are expanded in the typechecker, specifically in GHC.Tc.Gen.App.splitHsApps. See Note [Desugar OpApp in the typechecker] in that module * ExplicitLists are expanded in the renamer, when (and only when) OverloadedLists is on. * HsIf is expanded in the renamer when (and only when) RebindableSyntax is on. Reason: the coverage checker treats HsIf specially. Maybe we could instead expand it unconditionally, and fix up the coverage checker, but I did not attempt that. Overloaded literals Overloaded literals, like numbers (3, 4.2) and strings with OverloadedStrings, were not working correctly with explicit type applications (see #19167). Ideally I'd also expand them in the renamer, like the stuff above, but I drew back on that because they can occur in HsPat as well, and I did not want to to do the HsExpanded thing for patterns. But they *can* now be the "head" of an application in the typechecker, and hence something like ("foo" @T) works now. See GHC.Tc.Gen.Head.tcInferOverLit. It's also done a bit more elegantly, rather than by constructing a new HsExpr and re-invoking the typechecker. There is some refactoring around tcShortCutLit. Ultimately there is more to do here, following the Rebindable Syntax story. There are a lot of knock-on effects: * HsOverLabel and ExplicitList no longer need funny (Maybe SyntaxExpr) fields to support rebindable syntax -- good! * HsOverLabel, OpApp, SectionL, SectionR all become impossible in the output of the typecheker, GhcTc; so we set their extension fields to Void. See GHC.Hs.Expr Note [Constructor cannot occur] * Template Haskell quotes for HsExpanded is a bit tricky. See Note [Quotation and rebindable syntax] in GHC.HsToCore.Quote. * In GHC.HsToCore.Match.viewLExprEq, which groups equal HsExprs for the purpose of pattern-match overlap checking, I found that dictionary evidence for the same type could have two different names. Easily fixed by comparing types not names. * I did quite a bit of annoying fiddling around in GHC.Tc.Gen.Head and GHC.Tc.Gen.App to get error message locations and contexts right, esp in splitHsApps, and the HsExprArg type. Tiresome and not very illuminating. But at least the tricky, higher order, Rebuilder function is gone. * Some refactoring in GHC.Tc.Utils.Monad around contexts and locations for rebindable syntax. * Incidentally fixes #19346, because we now print renamed, rather than typechecked, syntax in error mesages about applications. The commit removes the vestigial module GHC.Builtin.RebindableNames, and thus triggers a 2.4% metric decrease for test MultiLayerModules (#19293). Metric Decrease: MultiLayerModules T12545 compiler/GHC/Builtin/Names.hs | 18 ++-- compiler/GHC/Builtin/RebindableNames.hs | 6 -- compiler/GHC/Builtin/Types/Prim.hs | 34 ++++--- compiler/GHC/Hs/Expr.hs | 190 +++++++++++++++++++++++++++++++--- compiler/GHC/Hs/Utils.hs | 2 +- compiler/GHC/HsToCore/Coverage.hs | 27 ++--- compiler/GHC/HsToCore/Expr.hs | 129 ++++------------------- compiler/GHC/HsToCore/Match.hs | 14 ++- compiler/GHC/HsToCore/Match/Literal.hs | 20 ++-- compiler/GHC/HsToCore/Quote.hs | 40 +++++++- compiler/GHC/Iface/Ext/Ast.hs | 6 +- compiler/GHC/Parser.y | 2 +- compiler/GHC/Parser/PostProcess.hs | 2 +- compiler/GHC/Rename/Env.hs | 77 +++++--------- compiler/GHC/Rename/Expr.hs | 379 ++++++++++++++++++++++++++++++++++++++++++++++++++++++++------------ compiler/GHC/Rename/Splice.hs | 1 - compiler/GHC/Tc/Gen/App.hs | 235 ++++++++++++++++++++++++------------------ compiler/GHC/Tc/Gen/Expr.hs | 282 +++++++++++++++----------------------------------- compiler/GHC/Tc/Gen/Expr.hs-boot | 6 +- compiler/GHC/Tc/Gen/Head.hs | 314 ++++++++++++++++++++++++++++++++++++-------------------- compiler/GHC/Tc/Module.hs | 2 +- compiler/GHC/Tc/TyCl/PatSyn.hs | 2 +- compiler/GHC/Tc/Types/Origin.hs | 4 +- compiler/GHC/Tc/Utils/Instantiate.hs | 64 +++++------- compiler/GHC/Tc/Utils/Monad.hs | 70 ++++++++----- compiler/GHC/Tc/Utils/Zonk.hs | 85 ++++++++++++---- compiler/GHC/ThToHs.hs | 4 +- compiler/GHC/Types/Id.hs | 11 +- compiler/GHC/Types/Id/Make.hs | 87 ++++++++++++++-- compiler/GHC/Types/Var.hs | 14 ++- compiler/Language/Haskell/Syntax/Expr.hs | 155 +--------------------------- compiler/ghc.cabal.in | 1 - testsuite/tests/annotations/should_fail/annfail10.stderr | 12 +-- testsuite/tests/ghci.debugger/Test3.hs | 2 +- testsuite/tests/ghci.debugger/scripts/break017.script | 6 ++ testsuite/tests/ghci.debugger/scripts/break017.stdout | 5 +- testsuite/tests/ghci.debugger/scripts/listCommand001.stdout | 4 +- testsuite/tests/indexed-types/should_fail/T5439.stderr | 3 +- testsuite/tests/indexed-types/should_fail/T7354.stderr | 12 +-- testsuite/tests/linear/should_compile/OldList.hs | 2 + testsuite/tests/overloadedrecflds/ghci/overloadedlabelsghci01.stdout | 2 +- testsuite/tests/overloadedrecflds/should_compile/T19154.hs | 37 +++++++ testsuite/tests/overloadedrecflds/should_compile/all.T | 2 + testsuite/tests/overloadedrecflds/should_fail/overloadedlabelsfail01.stderr | 2 +- testsuite/tests/parser/should_compile/T2245.stderr | 4 +- testsuite/tests/parser/should_compile/T515.stderr | 12 +-- testsuite/tests/rebindable/T19167.hs | 29 ++++++ testsuite/tests/rebindable/all.T | 1 + testsuite/tests/th/T16976.stderr | 2 +- testsuite/tests/typecheck/should_compile/T14590.stderr | 12 +-- testsuite/tests/typecheck/should_compile/T17775-viewpats-b.stderr | 4 +- testsuite/tests/typecheck/should_fail/T12921.stderr | 12 +-- testsuite/tests/typecheck/should_fail/T19346.hs | 9 ++ testsuite/tests/typecheck/should_fail/T19346.stderr | 6 ++ testsuite/tests/typecheck/should_fail/T6069.stderr | 2 +- testsuite/tests/typecheck/should_fail/all.T | 1 + testsuite/tests/typecheck/should_fail/tcfail013.stderr | 2 +- testsuite/tests/typecheck/should_fail/tcfail140.hs | 3 - testsuite/tests/typecheck/should_fail/tcfail140.stderr | 5 +- 59 files changed, 1449 insertions(+), 1027 deletions(-)