1.7. Release notes for version 7.4.1

The significant changes to the various parts of the compiler are listed in the following sections. There have also been numerous bug fixes and performance improvements over the 7.2 branch.

1.7.1. Highlights

The highlights, since the 7.0 branch, are:

  • The Num class no longer has Eq or Show superclasses. A number of other classes and functions have therefore gained explicit Eq or Show constraints, rather than relying on a Num constraint to provide them.

    You can make code that works with both Haskell98/Haskell2010 and GHC by:

    • Whenever you make a Num instance of a type, also make Show and Eq instances, and

    • Whenever you give a function, instance or class a Num t constraint, also give it Show t and Eq t constraints.

  • There is a new feature Safe Haskell (-XSafe, -XTrustworthy, -XUnsafe): Section 7.23, “Safe Haskell”. The design has changed since 7.2.

  • There is a new feature kind polymorphism (-XPolyKinds): Section 7.8.1, “Kind polymorphism”. A side-effect of this is that, when the extension is not enabled, in certain circumstances kinds are now defaulted to * rather than being inferred.

  • There is a new feature constraint kinds (-XConstraintKinds): Section 7.10, “The Constraint kind”.

  • It is now possible to give any sort of declaration at the ghci prompt: Section 2.4.4, “Type, class and other declarations”.

  • The profiling and hpc implementations have been merged and overhauled. Visible changes include renaming of profiling flags and the cost-centre stacks have a new semantics, which should in most cases result in more useful and intuitive profiles. The +RTS -xc flag now also gives a stack trace.

  • It is now possible to write compiler plugins: Section 9.3, “Compiler Plugins”.

  • DPH support has been significantly improved.

  • There is now preliminary support for registerised compilation on the ARM platform, using LLVM.

1.7.2. Full details

