Difference between revisions of "Upgrading packages/Updating to GHC 6.10"

From HaskellWiki
Jump to navigation Jump to search
m (Upgrading packages moved to Upgrading packages/Updating to GHC 6.10: This version applies to the older GHC 6.10. It is out-of-date for GHC-7.0)
 
(34 intermediate revisions by 16 users not shown)
Line 9: Line 9:
   
 
When upgrading to GHC 6.10, any of your packages that worked against
 
When upgrading to GHC 6.10, any of your packages that worked against
the base-3 library will continue to work. GHC 6.10 provides both the old
+
the base-3 library will continue to work (unless you define instances of the <code>Arrow</code> class: see below). GHC 6.10 provides both the old
 
base-3 library and the new base-4.
 
base-3 library and the new base-4.
   
Line 27: Line 27:
 
Force use of package base-3 when using --make,
 
Force use of package base-3 when using --make,
   
ghc --make --package base-3.0.3.0
+
ghc --make -package base-3.0.3.0
   
 
===runhaskell ===
 
===runhaskell ===
Line 51: Line 51:
 
--constraint="base<4"
 
--constraint="base<4"
   
== Changes in base 4 ==
+
== Typical breakages with GHC 6.10 ==
   
  +
[http://article.gmane.org/gmane.comp.lang.haskell.glasgow.user/15430 48 new packages] break with the current GHC 6.10 release candidate.
* Exceptions
 
  +
  +
The primary reasons are:
  +
  +
* Changes to the Arrow class definition break Arrow instances
  +
* Changes to the return types of Map and Set functions
  +
* Cabal changes
  +
* Changes to ghc-api
  +
* Changes to when 'forall' is parsed
  +
* GHC.Prim was moved,
  +
* Changes to -fvia-C and headers
  +
* GADT changes,
  +
* pragma warnings tightened
  +
* Integer constructors have moved
  +
* New warnings and used -Werror
  +
  +
Each of these has a standard way to solve the problem. Techniques should be attached here.
  +
  +
=== Arrow instances ===
  +
  +
The relevant change is essentially that Arrow became a subclass of Category. To be exact:
  +
  +
* <code>(.)</code> is a new function, in Category. <code>(>>>)</code> was removed from Arrow and made a function.
  +
* <code>id</code> is a new function, in Category
  +
  +
The base-3 compatibility package contains the same classes as base-4, so it will not save you if you define instances of the Arrow class: you'll need to change your code.
  +
Whenever you define an instance of Arrow you must also define an instance of Category, as follows:
  +
  +
* Add the following imports:
  +
<haskell>
  +
import Control.Category
  +
import Prelude hiding (id,(.)) -- conflicts with Category otherwise
  +
</haskell>
  +
* Add <code>instance Category [your type] where</code> for any Arrow instances you define.
  +
* Move your <code>(>>>)</code> definition into Category, and change <code>f >>> g = ...</code> into <code>g . f = ...</code>
  +
* Define <code>id</code> in Category to something equivalent to
  +
<haskell>
  +
id = arr id
  +
</haskell>
  +
: Unfortunately this exact definition does not work in GHC 6.10.1 with optimization turned on (this is bug [http://hackage.haskell.org/trac/ghc/ticket/2722 #2722]), but anything equivalent to it is OK.
  +
  +
And you're done.
  +
  +
Following the recipe above will make your library work with ghc 6.9 and 6.10 and ''not work'' with 6.8.
  +
With a little more work and the help of CPP, you can manage the differences between 6.8, 6.9, and 6.10 and make your library work on all of them.
  +
  +
The following directions are an alternative to the ones above.
  +
  +
First, include <code>CPP</code> to your <code>LANGUAGE</code> pragma.
  +
  +
Then add the following lines in place of your <hask>import Control.Arrow</hask>:
  +
<haskell>
  +
#if __GLASGOW_HASKELL__ >= 609
  +
import Control.Category
  +
import Prelude hiding ((.), id)
  +
#endif
  +
  +
import Control.Arrow
  +
#if __GLASGOW_HASKELL__ < 610
  +
hiding (pure)
  +
#endif
  +
</haskell>
  +
This <hask>hiding (pure)</hask> is to accommodate the removal of <hask>pure</hask> from the <hask>Arrow</hask> interface, and you'll want it if you work with the <hask>pure</hask> method of <hask>Applicative</hask>.
  +
Before ghc 6.10, the <hask>hiding</hask> part is necessary, while afterward it's illegal.
  +
  +
Finally, doctor your <hask>Arrow</hask> instances.
  +
The following example is taken from [http://hackage.haskell.org/packages/archive/TypeCompose/latest/doc/html/src/Control-Compose.html Control.Compose] in the TypeCompose package.
  +
  +
<haskell>
  +
#if __GLASGOW_HASKELL__ >= 609
  +
instance FunAble h => Category (FunA h) where
  +
id = FunA (arrFun id)
  +
(.) = inFunA2 (.)
  +
#endif
  +
  +
instance FunAble h => Arrow (FunA h) where
  +
arr p = FunA (arrFun p)
  +
#if __GLASGOW_HASKELL__ < 609
  +
(>>>) = inFunA2 (>>>)
  +
#endif
  +
first = inFunA firstFun
  +
second = inFunA secondFun
  +
(***) = inFunA2 (***%)
  +
(&&&) = inFunA2 (&&&%)
  +
</haskell>
  +
  +
===Return types of Map and Set functions ===
  +
  +
Functions with signatures like
  +
<haskell>
  +
lookup :: (Monad m, Ord k) => k -> Map k a -> m a
  +
</haskell>
  +
have been specialized to
  +
<haskell>
  +
lookup :: (Ord k) => k -> Map k a -> Maybe a
  +
</haskell>
  +
If you assume the more specific type, your code will work with both old and new versions of the <code>containers</code> package.
  +
The brute force approach is to change each <code>lookup k m</code> to
  +
<haskell>
  +
fromMaybe (fail "lookup: key not found") $
  +
lookup k m
  +
</haskell>
  +
but you could also consider how you want to handle possible failures, or at least give a more informative error message.
  +
  +
=== Exception handling changes ===
  +
  +
The exception system was generalised in GHC 6.10, but GHC 6.10 still provides base-3, so all your applications can continue to work.
  +
  +
Follow the steps for compiling against base-3 at the top of the page, based on your build system.
  +
  +
Note that if you use cabal-install, it is smart enough to work this out for you.
  +
  +
=== Changes to -fvia-C and headers ===
  +
  +
GHC 6.10 no longer includes extra header files when compiling with -fvia-C. This makes compilation with -fvia-C consistent with the native code generator.
  +
  +
As a consequence, defining inline functions in header files and relying on -fvia-C to pick them up no longer works. Similarly calling C 'functions' that are actually defined via CPP macros also does not work.
  +
  +
* If you use a library that provides inline functions that you want to use, you will have to create wrapper functions to use them via FFI.
  +
* If you use the <code>#def</code> feature of hsc2hs, you can no longer define inline functions. That is, replace <code>#def inline void foobar() { ... } </code> by just <code>#def void foobar() { ... }</code>
  +
  +
The problem typically manifests itself as link errors (for example "ghc26356_0.hc:(.text+0x20282): undefined reference to `hs_curses_color_pair'").
  +
  +
Beware: In some cases, a library using inline functions will be built successfully, but programs using the library will fail to build.
  +
  +
=== Changes to RULES parsing ===
  +
  +
RULES are now always parsed and checked. No ghc flags or language extensions are required. (Note: the first 6.10 RC had a bug in this area)
  +
  +
RULES are only exported if the defining module is built with -O. This is the same as for other cross-module optimisations like exporting the bodies of inlinable functions.
  +
  +
=== Changes to GADT matching ===
  +
  +
GHC now enforces the rule that in a GADT pattern match:
  +
  +
* the type of the scrutinee must be rigid
  +
* the result type must be rigid
  +
* the type of any variable free in the case branch must be rigid
  +
  +
Here "rigid" means "fully known to the compiler, usually by way of a type signature". This rule is to make type inference simple and predictable.
  +
  +
Observe that this means that GHC must know the result type of the match ''at the match point''. There is no workaround other than finding a way to provide enough annotations in order to make GHC happy. Nevertheless, this heuristic was suggested:
  +
  +
<blockquote>My general method for solving these problems was to find an expression
  +
or statement that enclosed both the left and right hand sides, and add
  +
<code>:: Int</code> to it. I then recompiled and got an error message saying it
  +
couldn't match <code>Int</code> with "something". I then replaced <code>Int</code> with
  +
"something" and it worked.</blockquote>
  +
  +
For example, if GHC is complaining about a case-expression you might try rewriting it like this:
  +
(case ... of { ...}) :: type
  +
  +
  +
In any case, [http://thread.gmane.org/gmane.comp.lang.haskell.glasgow.user/15153 this thread] is probably a must-read if you are running into this.
  +
  +
Here's an example from [http://www.haskell.org/haskellwiki/QuickCheck_/_GADT the wiki entry on using QuickCheck with GADTs]. This failed with 6.10.1 with:
  +
  +
<code>
  +
GADT.hs:153:12:
  +
GADT pattern match with non-rigid result type `t'
  +
Solution: add a type signature
  +
In a case alternative: RInt -> text "RInt"
  +
In the expression:
  +
case s of {
  +
RInt -> text "RInt"
  +
RChar -> text "RChar"
  +
RList y -> text "RList" <> space <> parens (prettyRep (Rep y))
  +
RPair y1 y2
  +
-> text "RPair" <> space <> parens (prettyRep (Rep y1)) <> space
  +
<>
  +
parens (prettyRep (Rep y2))
  +
RDyn -> text "RDyn" }
  +
</code>
  +
  +
Adding the type signature to the function (not the case alternative as you might infer from the error message): <haskell>prettyRep :: Rep -> Doc</haskell> solves the problem.
  +
  +
A related issue is this. GHC 6.10 insists on <code>-XGADTs</code> when you ''define'' a GADT, but does not insist on the flag when you ''match'' on a GADT. However, when supplying a type signature for a recursive or mutually-recursive function which does GADT matching, you should use <code>-XRelaxedPolyRec</code> (or <code>-XGADTs</code>, which implies the former) to ensure that the type signature is completely rigid. (Why? It's to do with the way that the Hindley-Milner algorithm typechecks mutually recursive definitions. See this [http://www.haskell.org/pipermail/glasgow-haskell-users/2008-December/016370.html mail thread].)
  +
  +
=== No more GHC.Prim ===
  +
  +
It is no longer possible to import GHC.Prim, instead, GHC.Exts should be used to get at the compiler's primops.
   
 
== Backwards compatibility ==
 
== Backwards compatibility ==
Line 62: Line 242:
   
 
is not backwards compatible with older versions of Cabal. Users will need to upgrade to the newer Cabal to build packages that start using this syntax.
 
is not backwards compatible with older versions of Cabal. Users will need to upgrade to the newer Cabal to build packages that start using this syntax.
  +
  +
== GHC API changes ==
  +
  +
For converting a package that uses GHC-API, see [[http://hackage.haskell.org/trac/ghc/wiki/GhcApiStatus GhcApiStatus]] for notes on the changes to the API and its use in 6.10. There are four main changes:
  +
  +
* add imports '<code>MonadUtils</code>' and '<code>SrcLoc</code>'
  +
* use of '<code>runGhc</code>' instead of newSession
  +
* code using getSession and related, converts to become monadic within <code>Ghc</code>monad
  +
* String type becomes Located String type. To convert basic strings, use "L noSrcSpan <string>"
   
 
[[Category:Libraries]]
 
[[Category:Libraries]]
  +
[[Category:GHC]]

Latest revision as of 18:00, 13 March 2011

A list of things that need updating when porting packages to newer library/cabal versions.

If you maintain a Haskell package this is for you. For older versions of this document:

Updating to GHC 6.10 and Cabal 1.6

When upgrading to GHC 6.10, any of your packages that worked against the base-3 library will continue to work (unless you define instances of the Arrow class: see below). GHC 6.10 provides both the old base-3 library and the new base-4.

To ensure your old code continues to work, you can have the code compile and link against base-3, and then, over time, migrate code to the base-4 series.

Adding base-3 constraints

How to do this depends on how you build your Haskell code. We'll start with the most simplistic build mechanisms. cabal-install, the most sophisticated tool, will sort this all out for you anyway, so things should change.

ghc --make

Force use of package base-3 when using --make,

   ghc --make -package base-3.0.3.0

runhaskell

If you build your packages with the 'runhaskell Setup.hs configure' method, then you can force the use of base-3,

   --constraint="base<4"

cabal-install

It is worth upgrading cabal-install immediately (maybe before installing GHC). This way you can use the smart dependency solver to work out what to install for you.

* install HTTP from hackage
* install zlib from hackage

Then build cabal-install.

You can also override the dependencies when using the 'cabal' binary, with

   --constraint="base<4"

Typical breakages with GHC 6.10

48 new packages break with the current GHC 6.10 release candidate.

The primary reasons are:

  • Changes to the Arrow class definition break Arrow instances
  • Changes to the return types of Map and Set functions
  • Cabal changes
  • Changes to ghc-api
  • Changes to when 'forall' is parsed
  • GHC.Prim was moved,
  • Changes to -fvia-C and headers
  • GADT changes,
  • pragma warnings tightened
  • Integer constructors have moved
  • New warnings and used -Werror

Each of these has a standard way to solve the problem. Techniques should be attached here.

Arrow instances

The relevant change is essentially that Arrow became a subclass of Category. To be exact:

  • (.) is a new function, in Category. (>>>) was removed from Arrow and made a function.
  • id is a new function, in Category

The base-3 compatibility package contains the same classes as base-4, so it will not save you if you define instances of the Arrow class: you'll need to change your code. Whenever you define an instance of Arrow you must also define an instance of Category, as follows:

  • Add the following imports:
    import Control.Category
    import Prelude hiding (id,(.)) -- conflicts with Category otherwise
  • Add instance Category [your type] where for any Arrow instances you define.
  • Move your (>>>) definition into Category, and change f >>> g = ... into g . f = ...
  • Define id in Category to something equivalent to
    id = arr id
Unfortunately this exact definition does not work in GHC 6.10.1 with optimization turned on (this is bug #2722), but anything equivalent to it is OK.

And you're done.

Following the recipe above will make your library work with ghc 6.9 and 6.10 and not work with 6.8. With a little more work and the help of CPP, you can manage the differences between 6.8, 6.9, and 6.10 and make your library work on all of them.

The following directions are an alternative to the ones above.

First, include CPP to your LANGUAGE pragma.

Then add the following lines in place of your import Control.Arrow:

#if __GLASGOW_HASKELL__ >= 609
import Control.Category
import Prelude hiding ((.), id)
#endif

import Control.Arrow
#if __GLASGOW_HASKELL__ < 610
                      hiding (pure)
#endif

This hiding (pure) is to accommodate the removal of pure from the Arrow interface, and you'll want it if you work with the pure method of Applicative. Before ghc 6.10, the hiding part is necessary, while afterward it's illegal.

Finally, doctor your Arrow instances. The following example is taken from Control.Compose in the TypeCompose package.

#if __GLASGOW_HASKELL__ >= 609
instance FunAble h => Category (FunA h) where
  id  = FunA (arrFun id)
  (.) = inFunA2 (.)
#endif

instance FunAble h => Arrow (FunA h) where
  arr p  = FunA    (arrFun p)
#if __GLASGOW_HASKELL__ < 609
  (>>>)  = inFunA2 (>>>)
#endif
  first  = inFunA  firstFun
  second = inFunA  secondFun
  (***)  = inFunA2 (***%)
  (&&&)  = inFunA2 (&&&%)

Return types of Map and Set functions

Functions with signatures like

lookup :: (Monad m, Ord k) => k -> Map k a -> m a

have been specialized to

lookup :: (Ord k) => k -> Map k a -> Maybe a

If you assume the more specific type, your code will work with both old and new versions of the containers package. The brute force approach is to change each lookup k m to

fromMaybe (fail "lookup: key not found") $
  lookup k m

but you could also consider how you want to handle possible failures, or at least give a more informative error message.

Exception handling changes

The exception system was generalised in GHC 6.10, but GHC 6.10 still provides base-3, so all your applications can continue to work.

Follow the steps for compiling against base-3 at the top of the page, based on your build system.

Note that if you use cabal-install, it is smart enough to work this out for you.

Changes to -fvia-C and headers

GHC 6.10 no longer includes extra header files when compiling with -fvia-C. This makes compilation with -fvia-C consistent with the native code generator.

As a consequence, defining inline functions in header files and relying on -fvia-C to pick them up no longer works. Similarly calling C 'functions' that are actually defined via CPP macros also does not work.

  • If you use a library that provides inline functions that you want to use, you will have to create wrapper functions to use them via FFI.
  • If you use the #def feature of hsc2hs, you can no longer define inline functions. That is, replace #def inline void foobar() { ... } by just #def void foobar() { ... }

The problem typically manifests itself as link errors (for example "ghc26356_0.hc:(.text+0x20282): undefined reference to `hs_curses_color_pair'").

Beware: In some cases, a library using inline functions will be built successfully, but programs using the library will fail to build.

Changes to RULES parsing

RULES are now always parsed and checked. No ghc flags or language extensions are required. (Note: the first 6.10 RC had a bug in this area)

RULES are only exported if the defining module is built with -O. This is the same as for other cross-module optimisations like exporting the bodies of inlinable functions.

Changes to GADT matching

GHC now enforces the rule that in a GADT pattern match:

  • the type of the scrutinee must be rigid
  • the result type must be rigid
  • the type of any variable free in the case branch must be rigid

Here "rigid" means "fully known to the compiler, usually by way of a type signature". This rule is to make type inference simple and predictable.

Observe that this means that GHC must know the result type of the match at the match point. There is no workaround other than finding a way to provide enough annotations in order to make GHC happy. Nevertheless, this heuristic was suggested:

My general method for solving these problems was to find an expression

or statement that enclosed both the left and right hand sides, and add :: Int to it. I then recompiled and got an error message saying it couldn't match Int with "something". I then replaced Int with

"something" and it worked.

For example, if GHC is complaining about a case-expression you might try rewriting it like this:

    (case ... of { ...})  ::  type


In any case, this thread is probably a must-read if you are running into this.

Here's an example from the wiki entry on using QuickCheck with GADTs. This failed with 6.10.1 with:

GADT.hs:153:12:

   GADT pattern match with non-rigid result type `t'
     Solution: add a type signature
   In a case alternative: RInt -> text "RInt"
   In the expression:
       case s of {
         RInt -> text "RInt"
         RChar -> text "RChar"
         RList y -> text "RList" <> space <> parens (prettyRep (Rep y))
         RPair y1 y2
           -> text "RPair" <> space <> parens (prettyRep (Rep y1)) <> space
      <>
        parens (prettyRep (Rep y2))
         RDyn -> text "RDyn" }

Adding the type signature to the function (not the case alternative as you might infer from the error message):
prettyRep :: Rep -> Doc
solves the problem.

A related issue is this. GHC 6.10 insists on -XGADTs when you define a GADT, but does not insist on the flag when you match on a GADT. However, when supplying a type signature for a recursive or mutually-recursive function which does GADT matching, you should use -XRelaxedPolyRec (or -XGADTs, which implies the former) to ensure that the type signature is completely rigid. (Why? It's to do with the way that the Hindley-Milner algorithm typechecks mutually recursive definitions. See this mail thread.)

No more GHC.Prim

It is no longer possible to import GHC.Prim, instead, GHC.Exts should be used to get at the compiler's primops.

Backwards compatibility

The new, suggested Cabal version range syntax,

  build-depends: base-3.*

is not backwards compatible with older versions of Cabal. Users will need to upgrade to the newer Cabal to build packages that start using this syntax.

GHC API changes

For converting a package that uses GHC-API, see [GhcApiStatus] for notes on the changes to the API and its use in 6.10. There are four main changes:

  • add imports 'MonadUtils' and 'SrcLoc'
  • use of 'runGhc' instead of newSession
  • code using getSession and related, converts to become monadic within Ghcmonad
  • String type becomes Located String type. To convert basic strings, use "L noSrcSpan <string>"