[Git][ghc/ghc][master] Make the implicit-parameter class have representational role
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 34a27e20 by Simon Peyton Jones at 2026-01-21T16:08:17-05:00 Make the implicit-parameter class have representational role This MR addresses #26737, by making the built-in class IP have a representational role for its second parameter. See Note [IP: implicit parameter class] in ghc-internal:GHC.Internal.Classes.IP In fact, IP is (unfortunately, currently) exposed by base:GHC.Base, so we ran a quick CLC proposal to agree the change: https://github.com/haskell/core-libraries-committee/issues/385 Some (small) compilations get faster because they only need to load (small) interface file GHC.Internal.Classes.IP.hi, rather than (large) GHC.Internal.Classes.hi. Metric Decrease: T10421 T12150 T12425 T24582 T5837 T5030 - - - - - 14 changed files: - compiler/GHC/Builtin/Names.hs - docs/users_guide/9.16.1-notes.rst - libraries/ghc-internal/ghc-internal.cabal.in - libraries/ghc-internal/src/GHC/Internal/Classes.hs - + libraries/ghc-internal/src/GHC/Internal/Classes/IP.hs - testsuite/tests/interface-stability/base-exports.stdout - testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs - testsuite/tests/interface-stability/base-exports.stdout-mingw32 - testsuite/tests/interface-stability/base-exports.stdout-ws-32 - testsuite/tests/interface-stability/ghc-prim-exports.stdout - testsuite/tests/interface-stability/ghc-prim-exports.stdout-mingw32 - testsuite/tests/th/TH_implicitParams.stdout - + testsuite/tests/typecheck/should_compile/T26737.hs - testsuite/tests/typecheck/should_compile/all.T Changes: ===================================== compiler/GHC/Builtin/Names.hs ===================================== @@ -526,7 +526,7 @@ genericTyConNames = [ gHC_PRIM, gHC_PRIM_PANIC, gHC_TYPES, gHC_INTERNAL_DATA_DATA, gHC_MAGIC, gHC_MAGIC_DICT, - gHC_CLASSES, gHC_PRIMOPWRAPPERS :: Module + gHC_CLASSES, gHC_CLASSES_IP, gHC_PRIMOPWRAPPERS :: Module gHC_PRIM = mkGhcInternalModule (fsLit "GHC.Internal.Prim") -- Primitive types and values gHC_PRIM_PANIC = mkGhcInternalModule (fsLit "GHC.Internal.Prim.Panic") gHC_TYPES = mkGhcInternalModule (fsLit "GHC.Internal.Types") @@ -534,6 +534,7 @@ gHC_MAGIC = mkGhcInternalModule (fsLit "GHC.Internal.Magic") gHC_MAGIC_DICT = mkGhcInternalModule (fsLit "GHC.Internal.Magic.Dict") gHC_CSTRING = mkGhcInternalModule (fsLit "GHC.Internal.CString") gHC_CLASSES = mkGhcInternalModule (fsLit "GHC.Internal.Classes") +gHC_CLASSES_IP = mkGhcInternalModule (fsLit "GHC.Internal.Classes.IP") gHC_PRIMOPWRAPPERS = mkGhcInternalModule (fsLit "GHC.Internal.PrimopWrappers") gHC_INTERNAL_TUPLE = mkGhcInternalModule (fsLit "GHC.Internal.Tuple") @@ -1521,7 +1522,7 @@ fromLabelClassOpName -- Implicit Parameters ipClassName :: Name ipClassName - = clsQual gHC_CLASSES (fsLit "IP") ipClassKey + = clsQual gHC_CLASSES_IP (fsLit "IP") ipClassKey -- Overloaded record fields hasFieldClassName :: Name ===================================== docs/users_guide/9.16.1-notes.rst ===================================== @@ -30,6 +30,18 @@ Language - The extension :extension:`ExplicitNamespaces` now allows namespace-specified wildcards ``type ..`` and ``data ..`` in import and export lists. +- Implicit parameters and ``ImpredicativeTypes``. GHC now knows + that if ``?foo::S`` is coecible to ``?foo::T`` only if ``S`` is coercible to ``T``. + Example (from :ghc-ticket:`#26737`):: + + {-# LANGUAGE ImplicitParams, ImpredicativeTypes #-} + newtype N = MkN Int + test :: ((?foo::N) => Bool) -> ((?foo::Int) => Bool) + test = coerce + + This is achieved by arranging that ``?foo :: T`` has a representational + role for ``T``. + Compiler ~~~~~~~~ ===================================== libraries/ghc-internal/ghc-internal.cabal.in ===================================== @@ -343,6 +343,7 @@ Library GHC.Internal.CString GHC.Internal.Classes + GHC.Internal.Classes.IP GHC.Internal.Debug GHC.Internal.Magic GHC.Internal.Magic.Dict ===================================== libraries/ghc-internal/src/GHC/Internal/Classes.hs ===================================== @@ -1,10 +1,9 @@ {-# LANGUAGE Trustworthy #-} {-# LANGUAGE NoImplicitPrelude, MagicHash, StandaloneDeriving, BangPatterns, KindSignatures, DataKinds, ConstraintKinds, - MultiParamTypeClasses, FunctionalDependencies #-} -{-# LANGUAGE UnboxedTuples #-} -{-# LANGUAGE AllowAmbiguousTypes #-} - -- ip :: IP x a => a is strictly speaking ambiguous, but IP is magic + MultiParamTypeClasses, FunctionalDependencies, + UnboxedTuples #-} + {-# LANGUAGE UndecidableSuperClasses #-} -- Because of the type-variable superclasses for tuples @@ -142,6 +141,7 @@ import GHC.Internal.Prim import GHC.Internal.Tuple import GHC.Internal.CString (unpackCString#) import GHC.Internal.Types +import GHC.Internal.Classes.IP infix 4 ==, /=, <, <=, >=, > infixr 3 && @@ -149,12 +149,6 @@ infixr 2 || default () -- Double isn't available yet --- | The syntax @?x :: a@ is desugared into @IP "x" a@ --- IP is declared very early, so that libraries can take --- advantage of the implicit-call-stack feature -class IP (x :: Symbol) a | x -> a where - ip :: a - {- $matching_overloaded_methods_in_rules Matching on class methods (e.g. @(==)@) in rewrite rules tends to be a bit ===================================== libraries/ghc-internal/src/GHC/Internal/Classes/IP.hs ===================================== @@ -0,0 +1,87 @@ +{-# LANGUAGE Trustworthy #-} +{-# LANGUAGE NoImplicitPrelude, MagicHash, StandaloneDeriving, BangPatterns, + KindSignatures, DataKinds, ConstraintKinds, + MultiParamTypeClasses, FunctionalDependencies #-} + +{-# LANGUAGE AllowAmbiguousTypes, RoleAnnotations, IncoherentInstances #-} + -- LANGUAGE pragmas: see Note [IP: implicit parameter class] + +{-# OPTIONS_HADDOCK not-home #-} +----------------------------------------------------------------------------- +-- | +-- Module : GHC.Internal.Classes.IP +-- Copyright : (c) The University of Glasgow, 1992-2002 +-- License : see libraries/base/LICENSE +-- +-- Maintainer : ghc-devs@haskell.org +-- Stability : internal +-- Portability : non-portable (GHC extensions) +-- +-- Basic classes. +-- Do not import this module directly. It is an GHC internal only +-- module. Some of its contents are instead available from @Prelude@ +-- and @GHC.Int@. +-- +----------------------------------------------------------------------------- + +module GHC.Internal.Classes.IP( IP(..)) where + +import GHC.Internal.Types + + +default () -- Double isn't available yet + +-- | The syntax @?x :: a@ is desugared into @IP "x" a@ +-- IP is declared very early, so that libraries can take +-- advantage of the implicit-call-stack feature +type role IP nominal representational -- See (IPRoles) +class IP (x :: Symbol) a | x -> a where + ip :: a + +{- Note [IP: implicit parameter class] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +An implicit parameter constraint (?foo::ty) is just short for + + IP "foo" ty + +where ghc-internal:GHC.Internal.Classes.IP is a special class that +GHC knows about, defined in this module. + +* It is a unary type class, with one method `ip`, so it has no cost. + For example, (?foo::Int) is represented just by an Int. + +* Criticially, it has a functional dependency: + class IP (x :: Symbol) a | x -> a where ... + So if we have + [G] IP "foo" Int + [W] IP "foo" alpha + the fundep wil lgive us alpha ~ Int, as desired. + +* The solver has a number of special cases for implicit parameters, + mainly because a binding (let ?foo::Int = rhs in body) + is like a local instance declaration for IP. Search for uses + of `isIPClass`. + +Wrinkles + +(IPAmbiguity) The single method of IP has an ambiguous type + ip :: forall a. IP s a => a + Hence the LANGUAGE pragama AllowAmbiguousTypes. + The method `ip` is never called by the user, so ambiguity doesn't matter. + +(IPRoles) IP has a role annotation. Why? See #26737. We want + [W] IP "foo" t1 ~R# IP "foo" t2 + to decompose to give [W] IP t1 ~R# t2, using /representational/ + equality for (t1 ~R# t2) not nominal. + + This usually gives a complaint about incoherence, because in general + (t1 ~R# t2) does NOT imply (C t1) ~R# (C t2) for any normal class. + But it does for IP, because instance selection is controlled by the Symbol, + not the type of the payload. Hence LANGUAGE pragma IncoherentInstances. + (It is unfortunate that we need a module-wide IncoherentInstances here; + see #17167.) + + Side note: arguably this treatment could be applied to any class + with a functional dependency; but for now we restrict it to IP. +-} + ===================================== testsuite/tests/interface-stability/base-exports.stdout ===================================== @@ -3293,6 +3293,7 @@ module GHC.Base where {-# MINIMAL fmap #-} type IO :: * -> * newtype IO a = IO (State# RealWorld -> (# State# RealWorld, a #)) + type role IP nominal representational type IP :: Symbol -> * -> Constraint class IP x a | x -> a where ip :: a ===================================== testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs ===================================== @@ -3293,6 +3293,7 @@ module GHC.Base where {-# MINIMAL fmap #-} type IO :: * -> * newtype IO a = IO (State# RealWorld -> (# State# RealWorld, a #)) + type role IP nominal representational type IP :: Symbol -> * -> Constraint class IP x a | x -> a where ip :: a ===================================== testsuite/tests/interface-stability/base-exports.stdout-mingw32 ===================================== @@ -3293,6 +3293,7 @@ module GHC.Base where {-# MINIMAL fmap #-} type IO :: * -> * newtype IO a = IO (State# RealWorld -> (# State# RealWorld, a #)) + type role IP nominal representational type IP :: Symbol -> * -> Constraint class IP x a | x -> a where ip :: a ===================================== testsuite/tests/interface-stability/base-exports.stdout-ws-32 ===================================== @@ -3293,6 +3293,7 @@ module GHC.Base where {-# MINIMAL fmap #-} type IO :: * -> * newtype IO a = IO (State# RealWorld -> (# State# RealWorld, a #)) + type role IP nominal representational type IP :: Symbol -> * -> Constraint class IP x a | x -> a where ip :: a ===================================== testsuite/tests/interface-stability/ghc-prim-exports.stdout ===================================== @@ -1171,6 +1171,7 @@ module GHC.Classes where (==) :: a -> a -> GHC.Internal.Types.Bool (/=) :: a -> a -> GHC.Internal.Types.Bool {-# MINIMAL (==) | (/=) #-} + type role IP nominal representational type IP :: GHC.Internal.Types.Symbol -> * -> Constraint class IP x a | x -> a where ip :: a ===================================== testsuite/tests/interface-stability/ghc-prim-exports.stdout-mingw32 ===================================== @@ -1171,6 +1171,7 @@ module GHC.Classes where (==) :: a -> a -> GHC.Internal.Types.Bool (/=) :: a -> a -> GHC.Internal.Types.Bool {-# MINIMAL (==) | (/=) #-} + type role IP nominal representational type IP :: GHC.Internal.Types.Symbol -> * -> Constraint class IP x a | x -> a where ip :: a ===================================== testsuite/tests/th/TH_implicitParams.stdout ===================================== @@ -1,5 +1,5 @@ -Main.funcToReify :: GHC.Internal.Classes.IP "z" - GHC.Internal.Types.Int => +Main.funcToReify :: GHC.Internal.Classes.IP.IP "z" + GHC.Internal.Types.Int => GHC.Internal.Types.Int 5 1 ===================================== testsuite/tests/typecheck/should_compile/T26737.hs ===================================== @@ -0,0 +1,10 @@ +{-# LANGUAGE ImpredicativeTypes, ImplicitParams #-} + +module T26737 where + +import Data.Coerce + +newtype Foo = MkFoo Int + +b :: ((?foo :: Foo) => Int) -> ((?foo :: Int) => Int) +b = coerce @(((?foo :: Foo) => Int)) @(((?foo :: Int) => Int)) ===================================== testsuite/tests/typecheck/should_compile/all.T ===================================== @@ -958,3 +958,4 @@ test('T14745', normal, compile, ['']) test('T26451', normal, compile, ['']) test('T26582', normal, compile, ['']) test('T26746', normal, compile, ['']) +test('T26737', normal, compile, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/34a27e2042b697b198aa85a7460fee79... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/34a27e2042b697b198aa85a7460fee79... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Marge Bot (@marge-bot)