Changelog for base-4.21.0.0
Changelog for base package
4.21.0.0 December 2024
- Shipped with GHC 9.12.1
- Introduce Data.Boundedmodule exporting theBoundedtypeclass (finishing CLC proposal #208)
- Deprecate export of Boundedclass fromData.Enum(CLC proposal #208)
- GHC.Desugarhas been deprecated and should be removed in GHC 9.14. (CLC proposal #216)
- Add a readTixFilefield to theHpcFlagsrecord inGHC.RTS.Flags(CLC proposal #276)
- Add compareLengthtoData.ListandData.List.NonEmpty(CLC proposal #257)
- Add INLINE[1]tocompareInt/compareWord(CLC proposal #179)
- Refactor GHC.RTS.Flagsin preparation for new I/O managers: introducedata IoManagerFlagand use it inMiscFlags, removegetIoManagerFlag, deprecate re-export ofIoSubSystem(CLC proposal #263)
- Add the MonadFixinstance for(,) a, similar to the one forWriter a(CLC proposal #238)
- Improve toInteger :: Word32 -> Integeron 64-bit platforms (CLC proposal #259)
- Make fliprepresentation polymorphic (CLC proposal #245)
- The HasFieldclass now supports representation polymorphism (CLC proposal #194)
- Make readaccept binary integer notation (CLC proposal #177)
- Improve the performance of Data.List.sortusing an improved merging strategy. Instead ofcompare,sortnow uses(>)which may break malformedOrdinstances (CLC proposal #236)
- Add inits1andtails1toData.List, factored from the corresponding functions inData.List.NonEmpty(CLC proposal #252)
- Add firstAandsecondAtoData.Bitraversable. (CLC proposal #172)
- Deprecate GHC.TypeNats.Internal,GHC.TypeLits.Internal,GHC.ExecutionStack.Internal(CLC proposal #217)
- System.IO.Error.ioErrorand- Control.Exception.ioErrornow both carry- HasCallStackconstraints (CLC proposal #275)
- Define Eq1,Ord1,Show1andRead1instances for basicGenericrepresentation types. (CLC proposal #273)
- setNonBlockingModewill no longer throw an exception when called on a FD associated with a unknown device type. (CLC proposal #282)
- Add exception type metadata to default exception handler output. (CLC proposal #231 and CLC proposal #261)
- The deprecation process of GHC.Pack has come its term. The module has now been removed from base.
- Propagate HasCallStack from errorCallWithCallStackExceptionto exception backtraces, fixing a bug in the implementation of CLC proposal #164.
- Annotate re-thrown exceptions with the backtrace as per CLC proposal #202 (introduces WhileHandlingand modifies such ascatchandonExceptionaccordingly to propagate or rethrow exceptions)
- Introduced catchNoPropagate,rethrowIOandtryWithContextas part of CLC proposal #202 to facilitate rethrowing exceptions without adding aWhileHandlingcontext -- if rethrowinge, you don't want to addWhileHandling eto the context since it will be redundant. These functions are mostly useful for libraries that define exception-handling combinators likecatchandonException, such asbase, or theexceptionspackage.
- Move Lift ByteArrayandLift Fixedinstances intobasefromtemplate-haskell. See CLC proposal #287.
- Modify the implementation of Control.Exception.throwto avoid call-sites being inferred as diverging via precise exception. (GHC #25066, CLC proposal #290)
- Make Debug.Trace.{traceEventIO,traceMarkerIO}faster when tracing is disabled. See CLC proposal #291.
- The exception messages were improved according to CLC proposal #285. In particular:
- Improve the message of the uncaught exception handler
- Make displayException (SomeException e) = displayException e. The additional information that is printed when exceptions are surfaced to the top-level is added byuncaughtExceptionHandler.
- Get rid of the HasCallStack mechanism manually propagated by ErrorCallin favour of the more general HasCallStack exception backtrace mechanism, to remove duplicate call stacks for uncaught exceptions.
- Freeze the callstack of error,undefined,throwIO,ioException,ioErrorto prevent leaking the implementation of these error functions into the callstack.
 
4.20.0.0 May 2024
- 
Shipped with GHC 9.10.1 
- 
Introduce Data.Enummodule exporting bothEnumandBounded. Note that the export ofBoundedwill be deprecated in a future release (CLC proposal #208)
- 
Deprecate GHC.Pack(#21461)
- 
Export foldl'fromPrelude(CLC proposal #167)
- 
The top-level handler for uncaught exceptions now displays the output of displayExceptionrather thanshow(CLC proposal #198)
- 
Add permutationsandpermutations1toData.List.NonEmpty(CLC proposal #68)
- 
Add a RULEtoPrelude.lookup, allowing it to participate in list fusion (CLC proposal #175)
- 
Implement stimesforinstance Semigroup (Endo a)explicitly (CLC proposal #4)
- 
Add startTimeProfileAtStartuptoGHC.RTS.Flagsto expose new RTS flag--no-automatic-heap-samplesin the Haskell API (CLC proposal #243).
- 
Implement sconcatforinstance Semigroup Data.Semigroup.Firstandinstance Semigroup Data.Monoid.Firstexplicitly, increasing laziness (CLC proposal #246)
- 
Add laws relating between Foldable/TraversablewithBifoldable/Bitraversable(CLC proposal #205)
- 
The Enum Int64andEnum Word64instances now use native operations on 32-bit platforms, increasing performance by up to 1.5x on i386 and up to 5.6x with the JavaScript backend. (CLC proposal #187)
- 
Exceptions can now be decorated with user-defined annotations via ExceptionContext(CLC proposal #200)
- 
Exceptions now capture backtrace information via their ExceptionContext. GHC supports several mechanisms by which backtraces can be collected which can be individually enabled and disabled viaGHC.Exception.Backtrace.setBacktraceMechanismState(CLC proposal #199)
- 
Add HasCallStackconstraint toControl.Exception.throw{,IO}(CLC proposal #201)
- 
Update to Unicode 15.1.0. 
- 
Fix withFile,withFileBlocking, andwithBinaryFileto not incorrectly annotate exceptions raised in wrapped computation. (CLC proposal #237)
- 
Fix fdIsNonBlockingto always be0for regular files and block devices on unix, regardless ofO_NONBLOCK
- 
Always use safecall toreadfor regular files and block devices on unix if the RTS is multi-threaded, regardless ofO_NONBLOCK. (CLC proposal #166)
- 
Export List from Data.List (CLC proposal #182). 
- 
Add {-# WARNING in "x-data-list-nonempty-unzip" #-}toData.List.NonEmpty.unzip. Use{-# OPTIONS_GHC -Wno-x-data-list-nonempty-unzip #-}to disable it. (CLC proposal #86 and CLC proposal #258)
- 
Add System.Mem.performMajorGC(CLC proposal #230)
- 
Fix exponent overflow/underflow bugs in the Readinstances forFloatandDouble(CLC proposal #192)
- 
Foreign.C.Error.errnoToIOErrornow uses the reentrantstrerror_rto render system errors when possible (CLC proposal #249)
- 
Implement manyandsomemethods ofinstance Alternative (Compose f g)explicitly. (CLC proposal #181)
- 
Change the types of the GHC.Stack.StackEntry.closureTypeandGHC.InfoProv.InfoProv.ipDescrecord fields to useGHC.Exts.Heap.ClosureTyperather than anInt. To recover the old value usefromEnum. (CLC proposal #210)
- 
The functions GHC.Exts.dataToTag#andGHC.Base.getTaghave had their types changed to the following:dataToTag#, getTag :: forall {lev :: Levity} (a :: TYPE (BoxedRep lev)) . DataToTag a => a -> Int#In particular, they are now applicable only at some (not all) lifted types. However, if tis an algebraic data type (i.e.tmatches adataordata instancedeclaration) with all of its constructors in scope and the levity oftis statically known, then the constraintDataToTag tcan always be solved. (CLC proposal #104)
- 
GHC.Extsno longer exports the GHC-internalwhereFrom#primop (CLC proposal #214)
- 
GHC.InfoProv.InfoProvnow provides aipUnitId :: Stringfield encoding the unit ID of the unit defining the info table (CLC proposal #214)
- 
Add sortOntoData.List.NonEmpty(CLC proposal #227)
- 
Add more instances for Compose:Fractional,RealFrac,Floating,RealFloat(CLC proposal #226)
- 
Treat all FDs as "nonblocking" on wasm32 (CLC proposal #234) 
- 
Add HeapByEra,eraSelectorandautomaticEraIncrementtoGHC.RTS.Flagsto reflect the new RTS flags:-heprofiling mode,-heselector and--automatic-era-increment. (CLC proposal #254)
- 
Document that certain modules are unstable and not meant to be consumed by the general public (CLC proposal #146) 
- 
Add unaligned Addr#primops (CLC proposal #154)
- 
Deprecate stgDoubleToWord{32,64}andstgWord{32,64}ToDoublein favor of new primopscastDoubleToWord{32,64}#andcastWord{32,64}ToDouble#(CLC proposal #253)
- 
Add unsafeThawByteArray#, opposite to the existingunsafeFreezeByteArray#(CLC proposal #184)
4.19.0.0 October 2023
- Shipped with GHC 9.8.1
- Add {-# WARNING in "x-partial" #-}toData.List.{head,tail}. Use{-# OPTIONS_GHC -Wno-x-partial #-}to disable it. (CLC proposal #87 and #114)
- Add fromThreadId :: ThreadId -> Word64toGHC.Conc.Sync, which maps a thread to a per-process-unique identifier (CLC proposal #117)
- Add Data.List.!?(CLC proposal #110)
- Mark maximumBy/minimumByasINLINEimproving performance for unpackable types significantly.
- Add INLINABLE pragmas to generic*functions in Data.OldList (CLC proposal #129)
- Export getSolofromData.Tuple. (CLC proposal #113)
- Add Type.Reflection.decTypeRep,Data.Typeable.decTandData.Typeable.hdecTequality decisions functions. (CLC proposal #98)
- Add Data.Functor.unzip(CLC proposal #88)
- Add System.Mem.Weak.{get,set}FinalizerExceptionHandler, which allows the user to set the global handler invoked by when aWeakpointer finalizer throws an exception. (CLC proposal #126)
- Add System.Mem.Weak.printToHandleFinalizerExceptionHandler, which can be used withsetFinalizerExceptionHandlerto print exceptions thrown by finalizers to the givenHandle. (CLC proposal #126)
- Add Data.List.unsnoc(CLC proposal #165)
- Implement more members of instance Foldable (Compose f g)explicitly. (CLC proposal #57)
- Add EqandOrdinstances forSSymbol,SChar, andSNat. (CLC proposal #148)
- Add COMPLETEpragmas to theTypeRep,SSymbol,SChar, andSNatpattern synonyms. (CLC proposal #149)
- Make ($)representation polymorphic (CLC proposal #132)
- Implement GHC Proposal #433,
adding the class Unsatisfiable :: ErrorMessage -> TypeErrortoGHC.TypeError, which provides a mechanism for custom type errors that reports the errors in a more predictable behaviour thanTypeError.
- Add more instances for Compose:Enum,Bounded,Num,Real,Integral(CLC proposal #160)
- Make (&)representation polymorphic in the return type (CLC proposal #158)
- Implement GHC.IORef.atomicSwapIORefvia a new dedicated primopatomicSwapMutVar#(CLC proposal #139)
- Change BufferCodecto use an unboxed implementation, while providing a compatibility layer using pattern synonyms. (CLC proposal #134 and #178)
- Add nominal role annotations to SNat/SSymbol/SChar(CLC proposal #170)
- Make Semigroup'sstimesspecializable. (CLC proposal #8)
- Implement copyBytes,fillBytes,moveBytesandstimesforData.Array.Byte.ByteArrayusing primops (CLC proposal #188)
- Add rewrite rules for conversion between Int64/Word64andFloat/Doubleon 64-bit architectures (CLC proposal #203).
- Genericinstances for tuples now expose- Unit,- Tuple2,- Tuple3, ...,- Tuple64as the actual names for tuple type constructors (GHC proposal #475).
- Reject FilePaths containing interiorNULs (CLC proposal #144)
- Add GHC.JS.Foreign.Callbackmodule for JavaScript backend (CLC proposal #150)
- Generalize the type of keepAlive#andtouch#(CLC proposal #152)
4.18.0.0 March 2023
- Shipped with GHC 9.6.1
- Foreign.C.ConstPtr.ConstrPtrwas added to encode- const-qualified pointer types in foreign declarations when using- CApiFFIextension. (CLC proposal #117)
- Add forall a. Functor (p a)superclass forBifunctor p(CLC proposal #91)
- Add forall a. Functor (p a)superclass forBifunctor p.
- Add Functor instances for (,,,,) a b c d,(,,,,,) a b c d eand(,,,,,) a b c d e f.
- Exceptions thrown by weak pointer finalizers can now be reported by setting
a global exception handler, using System.Mem.Weak.setFinalizerExceptionHandler. The default behaviour is unchanged (exceptions are ignored and not reported).
- Numeric.Naturalre-exports- GHC.Natural.minusNaturalMaybe(CLC proposal #45)
- Add Data.Foldable1andData.Bifoldable1(CLC proposal #9)
- Add applyWhentoData.Function(CLC proposal #71)
- Add functions mapAccumMandforAccumMtoData.Traversable(CLC proposal #65)
- Add default implementation of (<>)in terms ofsconcatandmemptyin terms ofmconcat(CLC proposal #61).
- GHC.Conc.Sync.listThreadswas added, allowing the user to list the threads (both running and blocked) of the program.
- GHC.Conc.Sync.labelThreadByteArray#was added, allowing the user to specify a thread label by way of a- ByteArray#containing a UTF-8-encoded string. The old- GHC.Conc.Sync.labelThreadis now implemented in terms of this function.
- GHC.Conc.Sync.threadLabelwas added, allowing the user to query the label of a given- ThreadId.
- Add inits1andtails1toData.List.NonEmpty(CLC proposal #67)
- Change default Ordimplementation of(>=),(>), and(<)to use(<=)instead ofcompare(CLC proposal #24).
- Export liftA2fromPrelude. This means that the entirety ofApplicativeis now exported fromPrelude(CLC proposal #50, the migration guide)
- Switch to a pure Haskell implementation of GHC.Unicode(CLC proposals #59 and #130)
- Update to Unicode 15.0.0.
- Add standard Unicode case predicates isUpperCaseandisLowerCasetoGHC.UnicodeandData.Char. These predicates use the standard Unicode case properties and are more intuitive thanisUpperandisLower(CLC proposal #90)
- Add EqandOrdinstances forGenerically1.
- Relax instances for Functor combinators; put superclass on Class1 and Class2 to make non-breaking (CLC proposal #10, migration guide)
- Add gcdetails_block_fragmentation_bytestoGHC.Stats.GCDetailsto track heap fragmentation.
- GHC.TypeLitsand- GHC.TypeNatsnow export the- natSing,- symbolSing, and- charSingmethods of- KnownNat,- KnownSymbol, and- KnownChar, respectively. They also export the- SNat,- SSymbol, and- SChartypes that are used in these methods and provide an API to interact with these types, per CLC proposal #85.
- The Enuminstance ofDown anow enumerates values in the opposite order as theEnum ainstance (CLC proposal #51)
- Foreign.Marshal.Poolnow uses the RTS internal arena instead of libc- mallocfor allocation. It avoids the O(n) overhead of maintaining a list of individually allocated pointers as well as freeing each one of them when freeing a- Pool(#14762, #18338)
- Type.Reflection.Unsafeis now marked as unsafe.
- Add Data.Typeable.heqT, a kind-heterogeneous version ofData.Typeable.eqT(CLC proposal #99)
- Various declarations GHC's new info-table provenance feature have been
moved from GHC.Stack.CCSto a newGHC.InfoProvmodule:- The InfoProv, along itsipName,ipDesc,ipTyDesc,ipLabel,ipMod, andipLocfields, have been moved.
- InfoProvnow has additional- ipSrcFileand- ipSrcSpanfields.- ipLocis now a function computed from these fields.
- The whereFromfunction has been moved
 
- The 
- Add functions traceWith,traceShowWith,traceEventWithtoDebug.Trace, per CLC proposal #36.
- Export ListfromGHC.List(CLC proposal #186).
4.17.0.0 August 2022
- 
Shipped with GHC 9.4.1 
- 
Add explicitly bidirectional pattern TypeReptoType.Reflection.
- 
Add GenericallyandGenerically1toGHC.Genericsfor deriving generic instances withDerivingVia.Genericallyinstances includeSemigroupandMonoid.Generically1instances:Functor,Applicative,Alternative,Eq1andOrd1.
- 
Introduce GHC.ExecutablePath.executablePath, which is more robust thangetExecutablePathin cases when the executable has been deleted.
- 
Add Data.Array.Bytemodule, providing boxedByteArray#andMutableByteArray#wrappers.
- 
fromEnumforNaturalnow throws an error for any number that cannot be repesented exactly by anInt(#20291).
- 
returnAis defined asControl.Category.idinstead ofarr id.
- 
Added symbolic synonyms for xorand shift operators toData.Bits:- .^.(- xor),
- .>>.and- !>>.(- shiftRand- unsafeShiftR),
- .<<.and- !<<.(- shiftLand- unsafeShiftL).
 These new operators have the same fixity as the originals. 
- 
GHC.Extsnow re-exportsMultiplicityandMultMul.
- 
A large number of partial functions in Data.ListandData.List.NonEmptynow have an HasCallStack constraint. Hopefully providing better error messages in case they are used in unexpected ways.
- 
Fix the Ord1instance forData.Ord.Downto reverse sort order.
- 
Any Haskell type that wraps a C pointer type has been changed from Ptr ()toCUIntPtr. For typical glibc based platforms, the affected type isCTimer.
- 
Remove instances of MonadFailfor theSTmonad (lazy and strict) as per the Core Libraries proposal. A migration guide is available.
- 
Re-export augmentandbuildfunction fromGHC.List
- 
Re-export the IsListtypeclass from the newGHC.IsListmodule.
- 
There's a new special function withDictinGHC.Exts: ::withDict :: forall {rr :: RuntimeRep} cls meth (r :: TYPE rr). WithDict cls meth => meth -> (cls => r) -> rwhere clsmust be a class containing exactly one method, whose type must bemeth.This function converts methto a type class dictionary. It removes the need forunsafeCoercein implementation of reflection libraries. It should be used with care, because it can introduce incoherent instances.For example, the withTypeablefunction from theType.Reflectionmodule can now be defined as: ::withTypeable :: forall k (a :: k) rep (r :: TYPE rep). () => TypeRep a -> (Typeable a => r) -> r withTypeable rep k = withDict @(Typeable a) rep kNote that the explicit type application is required, as the call to withDictwould be ambiguous otherwise.This replaces the old GHC.Exts.magicDict, which required an intermediate data type and was less reliable.
- 
Data.Word.Word64andData.Int.Int64are now always represented byWord64#andInt64#, respectively. Previously on 32-bit platforms these were rather represented byWord#andInt#. See GHC #11953.
- 
Add GHC.TypeErrormodule to contain functionality related to custom type errors.TypeErroris re-exported fromGHC.TypeLitsfor backwards compatibility.
- 
Comparison constraints in Data.Type.Ord(e.g.<=) now use the newGHC.TypeError.Asserttype family instead of type equality with~.
4.16.3.0 May 2022
- 
Shipped with GHC 9.2.4 
- 
winio: make consoleReadNonBlocking not wait for any events at all. 
- 
winio: Add support to console handles to handleToHANDLE 
4.16.2.0 May 2022
- 
Shipped with GHC 9.2.2 
- 
Export GHC.Event.Internal on Windows (#21245) 
Documentation Fixes
4.16.1.0 Feb 2022
- 
Shipped with GHC 9.2.2 
- 
The following Foreign C types now have an instance of Ix: CChar, CSChar, CUChar, CShort, CUShort, CInt, CUInt, CLong, CULong, CPtrdiff, CSize, CWchar, CSigAtomic, CLLong, CULLong, CBool, CIntPtr, CUIntPtr, CIntMax, CUIntMax.
4.16.0.0 Nov 2021
- 
Shipped with GHC 9.2.1 
- 
The unary tuple type, Solo, is now exported byData.Tuple.
- 
Add a Typeableconstraint tofromStaticPtrin the classGHC.StaticPtr.IsStatic.
- 
Make it possible to promote Naturals and remove the separateNatkind. For backwards compatibility,Natis now a type synonym forNatural. As a consequence, one must enableTypeSynonymInstancesin order to define instances forNat. Also, different instances forNatandNaturalwon't typecheck anymore.
- 
Add Data.Type.Ordas a module for type-level comparison operations. The(<=?)type operator fromGHC.TypeNats, previously kind-specific toNat, is now kind-polymorphic and governed by theComparetype family inData.Type.Ord. Note that this means GHC will no longer deduce0 <= nfor allnany more.
- 
Add cmpNat,cmpSymbol, andcmpChartoGHC.TypeNatsandGHC.TypeLits.
- 
Add CmpChar,ConsSymbol,UnconsSymbol,CharToNat, andNatToChartype families toGHC.TypeLits.
- 
Add the KnownCharclass,charValandcharVal'toGHC.TypeLits.
- 
Add SemigroupandMonoidinstances forData.Functor.ProductandData.Functor.Compose.
- 
Add Functor,Applicative,Monad,MonadFix,Foldable,Traversable,Eq,Ord,Show,Read,Eq1,Ord1,Show1,Read1,Generic,Generic1, andDatainstances forGHC.Tuple.Solo.
- 
Add Eq1,Read1andShow1instances forComplex; addEq1/2,Ord1/2,Show1/2andRead1/2instances for 3 and 4-tuples.
- 
Remove Data.Semigroup.Optionand the accompanyingoptionfunction.
- 
Make allocaBytesAlignedandallocathrow an IOError when the alignment is not a power-of-two. The underlying primopnewAlignedPinnedByteArray#actually always assumed this but we didn't document this fact in the user facing API until now.Generic1, andDatainstances forGHC.Tuple.Solo.
- 
Under POSIX, System.IO.openFilewill no longer leak a file descriptor if it is interrupted by an asynchronous exception (#19114, #19115).
- 
Additionally export asumfromControl.Applicative
- 
fromInteger :: Integer -> Float/Doublenow consistently round to the nearest value, with ties to even.
- 
Additions to Data.Bits:- 
Newtypes And,Ior,XorandIffwhich wrap their argument, and whoseSemigroupinstances are defined using(.&.),(.|.),xorand\x y -> complement (x `xor` y), respectively.
- 
oneBits :: FiniteBits a => a,oneBits = complement zeroBits.
 
- 
4.15.0.0 Feb 2021
- 
Shipped with GHC 9.0.1 
- 
openFilenow calls theopensystem call with aninterruptibleFFI call, ensuring that the call can be interrupted withSIGINTon POSIX systems.
- 
Make openFilemore tolerant of asynchronous exceptions: more care taken to release the file descriptor and the read/write lock (#18832)
- 
Add hGetContents',getContents', andreadFile'inSystem.IO: Strict IO variants ofhGetContents,getContents, andreadFile.
- 
Add singletonfunction forData.List.NonEmpty.
- 
The planned deprecation of Data.Monoid.FirstandData.Monoid.Lastis scrapped due to difficulties with the suggested migration path.
- 
Data.Semigroup.Optionand the accompanyingoptionfunction are deprecated and scheduled for removal in 4.16.
- 
Add Genericinstances toFingerprint,GiveGCStats,GCFlags,ConcFlags,DebugFlags,CCFlags,DoHeapProfile,ProfFlags,DoTrace,TraceFlags,TickyFlags,ParFlags,RTSFlags,RTSStats,GCStats,ByteOrder,GeneralCategory,SrcLoc
- 
Add rules unpackUtf8,unpack-listUtf8andunpack-appendUtf8toGHC.Base. They correspond to their ascii versions and hopefully make it easier for libraries to handle utf8 encoded strings efficiently.
- 
An issue with list fusion and elemwas fixed.elemapplied to known small lists will now compile to a simple case statement more often.
- 
Add MonadFixandMonadZipinstances forComplex
- 
Add Ixinstances for tuples of size 6 through 15
- 
Correct Boundedinstance and removeEnumandIntegralinstances forData.Ord.Down.
- 
catMaybesis now implemented usingmapMaybe, so that it is both a "good consumer" and "good producer" for list-fusion (#18574)
- 
Foreign.ForeignPtr.withForeignPtris now less aggressively optimised, avoiding the soundness issue reported in #17760 in exchange for a small amount more allocation. If your application regresses significantly and the continuation given towithForeignPtrwill not provably diverge then the previous optimisation behavior can be recovered by instead usingGHC.ForeignPtr.unsafeWithForeignPtr.
- 
Correct Boundedinstance and removeEnumandIntegralinstances forData.Ord.Down.
- 
Data.Foldablemethodsmaximum{,By},minimum{,By},productandsumare now stricter by default, as well as in the class implementation for List.
4.14.0.0 Jan 2020
- 
Bundled with GHC 8.10.1 
- 
Add a TestEqualityinstance for theComposenewtype.
- 
Data.Ord.Downnow has a field name,getDown
- 
Add Bits,Bounded,Enum,FiniteBits,Floating,Fractional,Integral,Ix,Real,RealFrac,RealFloatandStorableinstances toData.Ord.Down.
- 
Fix the integer-gmpvariant ofisValidNatural: Previously it would fail to detect values<= maxBound::Wordthat were incorrectly encoded using theNatJ#constructor.
- 
The type of coercehas been generalized. It is now runtime-representation polymorphic:forall {r :: RuntimeRep} (a :: TYPE r) (b :: TYPE r). Coercible a b => a -> b. The type argumentris marked asInferredto prevent it from interfering with visible type application.
- 
Make FixedandHasResolutionpoly-kinded.
- 
Add HasResolutioninstances forNats.
- 
Add Functor,Applicative,Monad,Alternative,MonadPlus,GenericandGeneric1instances toKleisli
- 
openTempFileis now fully atomic and thread-safe on Windows.
- 
Add isResourceVanishedError,resourceVanishedErrorType, andisResourceVanishedErrorTypetoSystem.IO.Error.
- 
Add newtypes for CSocklen(socklen_t) andCNfds(nfds_t) toSystem.Posix.Types.
- 
Add Functor,ApplicativeandMonadinstances to(,,) a band(,,,) a b c.
- 
Add resizeSmallMutableArray#toGHC.Exts.
- 
Add a Datainstance toWrappedArrow,WrappedMonad, andZipList.
- 
Add IsListinstance forZipList.
4.13.0.0 July 2019
- 
Bundled with GHC 8.8.1 
- 
The final phase of the MonadFailproposal has been implemented:- 
The failmethod ofMonadhas been removed in favor of the method of the same name in theMonadFailclass.
- 
MonadFail(fail)is now re-exported from thePreludeandControl.Monadmodules.
 
- 
- 
Fix Showinstance ofData.Fixed: Negative numbers are now parenthesized according to their surrounding context. I.e.Data.Fixed.showproduces syntactically correct Haskell for expressions likeJust (-1 :: Fixed E2). (#16031)
- 
Support the characters from recent versions of Unicode (up to v. 12) in literals (#5518). 
- 
The StableNametype parameter now has a phantom role instead of a representational one. There is really no reason to care about the type of the underlying object.
- 
Add foldMap', a strict version offoldMap, toFoldable.
- 
The shiftLandshiftRmethods in theBitsinstances ofInt,IntN,Word, andWordNnow throw an overflow exception for negative shift values (instead of being undefined behaviour).
- 
scanrno longer crashes when passed a fusable, infinite list. (#16943)
4.12.0.0 21 September 2018
- 
Bundled with GHC 8.6.1 
- 
The STM invariant-checking mechanism ( alwaysandalwaysSucceeds), which was deprecated in GHC 8.4, has been removed (as proposed in https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0011-deprecate-stm-invariants.rst). This is a bit earlier than proposed in the deprecation pragma included in GHC 8.4, but due to community feedback we decided to move ahead with the early removal.Existing users are encouraged to encapsulate their STM operations in safe abstractions which can perform the invariant checking without help from the runtime system. 
- 
Add a new module GHC.ResponseFile(previously defined in thehaddockpackage). (#13896)
- 
Move the module Data.Functor.Contravariantfrom thecontravariantpackage tobase.
- 
($!)is now representation-polymorphic like($).
- 
Add Applicative(forK1),SemigroupandMonoidinstances inGHC.Generics. (#14849)
- 
asinhforFloatandDoubleis now numerically stable in the face of non-small negative arguments and enormous arguments of either sign. (#14927)
- 
Numeric.showEFloat (Just 0)now respects the user's requested precision. (#15115)
- 
Data.Monoid.Altnow hasFoldableandTraversableinstances. (#15099)
- 
Data.Monoid.Aphas been introduced
- 
Control.Exception.throwis now levity polymorphic. (#15180)
- 
Data.Ord.Downnow has a number of new instances. These include:MonadFix,MonadZip,Data,Foldable,Traversable,Eq1,Ord1,Read1,Show1,Generic,Generic1. (#15098)
4.11.1.0 19 April 2018
- 
Bundled with GHC 8.4.2 
- 
Add the readFieldHashfunction toGHC.Readwhich behaves likereadField, but for a field that ends with a#symbol (#14918).
4.11.0.0 8 March 2018
- 
Bundled with GHC 8.4.1 
- 
System.IO.openTempFileis now thread-safe on Windows.
- 
Deprecated GHC.Stats.GCStatsinterface has been removed.
- 
Add showHFloattoNumeric
- 
Add Div,Mod, andLog2functions on type-level naturals inGHC.TypeLits.
- 
Add Alternativeinstance forZipList(#13520)
- 
Add instances Num,Functor,Applicative,Monad,SemigroupandMonoidforData.Ord.Down(#13097).
- 
Add Semigroupinstance forEventLifetime.
- 
Make Semigroupa superclass ofMonoid; exportSemigroup((<>))fromPrelude; removeMonoidreexport fromData.Semigroup(#14191).
- 
Generalise instance Monoid a => Monoid (Maybe a)toinstance Semigroup a => Monoid (Maybe a).
- 
Add infixl 9 !!declaration forData.List.NonEmpty.!!
- 
Add <&>operator toData.Functor(#14029)
- 
Remove the deprecated Typeable{1..7}type synonyms (#14047)
- 
Make Data.Type.Equality.==a closed type family. It now works for all kinds out of the box. Any modules that previously declared instances of this family will need to remove them. Whereas the previous definition was somewhat ad hoc, the behavior is now completely uniform. As a result, some applications that used to reduce no longer do, and conversely. Most notably,(==)no longer treats the*,j -> k, or()kinds specially; equality is tested structurally in all cases.
- 
Add instances SemigroupandMonoidforControl.Monad.ST(#14107).
- 
The Readinstances forProxy,Coercion,(:~:),(:~~:), andU1now ignore the parsing precedence. The effect of this is thatreadwill be able to successfully parse more strings containing"Proxy"et al. without surrounding parentheses (e.g.,"Thing Proxy") (#12874).
- 
Add iterate', a strict version ofiterate, toData.ListandData.OldList(#3474)
- 
Add Datainstances forIntPtrandWordPtr(#13115)
- 
Add missing MonadFailinstance forControl.Monad.Strict.ST.ST
- 
Make zipWithandzipWith3inlinable (#14224)
- 
Type.Reflection.Appnow matches on function types (fixes #14236)
- 
Type.Reflection.withTypeableis now polymorphic in theRuntimeRepof its result.
- 
Add installSEHHandlerstoMiscFlagsinGHC.RTS.Flagsto determine if exception handling is enabled.
- 
The deprecated functions isEmptyChanandunGetChaninControl.Concurrent.Chanhave been removed (#13561).
- 
Add generateCrashDumpFiletoMiscFlagsinGHC.RTS.Flagsto determine if a core dump will be generated on crashes.
- 
Add generateStackTracetoMiscFlagsinGHC.RTS.Flagsto determine if stack traces will be generated on unhandled exceptions by the RTS.
- 
getExecutablePathnow resolves symlinks on Windows (#14483)
- 
Deprecated STM invariant checking primitives ( checkInv,always, andalwaysSucceeds) inGHC.Conc.Sync(#14324).
- 
Add a FixIOExceptiondata type toControl.Exception.Base, and changefixIOto throw that instead of aBlockedIndefinitelyOnMVarexception (#14356).
4.10.1.0 November 2017
- 
Bundled with GHC 8.2.2 
- 
The file locking primitives provided by GHC.IO.Handlenow use Linux open file descriptor locking if available.
- 
Fixed bottoming definition of clearBitforNatural
4.10.0.0 July 2017
- 
Bundled with GHC 8.2.1 
- 
Data.Type.Bool.Notgiven a type family dependency (#12057).
- 
Foreign.Ptrnow exports the constructors forIntPtrandWordPtr(#11983)
- 
Generic1, as well as the associated datatypes and typeclasses inGHC.Generics, are now poly-kinded (#10604)
- 
New modulesData.BifoldableandData.Bitraversable(previously defined in thebifunctors` package) (#10448)
- 
Data.Eithernow providesfromLeftandfromRight(#12402)
- 
Data.Type.Coercionnow providesgcoerceWith(#12493)
- 
New methods liftReadList(2)andliftReadListPrec(2)in theRead1/Read2classes that are defined in terms ofReadPrecinstead ofReadS, as well as related combinators, have been added toData.Functor.Classes(#12358)
- 
Add Semigroupinstance forIO, as well as forEventandLifetimefromGHC.Event(#12464)
- 
Add Datainstance forConst(#12438)
- 
Added Eq1,Ord1,Read1andShow1instances forNonEmpty.
- 
Add wrappers for blksize_t,blkcnt_t,clockid_t,fsblkcnt_t,fsfilcnt_t,id_t,key_t, andtimer_tto System.Posix.Types (#12795)
- 
Add CBool, a wrapper around C'sbooltype, toForeign.C.Types(#13136)
- 
Raw buffer operations in GHC.IO.FDare now strict in the buffer, offset, and length operations (#9696)
- 
Add plusForeignPtrtoForeign.ForeignPtr.
- 
Add type family AppendSymbol (m :: Symbol) (n :: Symbol) :: SymboltoGHC.TypeLits(#12162)
- 
Add GHC.TypeNatsmodule withNatural-basedKnownNat. TheNatoperations inGHC.TypeLitsare a thin compatibility layer on top. Note: theKnownNatevidence is changed from anIntegerto aNatural.
- 
The type of asProxyTypeOfinData.Proxyhas been generalized (#12805)
- 
liftA2is now a method of theApplicativeclass.liftA2and<*>each have a default implementation based on the other. Various library functions have been updated to useliftA2where it might offer some benefit.liftA2is not yet in thePrelude, and must currently be imported fromControl.Applicative. It is likely to be added to thePreludein the future. (#13191)
- 
A new module, Type.Reflection, exposing GHC's new type-indexed type representation mechanism is now provided.
- 
Data.Dynamicnow exports theDyndata constructor, enabled by the new type-indexed type representation mechanism.
- 
Data.Type.Equalitynow provides a kind heterogeneous type equality evidence type,(:~~:).
- 
The CostCentresXMLconstructor ofGHC.RTS.Flags.DoCostCentreshas been replaced byCostCentresJSONdue to the new JSON export format supported by the cost centre profiler.
- 
The ErrorCallpattern synonym has been given aCOMPLETEpragma so that functions which solely match againErrorCalldo not produce non-exhaustive pattern-match warnings (#8779)
- 
Change the implementations of maximumByandminimumByfromData.Foldableto usefoldl1instead offoldr1. This makes them run in constant space when applied to lists. (#10830)
- 
mkFunTy,mkAppTy, andmkTyConAppfromData.Typeableno longer exist. This functionality is superceded by the interfaces provided byType.Reflection.
- 
mkTyCon3is no longer exported byData.Typeable. This function is replaced byType.Reflection.Unsafe.mkTyCon.
- 
Data.List.NonEmpty.unfoldhas been deprecated in favor ofunfoldr, which is functionally equivalent.
4.9.0.0 May 2016
- 
Bundled with GHC 8.0 
- 
errorandundefinednow print a partial stack-trace alongside the error message.
- 
New errorWithoutStackTracefunction throws an error without printing the stack trace.
- 
The restore operation provided by maskanduninterruptibleMasknow restores the previous masking state whatever the current masking state is.
- 
New GHC.Generics.packageNameoperation
- 
Redesigned GHC.Stack.CallStackdata type. As a result,CallStack'sShowinstance produces different output, andCallStackno longer has anEqinstance.
- 
New GHC.Generics.packageNameoperation
- 
New GHC.Stack.Typesmodule now contains the definition ofCallStackandSrcLoc
- 
New GHC.Stack.Types.emptyCallStackfunction builds an emptyCallStack
- 
New GHC.Stack.Types.freezeCallStackfunction freezes aCallStackpreventing futurepushCallStackoperations from having any effect
- 
New GHC.Stack.Types.pushCallStackfunction pushes a call-site onto aCallStack
- 
New GHC.Stack.Types.fromCallSiteListfunction creates aCallStackfrom a list of call-sites (i.e.,[(String, SrcLoc)])
- 
GHC.SrcLochas been removed
- 
GHC.Stack.showCallStackandGHC.SrcLoc.showSrcLocare now calledGHC.Stack.prettyCallStackandGHC.Stack.prettySrcLocrespectively
- 
add Data.List.NonEmptyandData.Semigroup(to become super-class ofMonoidin the future). These modules were provided by thesemigroupspackage previously. (#10365)
- 
Add selSourceUnpackedness,selSourceStrictness, andselDecidedStrictness, three functions which look up strictness information of a field in a data constructor, to theSelectortype class inGHC.Generics(#10716)
- 
Add URec,UAddr,UChar,UDouble,UFloat,UInt, andUWordtoGHC.Genericsas part of making GHC generics capable of handling unlifted types (#10868)
- 
The Eq,Ord,Read, andShowinstances forU1now use lazier pattern-matching
- 
Keep shift{L,R}onIntegerwith negative shift-arguments from segfaulting (#10571)
- 
Add forkOSWithUnmasktoControl.Concurrent, which is likeforkIOWithUnmask, but the child is run in a bound thread.
- 
The MINIMALdefinition ofArrowis nowarr AND (first OR (***)).
- 
The MINIMALdefinition ofArrowChoiceis nowleft OR (+++).
- 
Exported GiveGCStats,DoCostCentres,DoHeapProfile,DoTrace,RtsTime, andRtsNatfromGHC.RTS.Flags
- 
New function GHC.IO.interruptibleused to correctly implementControl.Exception.allowInterrupt(#9516)
- 
Made PatternMatchFail,RecSelError,RecConError,RecUpdError,NoMethodError, andAssertionFailednewtypes (#10738)
- 
New module Control.Monad.IO.Class(previously provided bytransformerspackage). (#10773)
- 
New modules Data.Functor.Classes,Data.Functor.Compose,Data.Functor.Product, andData.Functor.Sum(previously provided bytransformerspackage). (#11135)
- 
New instances for Proxy:Eq1,Ord1,Show1,Read1. All of the classes are fromData.Functor.Classes(#11756).
- 
New module Control.Monad.Failproviding newMonadFail(fail)class (#10751)
- 
Add GHC.TypeLits.TypeErrorandErrorMessageto allow users to define custom compile-time error messages.
- 
Redesign GHC.Genericsto use type-level literals to represent the metadata of generic representation types (#9766)
- 
The IsStringinstance for[Char]has been modified to eliminate ambiguity arising from overloaded strings and functions like(++).
- 
Move ConstfromControl.Applicativeto its own module inData.Functor.Const. (#11135)
- 
Re-export ConstfromControl.Applicativefor backwards compatibility.
- 
Expand Floatingclass to include operations that allow for better precision:log1p,expm1,log1pexpandlog1mexp. These are not available fromPrelude, but the full class is exported fromNumeric.
- 
New Control.Exception.TypeErrordatatype, which is thrown when an expression fails to typecheck when run using-fdefer-type-errors(#10284)
- 
The bitSizemethod ofData.Bits.Bitsnow has a (partial!) default implementation based onbitSizeMaybe. (#12970)
New instances
- 
Alt,Dual,First,Last,Product, andSumnow haveData,MonadZip, andMonadFixinstances
- 
The datatypes in GHC.Genericsnow haveEnum,Bounded,Ix,Functor,Applicative,Monad,MonadFix,MonadPlus,MonadZip,Foldable,Foldable,Traversable,Generic1, andDatainstances as appropriate.
- 
Maybenow has aMonadZipinstance
- 
AllandAnynow haveDatainstances
- 
Dual,First,Last,Product, andSumnow haveFoldableandTraversableinstances
- 
Dual,Product, andSumnow haveFunctor,Applicative, andMonadinstances
- 
(,) anow has aMonadinstance
- 
ZipListnow hasFoldableandTraversableinstances
- 
Identitynow hasSemigroupandMonoidinstances
- 
IdentityandConstnow haveBits,Bounded,Enum,FiniteBits,Floating,Fractional,Integral,IsString,Ix,Num,Real,RealFloat,RealFracandStorableinstances. (#11210, #11790)
- 
()now has aStorableinstance
- 
Complexnow hasGeneric,Generic1,Functor,Foldable,Traversable,Applicative, andMonadinstances
- 
System.Exit.ExitCodenow has aGenericinstance
- 
Data.Version.Versionnow has aGenericinstance
- 
IOnow has aMonoidinstance
- 
Add MonadPlus IOandAlternative IOinstances (previously orphans intransformers) (#10755)
- 
CallStacknow has anIsListinstance
- 
The field spInfoNameofGHC.StaticPtr.StaticPtrInfohas been removed. The value is no longer available when constructing theStaticPtr.
- 
VecElemandVecCountnow haveEnumandBoundedinstances.
Generalizations
- 
Generalize Debug.Trace.{traceM, traceShowM}fromMonadtoApplicative(#10023)
- 
Redundant typeclass constraints have been removed: - Data.Ratio.{denominator,numerator}have no- Integralconstraint anymore
- TODO
 
- 
Generalise foreverfromMonadtoApplicative
- 
Generalize filterM,mapAndUnzipM,zipWithM,zipWithM_,replicateM,replicateM_fromMonadtoApplicative(#10168)
- 
The Genericinstance forProxyis now poly-kinded (#10775)
- 
Enable PolyKindsin theData.Functor.Constmodule to giveConstthe kind* -> k -> *. (#10039)
4.8.2.0 Oct 2015
- 
Bundled with GHC 7.10.3 
- 
The restore operation provided by maskanduninterruptibleMasknow restores the previous masking state whatever the current masking state is.
- 
Exported GiveGCStats,DoCostCentres,DoHeapProfile,DoTrace,RtsTime, andRtsNatfromGHC.RTS.Flags
4.8.1.0 Jul 2015
- 
Bundled with GHC 7.10.2 
- 
Lifetimeis now exported fromGHC.Event
- 
Implicit-parameter based source location support exposed in GHC.SrcLocandGHC.Stack. See GHC User's Manual for more information.
4.8.0.0 Mar 2015
- 
Bundled with GHC 7.10.1 
- 
Make Applicativea superclass ofMonad
- 
Add reverse application operator Data.Function.(&)
- 
Add Data.List.sortOnsorting function
- 
Add System.Exit.die
- 
Deprecate versionTagsfield ofData.Version.Version. AddmakeVersion :: [Int] -> Versionconstructor function to aid migration to a futureversionTags-lessVersion.
- 
Add IsList Versioninstance
- 
Weaken RealFloat constraints on some Data.Complexfunctions
- 
Add Control.Monad.(<$!>)as a strict version of(<$>)
- 
The Data.Monoidmodule now has thePolyKindsextension enabled, so that theMonoidinstance forProxyare polykinded likeProxyitself is.
- 
Make absandsignumhandle (-0.0) correctly per IEEE-754.
- 
Re-export Data.Word.WordfromPrelude
- 
Add countLeadingZerosandcountTrailingZerosmethods toData.Bits.FiniteBitsclass
- 
Add Data.List.unconslist destructor (#9550)
- 
Export Monoid(..)fromPrelude
- 
Export Foldable(..)fromPrelude(hidingfold,foldl',foldr', andtoList)
- 
Export Traversable(..)fromPrelude
- 
Set fixity for Data.Foldable.{elem,notElem}to match the conventional one set forData.List.{elem,notElem}(#9610)
- 
Turn toList,elem,sum,product,maximum, andminimumintoFoldablemethods (#9621)
- 
Replace the Data.List-exported functionsall, and, any, concat, concatMap, elem, find, product, sum, mapAccumL, mapAccumRby re-exports of their generalised Data.Foldable/Data.Traversablecounterparts. In other words, unqualified imports ofData.ListandData.Foldable/Data.Traversableno longer lead to conflicting definitions. (#9586)
- 
New (unofficial) module GHC.OldListcontaining only list-specialised versions of the functions fromData.List(in other words,GHC.OldListcorresponds tobase-4.7.0.2'sData.List)
- 
Replace the Control.Monad-exported functionssequence_, msum, mapM_, forM_, forM, mapM, sequenceby re-exports of their generalised Data.Foldable/Data.Traversablecounterparts. In other words, unqualified imports ofControl.MonadandData.Foldable/Data.Traversableno longer lead to conflicting definitions. (#9586)
- 
Generalise Control.Monad.{when,unless,guard}fromMonadtoApplicativeand fromMonadPlustoAlternativerespectively.
- 
Generalise Control.Monad.{foldM,foldM_}toFoldable
- 
scanr,mapAccumLandfilterMnow take part in list fusion (#9355, #9502, #9546)
- 
Remove deprecated Data.OldTypeable(#9639)
- 
New module Data.Bifunctorproviding theBifunctor(bimap,first,second)class (previously defined inbifunctorspackage) (#9682)
- 
New module Data.Voidproviding the canonical uninhabited typeVoid(previously defined invoidpackage) (#9814)
- 
Update Unicode class definitions to Unicode version 7.0 
- 
Add Alt, anAlternativewrapper, toData.Monoid. (#9759)
- 
Add isSubsequenceOftoData.List(#9767)
- 
The arguments to ==andeqinData.List.nubandData.List.nubByare swapped, such thatData.List.nubBy (<) [1,2]now returns[1]instead of[1,2](#2528, #3280, #7913)
- 
New module Data.Functor.Identity(previously provided bytransformerspackage). (#9664)
- 
Add scanl', a strictly accumulating version ofscanl, toData.ListandData.OldList. (#9368)
- 
Add fillBytestoForeign.Marshal.Utils.
- 
Add new displayExceptionmethod toExceptiontypeclass. (#9822)
- 
Add Data.Bits.toIntegralSized, a size-checked version offromIntegral. (#9816)
- 
New module Numeric.Naturalproviding newNaturaltype representing non-negative arbitrary-precision integers. TheGHC.Naturalmodule exposes additional GHC-specific primitives. (#9818)
- 
Add (Storable a, Integeral a) => Storable (Ratio a)instance (#9826)
- 
Add Storable a => Storable (Complex a)instance (#9826)
- 
New module GHC.RTS.Flagsthat provides accessors to runtime flags.
- 
Expose functions for per-thread allocation counters and limits in GHC.ConcdisableAllocationLimit :: IO () enableAllocationLimit :: IO () getAllocationCounter :: IO Int64 setAllocationCounter :: Int64 -> IO ()together with a new exception AllocationLimitExceeded.
- 
Make read . show = idforData.Fixed(#9240)
- 
Add callocandcallocBytestoForeign.Marshal.Alloc. (#9859)
- 
Add callocArrayandcallocArray0toForeign.Marshal.Array. (#9859)
- 
Restore invariant in Data (Ratio a)instance (#10011)
- 
Add/expose rnfTypeRep,rnfTyCon,typeRepFingerprint, andtyConFingerprinthelpers toData.Typeable.
- 
Define proper MINIMALpragma forclass Ix. (#10142)
4.7.0.2 Dec 2014
- 
Bundled with GHC 7.8.4 
- 
Fix performance bug in Data.List.inits(#9345)
- 
Fix handling of null bytes in Debug.Trace.trace(#9395)
4.7.0.1 Jul 2014
- 
Bundled with GHC 7.8.3 
- 
Unhide Foreign.ForeignPtrin Haddock (#8475)
- 
Fix recomputation of TypeRepinTypeabletype-application instance (#9203)
- 
Fix regression in Data.Fixed Read instance (#9231) 
- 
Fix fdReadyto honorFD_SETSIZE(#9168)
4.7.0.0 Apr 2014
- 
Bundled with GHC 7.8.1 
- 
Add /Since: 4.[4567].0.0/Haddock annotations to entities denoting the package version, when the given entity was introduced (or its type signature changed in a non-compatible way)
- 
The Control.Categorymodule now has thePolyKindsextension enabled, meaning that instances ofCategoryno longer need be of kind* -> * -> *.
- 
There are now FoldableandTraversableinstances forEither a,Const r, and(,) a.
- 
There are now Show,Read,Eq,Ord,Monoid,Generic, andGeneric1instances forConst.
- 
There is now a Datainstance forData.Version.
- 
A new Data.Bits.FiniteBitsclass has been added to represent types with fixed bit-count. The existingBitsclass is extended with abitSizeMaybemethod to replace the now obsoletebitsizemethod.
- 
Data.Bits.Bitsgained a newzeroBitsmethod which completes theBitsAPI with a direct way to introduce a value with all bits cleared.
- 
There are now BitsandFiniteBitsinstances forBool.
- 
There are now Eq,Ord,Show,Read,Generic. andGeneric1instances forZipList.
- 
There are now Eq,Ord,ShowandReadinstances forDown.
- 
There are now Eq,Ord,Show,ReadandGenericinstances for types in GHC.Generics (U1,Par1,Rec1,K1,M1,(:+:),(:*:),(:.:)).
- 
Data.Monoid: There are nowGenericinstances forDual,Endo,All,Any,Sum,Product,First, andLast; as well asGeneric1instances forDual,Sum,Product,First, andLast.
- 
The Data.Monoid.{Product,Sum}newtype wrappers now haveNuminstances.
- 
There are now Functorinstances forSystem.Console.GetOpt'sArgOrder,OptDescr, andArgDescr.
- 
A zero-width unboxed poly-kinded Proxy#was added toGHC.Prim. It can be used to make it so that there is no the operational overhead for passing around proxy arguments to model type application.
- 
New Data.Proxymodule providing a concrete, poly-kinded proxy type.
- 
New Data.Coercemodule which exports the newCoercibleclass together with thecoerceprimitive which provide safe coercion (wrt role checking) between types with same representation.
- 
Control.Concurrent.MVarhas a new implementation ofreadMVar, which fixes a long-standing bug wherereadMVaris only atomic if there are no other threads runningputMVar.readMVarnow is atomic, and is guaranteed to return the value from the firstputMVar. There is also a newtryReadMVarwhich is a non-blocking version.
- 
New Control.Concurrent.MVar.withMVarMaskedwhich executesIOaction with asynchronous exceptions masked in the same style as the existingmodifyMVarMaskedandmodifyMVarMasked_.
- 
New threadWait{Read,Write}STM :: Fd -> IO (STM (), IO ())functions added toControl.Concurrentfor waiting on FD readiness with STM actions.
- 
Expose Data.Fixed.Fixed's constructor.
- 
There are now byte endian-swapping primitives byteSwap{16,32,64}available inData.Word, which use optimized machine instructions when available.
- 
Data.Boolnow exportsbool :: a -> a -> Bool -> a, analogously tomaybeandeitherin their respective modules.
- 
Data.Eithernow exportsisLeft, isRight :: Either a b -> Bool.
- 
Debug.Tracenow exportstraceId,traceShowId,traceM, andtraceShowM.
- 
Data.Functornow exports($>)andvoid.
- 
Rewrote portions of Text.Printf, and made changes toNumeric(addedNumeric.showFFloatAltandNumeric.showGFloatAlt) andGHC.Float(addedformatRealFloatAlt) to support it. The rewritten version is extensible to user types, adds a "generic" format specifier "%v", extends theprintfspec to support much of C'sprintf(3)functionality, and fixes the spurious warnings about usingText.Printf.printfat(IO a)while ignoring the return value. These changes were contributed by Bart Massey.
- 
The minimal complete definitions for all type-classes with cyclic default implementations have been explicitly annotated with the new {-# MINIMAL #-}pragma.
- 
Control.Applicative.WrappedMonad, which can be used to convert aMonadto anApplicative, has now aMonad m => Monad (WrappedMonad m)instance.
- 
There is now a Genericand aGeneric1instance forWrappedMonadandWrappedArrow.
- 
Handle ExitFailure (-sig)on Unix by killing process with signalsig.
- 
New module Data.Type.Boolproviding operations on type-level booleans.
- 
Expose System.Mem.performMinorGCfor triggering minor GCs.
- 
New System.Environment.{set,unset}Envfor manipulating environment variables.
- 
Add Typeableinstance for(->)andRealWorld.
- 
Declare CPP header <Typeable.h>officially obsolete as GHC 7.8+ does not support hand-writtenTypeableinstances anymore.
- 
Remove (unmaintained) Hugs98 and NHC98 specific code. 
- 
Optimize System.Timeout.timeoutfor the threaded RTS.
- 
Remove deprecated functions unsafeInterleaveST,unsafeIOToST, andunsafeSTToIOfromControl.Monad.ST.
- 
Add a new superclass SomeAsyncExceptionfor all asynchronous exceptions and makes the existingAsyncExceptionandTimeoutexception children ofSomeAsyncExceptionin the hierarchy.
- 
Remove deprecated functions blocked,unblock, andblockfromControl.Exception.
- 
Remove deprecated function forkIOUnmaskedfromControl.Concurrent.
- 
Remove deprecated function unsafePerformIOexport fromForeign(still available viaSystem.IO.Unsafe.unsafePerformIO).
- 
Various fixes and other improvements (see Git history for full details).