1.7.2.1. Language

  • GHC previously accepted this code:

    data T f = T
    
    class C a where
        t :: f a -> T f
    

    inferring the kind of f as * -> *, but it now (correctly, according to the Haskell 98 and Haskell 2010 standards) rejects it. You need to write this instead:

    {-# LANGUAGE KindSignatures #-}
    
    data T (f :: * -> *) = T
    
    class C a where
        t :: f a -> T f
    
  • When the new DataKinds extension is enabled, suitable user-defined datatypes are automatically "promoted" to kinds, e.g. Nat here:

    data Nat = Zero | Succ Nat
    data Vector :: * -> Nat -> * where
        VNil :: Vector a Zero
        VCons :: a -> Vector a n -> Vector a (Succ n)
    

    See Section 7.8.2, “Datatype promotion” for more information.

  • There is a new extension PolyKinds which make it possible for kinds to be polymorphic. For example, instead of

    class Typeable (t :: *) where
      typeOf :: t -> TypeRep
    
    class Typeable1 (t :: * -> *) where
      typeOf1 :: t a -> TypeRep
    
    [...]
    
    instance Typeable  Int  where typeOf _ = TypeRep
    instance Typeable1 []   where typeOf _ = TypeRep
    

    you can now say

    data Proxy t = Proxy
    
    class Typeable t where
      typeOf :: Proxy t -> TypeRep
    
    instance Typeable Int  where typeOf _ = TypeRep
    instance Typeable []   where typeOf _ = TypeRep
    

    and the kind of Proxy is polymorphic: forall k. k -> *.

    This feature is not yet fully mature, but please do file bug reports if you run into problems. See Section 7.8.1, “Kind polymorphism” for more information.

  • The Safe Haskell feature, new in GHC 7.2, has been redesigned in GHC 7.4. The motivation was to stop Safe Haskell from causing compilation failures for people not interested in using it.

    GHC now tries to infer whether a module is safe, unless the new -fno-safe-infer flag is given. Therefore, as well as the old -XSafe, there is now a -XUnsafe flag to explicitly state that a module should be treated as unsafe. The old -XSafeImports has been removed.

    The new flags -fwarn-safe and -fwarn-unsafe give warnings when a module is inferred to be safe or unsafe, respectively.

    There is a new flag -fpackage-trust. This controls whether packages containing imported trustworthy modules must be marked as trusted.

  • There is now a NOUNPACK pragma, which does the opposite of the existing PACK pragma. It is mainly useful when -funbox-strict-fields has been used, allowing you to declare that certain fields should not be unpacked.

  • GHC now requires, as per the standard, that if a newtype is used in an FFI declaration, then the constructor for that type must be in scope. For now you only get a warning if it is not, but in the future this will be an error.

  • There is a new extension ConstraintKind which adds a new kind, called Constraint, to GHC's type system. Then, for example,

    Show :: * -> Constraint
    (?x::Int) :: Constraint
    (Int ~ a) :: Constraint
    

    You can now write <em>any</em> type with kind Constraint on the left of =>, i.e. you can use type synonyms, type variables, indexed types, etc.

  • It is now possible to derive an Eq instance for types with no constructors.

  • In the MonadComprehensions extension, the then group by e form has been removed. You now need to explicitly say then group by e using groupWith.

  • There is a new extension TraditionalRecordSyntax which is on by default. When turned off, the standard Haskell record syntax cannot be used.

  • In DPH, it is now possible to vectorise things imported from other modules.

  • In DPH, the VECTORISE and VECTORISE SCALAR pragmas now have type, class and instance variants. See VectPragma for more details.

  • The -fdph-seq, -fdph-par, -fdph-this and -fdph-none flags have been removed. The vectoriser is now controlled by which Data.Array.Parallel and Data.Array.Parallel.Prim modules are in scope.

  • GHC now warns consistently about unused type variables.

  • GHC now implements the static pattern semantics as clarified by the Haskell' committee, i.e. the binding p = e is now equivalent to

    t = e
    f = case t of p -> f
    g = case t of p -> g
    

    where f and g are the variables bound by p.

  • The MonoPatBinds extension is now deprecated, and has no effect.

  • GHC will now reject a declaration if it infers a type for it that is impossible to use unambiguously. For example, given

    class Wob a b where
        to :: a -> b
        from :: b -> a
    
    foo x = [x, to (from x)]
    

    GHC would infer the ambiguous type

    foo :: forall a b. Wob a b => b -> [b]
    

    but it is impossible to use foo as a will always be ambiguous, so the declaration is rejected.

  • It is now possible for associated types to have fresh parameters, e.g. this is now allowed:

    class C a where
        type T a b :: *
    
    instance C Int
        type T Int b = b -> b
    

    where T has a type index b that is not one of the class variables.

  • It is now possible for multiple associated type declarations to be given in a single instance, e.g.

    class C a where
        type T a x :: *
    
    data A
    data B
    
    instance C Int where
        type T Int A = Int
        type T Int B = Bool
    
  • The import and export of type family data constructors has been refined. You now need to be more explicit about what should be exported.

  • Associated type default declarations are now fully supported. These allow you to specify a default definition for a type that will be used if an instance doesn't define its own type, e.g.

    class Cls a where
        type Typ a
        type Typ a = Maybe a
                  
    instance Cls Int where
    

    See Section 7.7.3.2, “Associated type synonym defaults” for more information.

  • You can now specify what simplifier phases SPECIALISE pragmas should be applied in, in the same way that you could for RULE pragmas, e.g. to specialise foo only in phase 1 use:

    {-# SPECIALISE [1] foo :: Int -> Int #-}
    
  • The typechecker is now able to do full constraint solving under a for-all, i.e. it can cope with the unification forall a. t1 ~ forall a. t2.

  • The kind ? has been renamed to OpenKind, and ?? to ArgKind.

1.7.2.2. Compiler

  • The recompilation checker now takes into account what flags were used when compiling. For example, if you first run ghc -c Foo.hs, and then ghc -DBAR -c Foo.hs, then GHC will now recompile Foo.hs.

  • The recompilation checker now also tracks files that are #included in Haskell sources.

    Note that we still don't get #included files in the ghc -M output.

  • The simplifier now maintains a count of how much transformation it does, and prints a warning if that exceeds a limit defined by the new -fsimpl-tick-factor=N flag (default is 100). The intention is to detect when it seems likely that GHC has gone into an infinite loop. In the future, GHC may give an error when the limit is exceeded.

  • There is a new flag -fpedantic-bottoms which makes GHC be more precise about its treatment of bottoms. In particular, it stops GHC eta-expanding through case expressions (which means performance can be worse).

  • GHC now knows how to call gcc to compile objective-c++ (.mm or .M files).

  • The -optm flag, which allowed extra arguments to be passed to the mangler, is now deprecated and does nothing. It will be removed in a future release.

  • GHC now works with LLVM version 3.0, and requires at least version 2.8.

  • We now pass gcc -no_compact_unwind on OS X x86 (as well as x86_64), in order to avoid the

    ld: warning: could not create compact unwind for .LFB3: non-standard register 5 being saved in prolog
    

    warning.

  • The context stack depth, which defines how deeply the type constraint solver may reason, has been increased from 20 to 200, as some people were running into the limit.

  • On x86, the new -msse4.2 flag tells GHC that it may use SSE4.2 instructions.

  • There is a new flag -dno-llvm-mangler which means the LLVM mangler isn't run. It is mainly useful when debugging GHC.

  • There is a new flag -dsuppress-var-kinds which can make the output clearer when -dppr-debug is also used.

  • The -keep-llvm-files flag now implies -fllvm.

  • The -split-objs flag can now be used with the LLVM backend.

  • There is a new flag -dumpdir which allows you to specify the directory in which the output of the -ddump-* flags should be put when -ddump-to-file is used. The -outputdir flag will now also set the dump directory.

  • Bitrotted registerised ports for mips, ia64, alpha, hppa1 and m68k have been removed.

1.7.2.3. GHCi

  • It is now possible to give any top-level declaration at the GHCi prompt, e.g.

    Prelude> data D = C Int
    Prelude> let f (C i) = i in f (C 5)
    5
    

    The current set of declarations are shown by the new :show bindings command. See Section 2.4.4, “Type, class and other declarations”. for more information

  • There is a new GHCi command :kind! which is like :kind except it also prints the normalised type; e.g., given

    type family F a
    type instance F Int = Bool
    

    we get

    *Main> :kind F Int
    F Int :: *
    *Main> :kind! F Int
    F Int :: *
    = Bool
    
  • There is a new flag -fno-ghci-history which stops GHCi from loading and saving the GHCi command history from and to ~/.ghc/ghci_history.

  • Library loading in GHCi has been improved; in particular, loading libstdc++.so now works, and GHCi will use .a archives to satisfy -lfoo flags on its commandline.

  • When using :load, GHCi will not unload the current modules until it has successfully loaded the new ones. This fixes this old problem:

    Prelude> :l foo
    target `foo' is not a module name or a source file
    >
    

1.7.2.4. Template Haskell

  • GHC used to treat \| and \] within quasiquote as escaped characters, parsing them as | and ] respectively. It now does not treat anything specially; if you would like to be able to include sequences such as |] inside a quasi-quote then you must define your own escaping mechanism in the quasi-quoter.

  • The interaction between the recompilation checker and Template Haskell has been improved. We now track which modules are used by splices, and if a module is changed then any splices that use it will need to be rerun.

1.7.2.5. Profiling

  • The profiling, coverage (HPC) and breakpoints infrastructure has been overhauled, and the three systems are now much more unified.

    As a result of these changes, the cost-centre stacks have a new semantics, which should give more intuitive profiling results. HPC is also slightly improved: In particular, unused derived instances and record field names are now highlighted, and entry counts are more accurate.

    The +RTS -xc flag now also gives a stack trace.

    The -auto-all flag has been renamed to -fprof-auto, -auto renamed to -fprof-auto-exported, and -caf-all renamed to -fprof-cafs. The old names are also still accepted for now.

    There are also two new flags. The -fprof-auto-top flag annotates all top-level bindings with SCCs, and the -fprof-auto-calls flag adds SCCs to all applications. This last flag is particularly useful for stack traces.

    Another new flag -fprof-no-count-entries indicates that entry counts do not need to be maintained. This makes profiled code faster, and is particularly useful when heap profiling, as heap profiles do not use the entry counts.

  • Cost centre names are now in UTF8 rather than Latin-1.

  • There is now better heap profiling support for pinned objects (e.g. ByteStrings). Previously we were completely ignoring them, due to technical difficulties, but now count all the pinned object space (including gaps between pinned objects) as being type ARR_WORDS. This isn't ideal, but at least we do now account for the memory, and give it the right type.

  • The quotes in an SCC pragma can now be omitted if the SCC name is a valid Haskell variable name, e.g. {-# SCC my_function #-} expr.

  • It is now possible to use profiling when running on multiple capabilities (i.e. when running with +RTS -N). There is a new built-in cost centre called IDLE, which records the ticks of idle capabilities.

    There are still some rough edges. In particular, it is strongly recommended that you use the -fno-prof-count-entries flag or the program will run very slowly.

1.7.2.6. Event logging

  • There are new eventlog events EVENT_SPARK_COUNTERS EVENT_SPARK_CREATE EVENT_SPARK_DUD EVENT_SPARK_OVERFLOW EVENT_SPARK_RUN EVENT_SPARK_STEAL EVENT_SPARK_FIZZLE and EVENT_SPARK_GC for giving information about sparks.

  • There is a new eventlog event EVENT_WALL_CLOCK_TIME which is used for matching the time of events between different processes.

  • There is a new eventlog event EVENT_THREAD_LABEL which is emitted by the existing GHC.Conc.labelThread function. This allows tools such as ThreadScope to use thread labels rather than thread numbers.

  • The eventlog class g is no longer ignored, but now controls whether events related to the garbage collector are emitted. There are also new event classes p and f, which contain sampled (approximate) and full (fully accurate) spark-related events respectively, and u which contains user events.

    There is also a meta eventlog class a which, when enabled or disabled, enables or disables all the classes.

    By default, all classes apart from f are enabled.

  • On Windows, if the program name ends in .exe then the .exe is removed when making the eventlog filename.

1.7.2.7. Runtime system

  • The restrictions on what +RTS flags are available by default has changed. By default, you can now use the -t, -T, -s and -S RTS flags, provided you do not give them a filename argument.

    Additionally, when linking with -threaded, you can now use the +RTS -N flag without having to link with -rtsopts. Also, when linking with "developer" ways (-debug, -eventlog and -prof) all the way-specific flags are allowed; for example, +RTS -h is allowed when linking with -prof.

  • There is a new RTS flag -T, which makes the RTS collect statistics (memory usage, etc) but not give any output. The new GHC.Stats module in the base package provides access to this data.

  • You can now give the RTS flag -H (without an argument) and the runtime system will infer a sensible value to use. See Section 4.17.3, “RTS options to control the garbage collector” for more details.

  • When using -no-hs-main and starting the runtime system yourself, if you wish to pass RTS flags then you will now need to use the new hs_init_ghc function. See Section 8.2.1.1, “Using your own main() for details.

  • The runtime system now supports using forkProcess when running with multiple capabilities (+RTS -N).

1.7.2.8. Build system

  • You can now build GHC with Alex 3.0.

  • On OS X, with XCode 4.0 and 4.1, GHC will use gcc-4.2 rather than gcc (which is based on LLVM, and currently produces slower code for GHC).

  • There is now preliminary support for registerised compilation on the ARM platform, using LLVM.

  • Dynamic libraries are now supported on OSX x86_64.

  • GHCi is now supported on kfreebsdgnu platforms.

  • GHC now recognises the s390x architecture.

1.7.3. Libraries

There have been some changes that have effected multiple libraries:

  • The Num class no longer has Eq or Show superclasses. A number of other classes and functions have therefore gained explicit Eq or Show constraints, rather than relying on a Num constraint to provide them.

    You can make code that works with both Haskell98/Haskell2010 and GHC by:

    • Whenever you make a Num instance of a type, also make Show and Eq instances, and

    • Whenever you give a function, instance or class a Num t constraint, also give it Show t and Eq t constraints.

  • Many modules have been given Safe Haskell Safe, Unsafe or Trustworthy annotations.

1.7.3.1. array

  • Version number 0.4.0.0 (was 0.3.0.3)

  • There are new modules Data.Array.IO.Safe, Data.Array.MArray.Safe, Data.Array.ST.Safe and Data.Array.Storable.Safe containing just the safe (in the Safe Haskell sense of the term) parts of their respective APIs, and Data.Array.Unsafe containing the unsafe parts of the Data.Array API.

  • There is a new module Data.Array.Storable.Internals which exports some internal functions for the Data.Array.Storable API.

  • Data.Array.IO.castIOUArray is now deprecated; use Data.Array.Unsafe.castIOUArray instead.

  • Data.Array.ST.castSTUArray is now deprecated; use Data.Array.Unsafe.castSTUArray instead.

  • Data.Array.MArray.unsafeFreeze and Data.Array.MArray.unsafeThaw are now deprecated; use Data.Array.Unsafe.unsafeFreeze and Data.Array.Unsafe.unsafeThaw instead.

  • Data.Array.Storable.unsafeForeignPtrToStorableArray is now deprecated; use Data.Array.Unsafe.unsafeForeignPtrToStorableArray instead.

1.7.3.2. base

  • Version number 4.5.0.0 (was 4.4.1.0)

  • Data.Monoid now exports <> as an infix synonym for mappend It associates to the right, and has precedence 6.

  • Data.List has a new function dropWhileEnd, which is similar to dropWhile except it removes the suffix of characters matching the predicate, rather than the prefix of characters.

  • The Data.Bits.Bits class has two new methods unsafeShiftL and unsafeShiftR which perform shifts on the assumption that the amount to be shifted by is positive.

  • The Data.Bits.Bits class has a new method popCount which returns the number of bits that are set in the value.

  • The C* types exported by Foreign.C.Types and System.Posix.Types are now exported non-abstractly, as the FFI now requires that the constructors for newtypes are visible.

  • In Data.Typeable, tyConString is now deprecated, in favour of the new tyConPackage, tyConModule and tyConName functions.

  • GHC.Exts.traceEvent is now deprecated. You should use the new Debug.Trace.traceEventIO instead. There is also a new function Debug.Trace.traceEvent that is analogous to Debug.Trace.trace.

  • Debug.Trace.putTraceMsg is now deprecated in favour of the new function Debug.Trace.traceIO.

  • When a program is compiled with -prof, GHC's run-time system now makes a stack trace (based on the SCCs defined) available to the program.

    There is a new function GHC.Exts.currentCallStack which returns the stack trace as a list of Strings.

    There is also a new function Debug.Trace.traceStack which is like Debug.Trace.trace but also prints a call stack trace if one is available.

  • GHC.Conc has a new function, getNumProcessors, which returns the number of CPUs that the machine has.

  • GHC.Conc has a new function, setNumCapabilities, which sets the number of Haskell threads which can run simultaneously. Currently GHC only allows increasing the number of running threads.

  • The encodings used for the filesystem, for foreign calls, and for the locale, are now mutable. In order to alter them you need to use setLocaleEncoding, setFileSystemEncoding and setForeignEncoding from GHC.IO.Encoding.

  • Assertions are now better behaved; if an assertion fails then you will get an assertion error, rather than another _|_ result from the expression that the assertion guards.

  • A bug in the behaviour of scaleFloat on Float and Double when used with non-finite values has been fixed.

  • A bug which meant that System.IO.fixIO was not threadsafe has been fixed.

    There is also now a new System.IO.Unsafe.unsafeFixIO that may be more efficient, but is not guaranteed to be threadsafe.

  • There is a new module GHC.Stats which exports a function getGCStats which gives some info from the runtime system using the GCStats type.

  • There is a new type GHC.Exts.Constraint which is used with the ConstraintKind extension.

  • The Control.Monad.Group module, and the MonadGroup class that it defined, have been removed.

  • Support for platforms where word size is less than 32bits has been removed.

1.7.3.3. bin-package-db

  • This is an internal package, and should not be used.

1.7.3.4. binary

  • Version number 0.5.0.3 (was 0.5.0.2) It is now exposed by default.

1.7.3.5. bytestring

  • Version number 0.9.2.1 (was 0.9.2.0)

1.7.3.6. Cabal

  • Version number 1.14.0.0 (was 1.12.0.0)

  • For details of the changes to the Cabal library, plese see the Cabal changelog.

1.7.3.7. containers

  • Version number 0.4.2.1 (was 0.4.1.0)

  • Data.Map now exports foldr, foldr', foldl and foldl'.

  • Data.Set now exports foldr, foldr', foldl and foldl'.

  • Data.IntMap now exports foldr, foldr', foldl, foldl', foldrWithKey, foldrWithKey', foldlWithKey and foldlWithKey'.

  • Data.IntSet now exports foldr, foldr', foldl and foldl'.

  • Data.Map.foldWithKey is no longer deprecated, although it is expected to be deprecated again in the future.

  • There are now NFData instance for Data.Map.Map, Data.Set.Set, Data.IntMap.IntMap, Data.IntSet.IntSet and Data.Tree.Tree.

1.7.3.8. deepseq

  • New package, version 1.3.0.0.

1.7.3.9. directory

  • Version number 1.1.0.2 (was 1.1.0.1)

1.7.3.10. extensible-exceptions

  • Version number 0.1.1.4 (was 0.1.1.3)

1.7.3.11. filepath

  • Version number 1.3.0.0 (was 1.2.0.1)

  • A bug, which caused normalise "/" to return "/." rather than "/", has been fixed.

1.7.3.12. ghc-prim

  • This is an internal package, and should not be used.

1.7.3.13. haskell98

  • Version number 2.0.0.1 (was 2.0.0.0)

1.7.3.14. haskell2010

  • Version number 1.1.0.1 (was 1.1.0.0)

1.7.3.15. hoopl

  • Version number 3.8.7.3 (was 3.8.7.2)

  • A new liftFuel method has been added to Compiler.Hoopl.Fuel.FuelMonadT.

1.7.3.16. hpc

  • Version number 0.5.1.1 (was 0.5.1.0)

1.7.3.17. integer-gmp

  • Version number 0.4.0.0 (was 0.3.0.0)

  • There is a new module GHC.Integer.GMP.Prim that exports the Haskell imports of the GMP functions. They are no longer exported by GHC.Integer.GMP.Internals.

  • GHC.Integer.GMP.Internals now exports gcdInteger and lcmInteger. They are no longer exported by GHC.Integer.

  • There is a new function mkInteger exported from GHC.Integer.Type and GHC.Integer. It constructs an Integer from a Bool (indicating the sign) and a list of Ints (which provide the value, in 31-bit chunks, least-significant first).

1.7.3.18. old-locale

  • Version number 1.0.0.4 (was 1.0.0.3)

1.7.3.19. old-time

  • Version number 1.1.0.0 (was 1.0.0.7)

  • A bug which caused System.Time.formatCalendarTime to show a value 1 too low for the %j format specifier has been fixed.

1.7.3.20. pretty

  • Version number 1.1.1.0 (was 1.1.0.0)

  • The recommended module is now Text.PrettyPrint rather than Text.PrettyPrint.HughesPJ.

  • Both modules now export first, which takes two documents and returns the first provided it is non-empty, and the second otherwise.

  • Both modules now export reduceDoc.

1.7.3.21. process

  • Version number 1.1.0.1 (was 1.1.0.0)

1.7.3.22. template-haskell

  • Version number 2.7.0.0 (was 2.6.0.0)

  • The Language.Haskell.TH.Syntax.Quasi class now has a qAddDependentFile method, which splices can use to indicate that the result of the splice depends upon the contents of a file. This tells the compiler that if the file has changed then it will need to recompile the module containing the splice.

    There is also a new helper function addDependentFile in Language.Haskell.TH.Syntax.

  • The Language.Haskell.TH.Syntax.Exp type now has UInfixE and ParensE constructors, and Language.Haskell.TH.Syntax.Pat gains corresponding UInfixP and ParensP constructors.

    There are corresponding helper functions uInfixE, parensE, uInfixP and parensP defined in Language.Haskell.TH.Lib and re-exported by Language.Haskell.TH.

    These constructors are used for infix expressions where the fixities of the operators are not known. The compiler will look up the fixities and reassociate the expression as necessary.

    There is also a new value Language.Haskell.TH.Ppr.unopPrec used when pretty-printing expressions of unknown fixity.

  • The Language.Haskell.TH.Syntax.Strict type now has an Unpacked constructor, which corresponds to the {-# UNPACK #-} pragma. There is a corresponding helper function Language.Haskell.TH.Lib.unpacked.

  • The Language.Haskell.TH.Syntax.Info type has a new constructor FamilyI, used when reifying a data or type family's name.

  • The Language.Haskell.TH.Syntax.ClassInstance type has been removed, and the ClassI constructor of Language.Haskell.TH.Syntax.Info now contains [InstanceDec] rather than [ClassInstance].

    Language.Haskell.TH.Syntax.InstanceDec is a new type synonym of Language.Haskell.TH.Syntax.Dec, but its constructor is guaranteed to be one of InstanceD (with empty [Dec]), DataInstD or NewtypeInstD (with empty derived [Name]), or TySynInstD.

    The qClassInstances method of the Language.Haskell.TH.Syntax.Quasi class has been replaced with a qReifyInstances method.

    Likewise, in Language.Haskell.TH.Syntax, the isClassInstance and classInstances functions have been replaced by isInstance and reifyInstances. They are also re-exported by Language.Haskell.TH.

  • The Language.Haskell.TH.Syntax.Quasi class now has a qLookupName method, which takes a Bool indictaing whether you are looking for a type or a value, and a String. It then tries to look up the name, returning a Maybe Name in the monad.

    There are also new helper functions lookupTypeName and lookupValueName, which are also re-exported by Language.Haskell.TH.

  • The Language.Haskell.TH.Syntax.Quasi class now has an Applicative superclass, rather than a Functor superclass. There is also now an Applicative instance for Language.Haskell.TH.Syntax.Q.

  • The NameSpace type is now abstractly re-exported by Language.Haskell.TH.

1.7.3.23. time

  • Version number 1.4 (was 1.2.0.5)

  • A RealFrac instance has been added for Data.Time.Clock.Scale.DiffTime.

  • NFData instances have been added for Data.Time.Calendar.Days.Day, Data.Time.Clock.Scale.UniversalTime, Data.Time.Clock.Scale.DiffTime, Data.Time.Clock.TAI.AbsoluteTime, Data.Time.Clock.UTC.UTCTime, Data.Time.Clock.UTC.NominalDiffTime, Data.Time.LocalTime.LocalTime.LocalTime, Data.Time.LocalTime.LocalTime.ZonedTime, Data.Time.LocalTime.TimeOfDay.TimeOfDay and Data.Time.LocalTime.TimeZone.TimeZone.

1.7.3.24. unix

  • Version number 2.5.1.0 (was 2.5.0.0)

  • System.Posix now re-exports System.Posix.DynamicLinker (although it hides the Default constructor, as that clashes with the constructor of the same name of the System.Posix.Signals.Handler type).

  • There is now a raw bytestring version of the filepath and environment APIs. It uses a RawFilePath = ByteString type synonym, and adds a number of new exposed modules: System.Posix.ByteString, System.Posix.ByteString.FilePath, System.Posix.Directory.ByteString, System.Posix.DynamicLinker.Module.ByteString, System.Posix.DynamicLinker.ByteString, System.Posix.Files.ByteString, System.Posix.IO.ByteString, System.Posix.Env.ByteString, System.Posix.Process.ByteString, System.Posix.Temp.ByteString and System.Posix.Terminal.ByteString.

1.7.3.25. Win32

  • Version number 2.2.2.0 (was 2.2.1.0)

  • System.Win32.File now exports failIfWithRetry, failIfWithRetry_ and failIfFalseWithRetry_.