2.1. Version 9.4.1¶
2.1.1. Language¶
A small change has been made to the way GHC infers types for definitions with no type signature: GHC will no longer generalize a function over a type variable determined by a functional dependency. For example:
class C a b | a -> b where op :: a -> b -> () f x = op True x
Previously, GHC inferred
f :: C Bool b => b -> ()
. However, the functional dependency says that only one type could ever be used forb
: this function is hardly valid “for all”b
s. With the change, GHC will reject, looking for the (non-existent) instance forC Bool b
.If you want to retain the old behavior, add a (backward-compatible) type signature, explicitly requesting this unusual quantification.
GHC no longer checks for
-XGADTs
or-XTypeFamilies
in order to use an equality constraint in a type. This is part of accepted proposal #371.There were previously cases around functional dependencies and injective type families where the result of type inference would depend on the order of constraints, as written in a source file. These cases are fundamentally ambiguous. While GHC previously made an arbitrary decision, it now notices the ambiguity and rejects the program. This means that some previously accepted programs are now rejected. The solution is to add a type annotation or type application to resolve the ambiguity.
This is the fix for #18851.
2.1.2. Compiler¶
New
-Wredundant-strictness-flags
that checks for strictness flags (!
) applied to unlifted types, which are always strict.New
-fprof-late-ccs
that adds automatic CCS annotations to all top level functions after core optimisation have been run.A new type of plugin: defaulting plugins. These plugins can propose defaults for ambiguous variables that would otherwise cause errors just like the built-in defaulting mechanism.
The way GHC checks for representation polymorphism has been overhauled: all the checks are now done during typechecking. The error messages now contain more detailed information about the specific check that was performed.
The parsing of implicit parameters is slightly more permissive, as GHC now allows
foo :: (?ip :: forall a. a -> a)
without requiring parentheses around
forall a. a -> a
. Note that implicit parameters with such kinds are unlikely to be very useful, due to #18759.Changes to the treatment of
UnboxedSums
:- GHC can now parse unboxed sum type constructors
(# | #)
,(# | | #)
,(# | | | #)
, etc. Partial applications need to be written in prefix form, e.g.(# | #) Int#
. - Unboxed sums now require the
UnboxedSums
extension to be enabled. - The
UnboxedTuples
extension now impliesUnboxedSums
. This means that code using unboxed sums that enabled theUnboxedTuples
extension but didn’t explicitly enableUnboxedSums
will continue to work without changes.
- GHC can now parse unboxed sum type constructors
Constructed Product Result analysis (c.f.
-fcpr-anal
) has been overhauled and will now unbox nestedly, if termination properties of the function permit. This allows unboxing of constructed results returned byIO
actions. E.g.:sumIO :: [Int] -> IO Int sumIO [] = return 0 sumIO (x:xs) = do r <- sumIO xs return $! x + r
Note the use of
$!
: Without it, GHC would be unable to see that evaluation ofr
andx
terminates (and rapidly, at that). An alternative would be to evaluate both with a bang pattern or aseq
, but thereturn $! <res>
idiom should work more reliably and needs less thinking.Demand analysis (cf.
-fstrictness
) now integrates a Boxity Analysis that tracks whether a function needs a parameter boxed. If that is the case, the worker/wrapper transformation (cf.-fworker-wrapper
) will not unbox that parameter, leading to less reboxing in many cases.For reasons of backwards-compatible performance, you may find that the new mechanism is too aggressive in a few cases (e.g., still unboxing a parameter that is used boxed in a hot path). Do post a bug report with your example! Then wrap the uses of the parameter in
GHC.Exts.lazy
for a short-term fix.Tag inference has been implemented.
It’s a new backend optimization pass aimed at avoiding redundant evaluatedness checks. The basic pass is always enabled and not optional. When using
-fworker-wrapper-cbv
it additionally will generate workers for functions with strict arguments, pushing the evaluation+tagging of the arguments into the wrapper and allowing the worker to simply assume all arguments are fully evaluated and properly tagged. Usually the wrapper will then inline, and if the argument is known to be properly tagged at the call site the wrapper will become a no-op. Giving us a more efficient worker without adding any overhead. If the argument isn’t known to be evaluated we perform the same amount of work, but do it at call sites instead of inside the called function.In general
-fworker-wrapper-cbv
is very beneficial and can be safely enabled. However sadly there are two exceptions. It can break rules for code which made assumptions about which functions get a W/W split which now no longer hold. See #20364 for the details. For this reason it isn’t enabled by default. For code which has the properINLINABLE
(INLINABLE pragma) andINLINE
(INLINE pragma) or that doesn’t define any rule-relevant functions this shouldn’t happen. The longterm fix here is to apply the proper pragmas. There is also a known issue where a function taking multiple unlifted arguments can cause excessive spilling (#20334). This seems to be an edge case. But if you think you are hitting this case please comment on the ticket so that we can prioritize it accordingly.Support for Sun SPARC architecture has been dropped (#16883).
A fix for GHC’s handling of the XDG Base Directory Specification (#6077, #20684, #20669, #20660):
- For the package database previously in
~/.ghc/<arch-ver>
, we will continue to use the old path if it exists. For example, if the~/.ghc/x86_64-linux-9.4.1
directory exists, GHC will use that for its user package database. If this directory does not exist, we will use$XDG_DATA_HOME/ghc/x86_64-linux-9.4.1
. This is in order to give tooling like cabal time to migrate - For GHCi configuration files previously located in
~/.ghc/
likeghci.conf
andghci_history
, we will first check if they exist in~/.ghc
and use those if they do. However, we will create new files likeghci_history
only in$XDG_DATA_HOME/ghc
. So if you don’t have a previous GHC installation which created~/.ghc/ghci_history
, the history file will be written to$XDG_DATA_HOME/ghc
. If you already have an older GHC installation which wrote~/.ghc/ghci_history
, then GHC will continue to write the history to that file.
- For the package database previously in
The
-Wunticked-promoted-constructors
warning is no longer enabled with-Wall
(#20531), as a part of long-term push towards Dependent Haskell.In GHCi, the
:type
command no longer instantiates quantified type variables when given a polymorphic type. (It used to instantiate inferred type variables.)
2.1.3. base
library¶
GHC.Exts.magicDict
has been renamed towithDict
and given a more specific type:withDict :: forall {rr :: RuntimeRep} st dt (r :: TYPE rr). st -> (dt => r) -> r
Unlike
magicDict
,withDict
can be used without defining an intermediate data type. For example, thewithTypeable
function from theData.Typeable
module can now be defined as:withTypeable :: forall k (a :: k) rep (r :: TYPE rep). () => TypeRep a -> (Typeable a => r) -> r withTypeable rep k = withDict @(TypeRep a) @(Typeable a) rep k
Note that the explicit type applications are required, as the call to
withDict
would be ambiguous otherwise.
2.1.4. ghc-prim
library¶
Primitive types and functions which handle boxed values are now levity-polymorphic, meaning that they now also work with unlifted boxed values (i.e. values whose type has kind
TYPE (BoxedRep Unlifted)
).The following type constructors are now levity-polymorphic:
Array#
,SmallArray#
,Weak#
,StablePtr#
,StableName#
,MutableArray#
,SmallMutableArray#
,MutVar#
,TVar#
,MVar#
,IOPort#
.
For example,
Array#
used to have kind:Type -> UnliftedType
but it now has kind:
forall {l :: Levity}. TYPE (BoxedRep l) -> UnliftedType
Similarly,
MutVar#
used to have kind:Type -> Type -> UnliftedType
but it now has kind:
forall {l :: Levity}. Type -> TYPE (BoxedRep l) -> UnliftedType
This means that in
Array# a
,MutableArray# s a
,MutVar# s a
, …, the element typea
, must always be boxed, but it can now either be lifted or unlifted. In particular, arrays and mutable variables can now be used to store other arrays and mutable variables.All functions which use these updated primitive types are also levity-polymorphic:
- all array operations (reading/writing/copying/…), for both arrays and small arrays,
mutable and immutable:
newArray#
,readArray#
,writeArray#
,sizeofArray#
,sizeofMutableArray#
,indexArray#
,unsafeFreezeArray#
,unsafeThawArray#
,copyArray#
,copyMutableArray#
,cloneArray#
,cloneMutableArray#
,freezeArray#
,thawArray#
,casArray#
,newSmallArray#
,shrinkSmallMutableArray#
,readSmallArray#
,writeSmallArray#
,sizeofSmallArray#
,getSizeofSmallMutableArray#
,indexSmallArray#
,unsafeFreezeSmallArray#
,unsafeThawSmallArray#
,copySmallArray#
,copySmallMutableArray#
,cloneSmallArray#
,cloneSmallMutableArray#
,freezeSmallArray#
,thawSmallArray#
,casSmallArray#
,
newMutVar#
,``readMutVar#``,``writeMutV#``,``casMutVar#``,- operations on
MVar#
andTVar#
:newTVar#
,readTVar#
,readTVarIO#
,writeTVar#
,newMVar#
,takeMVar#
,tryTakeMVar#
,putMVar#
,tryPutMVar#
,readMVar#
,tryReadMVar#
,
STM
operationsatomically#
,retry#
,catchRetry#
andcatchSTM#
.newIOPort#
,readIOPort#
,writeIOPort#
,mkWeak#
,mkWeakNoFinalizer#
,addCFinalizerToWeak#
,deRefWeak#
,finalizeWeak#
,makeStablePtr#
,deRefStablePtr#
,eqStablePtr#
,makeStableName#
,stableNameToInt#
,
For example, the full type of
newMutVar#
is now:newMutVar# :: forall {l :: Levity} s (a :: TYPE (BoxedRep l)). a -> State# s -> (# State# s, MVar# s a #)
and the full type of
writeSmallArray#
is:writeSmallArray# :: forall {l :: Levity} s (a :: TYPE (BoxedRep l)). SmallMutableArray# s a -> Int# -> a -> State# s -> State# s
ArrayArray#` and ``MutableArrayArray#
have been moved fromGHC.Prim
toGHC.Exts
. They are deprecated, because their functionality is now subsumed byArray#
andMutableArray#
.mkWeak#
,mkWeakNoFinalizer#
,touch#
andkeepAlive#
are now levity-polymorphic instead of representation-polymorphic. For instance:mkWeakNoFinalizer# :: forall {l :: Levity} {k :: Levity} (a :: TYPE (BoxedRep l)) (b :: TYPE (BoxedRep k)). a -> b -> State# RealWorld -> (# State# RealWorld, Weak# b #)
That is, the type signature now quantifies over the
GHC.Exts.Levity
ofa
instead of itsGHC.Exts.RuntimeRep
. In addition, this variable is now inferred, instead of specified, meaning that it is no longer eligible for visible type application. Note thatb
is now also levity-polymorphic, due to the change outlined in the previous point.Primitive functions for throwing and catching exceptions are now more polymorphic than before. For example,
catch#
now has type:catch# :: forall {r :: RuntimeRep} {l :: Levity} (a :: TYPE r) (b :: TYPE (BoxedRep l)). ( State# RealWorld -> (# State# RealWorld, a #) ) -> ( b -> State# RealWorld -> (# State# RealWorld, a #) ) -> State# RealWorld -> (# State# RealWorld, a #)
The following functions have been generalised in this way:
catch#
,raise#
,raiseIO#
,maskAsyncExceptions#
,maskUninterruptible#
,unmaskAsyncExceptions#
.
Note in particular that
raise#
is now both representation-polymorphic (with an inferred RuntimeRep argument) and levity-polymorphic, with type:raise# :: forall {l :: Levity} {r :: RuntimeRep} (a :: TYPE (BoxedRep l)) (b :: TYPE r). a -> b
fork#
andforkOn#
are now representation-polymorphic. For example,fork#
now has type:fork# :: forall {r :: RuntimeRep} (a :: TYPE r). (State# RealWorld -> (# State# RealWorld, a #)) -> (State# RealWorld -> (# State# RealWorld, a #))
GHC.Exts.reallyUnsafePtrEquality#
has been made more general, as it is now both levity-polymorphic and heterogeneous:reallyUnsafePtrEquality# :: forall {l :: Levity} {k :: Levity} (a :: TYPE (BoxedRep l)) (b :: TYPE (BoxedRep k)) . a -> b -> Int#
This means that
GHC.Exts.reallyUnsafePtrEquality#
can be used on primitive arrays such asGHC.Exts.Array#
andGHC.Exts.ByteArray#
. It can also be used on values of different types, without needing to callGHC.Exts.unsafeCoerce#
.Added
GHC.Exts.reallyUnsafePtrEquality
which recovers the previous behaviour ofGHC.Exts.reallyUnsafePtrEquality#
:reallyUnsafePtrEquality :: forall (a :: Type). a -> a -> Int#
Added
GHC.Exts.sameArray#
,GHC.Exts.sameSmallArray#
,GHC.Exts.sameByteArray#
andGHC.Exts.sameArrayArray#
:sameArray# :: Array# a -> Array# a -> Int# sameSmallArray# :: SmallArray# a -> SmallArray# a -> Int# sameByteArray# :: ByteArray# -> ByteArray# -> Int# sameArrayArray# :: ArrayArray# -> ArrayArray# -> Int#
2.1.5. ghc
library¶
- A new
GHC.Hs.Syn.Type
module has been introduced which defines functions for computing theType
of anHsExpr GhcTc
in a pure fashion. ThehsLitType
andhsPatType
functions that previously lived inGHC.Tc.Utils.Zonk
have been moved to this module. - A
Typeable
constraint has been added tofromStaticPtr
in the classGHC.StaticPtr.IsStatic
. GHC automatically wraps each use of thestatic
keyword withfromStaticPtr
. Becausestatic
requires its argument to be an instance ofTypeable
,fromStaticPtr
can safely carry this constraint as well. - The
newWanted
function exported byGHC.Tc.Plugin
now passes on the fullCtLoc
instead of reconstituting it from the type-checking environment. This makesnewWanted
consistent withnewGiven
. For authors of type-checking plugins, this means you don’t need to wrap a call tonewWanted
insetCtLocM
to create a new Wanted constraint with the providedCtLoc
. - GHC no longer carries
Derived
constraints. Accordingly, several functions in the plugin architecture that previously passed or received three sets of constraints (givens, deriveds, and wanteds) now work with two such sets.