Analysis of new packages breakages with ghc-6.10

Don Stewart dons at galois.com
Sat Oct 11 04:03:14 EDT 2008


OK, so we have *56* packages total that no longer compile with GHC 6.10, but
did with 6.8.3. We can now see exactly what broke and why.

I think these potential breakage issues, and how to solve them canonically ,
should be documented on the wiki. Most should have standard solutions, some
might be GHC bugs (which I've reported for the obvious ones, but Ian, better
have a look at the 'unknown' ones).

The following events broke the following packages, 

    * 7 Changes to Arrow class definition
        TypeCompose, Yampa, arrows, chp, hxt, quantum-arrow, streamproc

    * 6 Changes to Map monadic types
        EdisonCore, HPDF, WebBits, libgeni, regex-tdfa, stringtable-atom

    * 5 Cabal changes
        cabal-setup, hask-home, hinstaller, hslackbuilder, plugins

    * 5 Changes to ghc-api
        HTF, Hashell, hint, typalyze, xmonad-utils

    * 5 GHC panics/bugs, reported
        xmonad-contrib, stream-fusion, harpy, OpenAFP, Vec

    * 4 Unknown error, needs investigation.
        ArrayRef, YamlReference, parameterized-data, unicode-prelude

    * 3 Changes to when 'forall' is parsed
        MemoTrie, heap, hexpat

    * 3 GHC.Prim was moved,
        PArrow, logfloat, utf8-light

    * 3 Changes to -fvia-C and headers?
        cmath, hetris, mage 

    * 2 GADT changes,
        CLASE, hasim

    * 2 pragma warnings tightened
        numeric-prelude, yhccore

    * 2 Integer constructors have moved
        NewBinary, bytestring-show

    * 2 New warnings and used -Werror
        fixpoint, list-extras

    * 1 Addition of permutations to List library
        HaLeX

    * 1 Illegal type synonym family application
        hsx

    * 1 Exception's moved around?
        iException

------------------------------------------------------------------------
Below are the precise warnings:


** ArrayRef, ??
    Data/ArrayBZ/Internals/Unboxed.hs:60:0:
        Duplicate type signature:
          Data/ArrayBZ/Internals/Unboxed.hs:60:0-18: stUArrayTc :: TyCon
          Data/ArrayBZ/Internals/Unboxed.hs:59:0-18: stUArrayTc :: TyCon

CLASE,
    Data/Cursor/CLASE/Persistence.hs:124:11:
        GADT pattern match with non-rigid result type `GenParser Char st a'
          Solution: add a type signature

EdisonCore,
    src/Data/Edison/Assoc/StandardMap.hs:204:21:
        Couldn't match expected type `m' against inferred type `Maybe'
          `m' is a rigid type variable bound by

HPDF,
    Graphics/PDF/Data/Trie.hs:39:34:
        Couldn't match expected type `[a]'
               against inferred type `Maybe (MapString v)'

HTF,
    Test/Framework.hs:40:21: Not in scope: `currentModule'

HaLeX,
    HaLeX_lib/Language/HaLex/Util.hs:48:13:
        Ambiguous occurrence `permutations'
        It could refer to either `Language.HaLex.Util.permutations', defined at HaLeX_lib/Language/HaLex/Util.hs:46:0
                              or `Data.List.permutations', imported from Data.List at HaLeX_lib/Language/HaLex/Util.hs:24:0-15

Hashell,
    Hashell/Eval.hs:45:19: Not in scope: `GHC.newSession'

Hipmunk,
    Physics/Hipmunk/Space.hsc:531:2:
        Couldn't match expected type `Maybe (Either (ForeignPtr ()) Shape)'
               against inferred type `IO (Either (ForeignPtr ()) Shape)'

MemoTrie,
    src/Data/MemoTrie.hs:36:16: Not in scope: `forall'

NewBinary,
    NewBinary/Binary.hs:693:13: Not in scope: data constructor `S#'

PArrow,
    src/Text/ParserCombinators/PArrow/MD.hs:7:0:
        Failed to load interface for `GHC.Prim':
          it is a member of package ghc-prim, which is hidden

TypeCompose,
    src/Data/Bijection.hs:52:11:
        `>>>' is not a (visible) method of class `Arrow'

Vec,
    timeout

WebBits,
    src/WebBits/JavaScript/Environment.hs:216:2:
        Couldn't match expected type `Maybe Int'
               against inferred type `StateT (Z.Location Env) (State Int) Int'

YamlReference,
    Text/Yaml/Reference.hs:1482:19:
        No instance for (Match a14 ())
          arising from a use of `pat' at Text/Yaml/Reference.hs:1482:19-59

yampa,
    src/FRP/Yampa.hs:650:4:
        `>>>' is not a (visible) method of class `Arrow'

arrows,
    Control/Arrow/Transformer/CoState.hs:24:29:
        Module `Control.Arrow' does not export `pure'

bytestring-show
    Text/Show/ByteString/Integer.hs:31:14:
        Not in scope: data constructor `S#'

cabal-setup,
    CabalSetup.hs:14:7:
        Could not find module `Distribution.Simple.SetupWrapper':
          Use -v to see a list of the files searched for.

chp,
    Control/Concurrent/CHP/Arrow.hs:107:22:
        `>>>' is not a (visible) method of class `Arrow'

fixpoint,
    Data/Fixpoint/Instances.hs:24:9:
        Warning: orphan instance: instance Foldable (Pre [a])
    <no location info>: 
    Failing due to -Werror.

hasim,
    src/Control/Hasim/SimRun.hs:291:13:
        GADT pattern match with non-rigid result type `t'
          Solution: add a type signature

hask-home,
    hask-home.hs:101:15: Not in scope: `showPackageId'

heap,
    Data/Heap.hs:297:18: Not in scope: `forall'

hetris,
    /home/dons/.cabal/lib/hscurses-1.3/ghc-6.10.0.20081007/libHShscurses-1.3.a(Curses.o): In function `s93V_info':
    ghc26356_0.hc:(.text+0x20282): undefined reference to `hs_curses_color_pair'
    collect2: ld returned 1 exit status

hexpat,
    C2HS.hs:198:30: Not in scope: `forall'

hinstaller
    src/System/Installer/Foreign.hs:131:18:
        Not in scope: `buildVerbose'

hint
    src/Hint/Parsers.hs:7:21: Module `GHC' does not export `Session'

hslackbuilder
    Distribution/Slackware/SlackBuild.hs:215:24:
        Not in scope: `showVersionRange'

hsx:
    src/HSX/XMLGenerator.hs:71:0:
        Illegal type synonym family application in instance: XML m
        In the instance declaration for `EmbedAsChild m (XML m)'

hxt:
    src/Text/XML/HXT/RelaxNG/DataTypeLibUtils.hs:67:7:
        `>>>' is not a (visible) method of class `Arrow'

iException:
    Control/Monad/Trans/InterleavableIO/Control/Exception.hs:131:26:
        Ambiguous occurrence `Exception'
        It could refer to either `Control.Exception.Exception', imported from Control.Exception at Control/Monad/Trans/InterleavableIO/Control/Exception.hs:(31,0)-(52,2)
                              or `GHC.IOBase.Exception', imported from GHC.IOBase at Control/Monad/Trans/InterleavableIO/Control/Exception.hs:(58,0)-(62,2)

libgeni:
    libgeni/NLP/GenI/CkyEarley/CkyBuilder.lhs:559:4:
        Couldn't match expected type `Maybe ([String], [String], GNode)'
               against inferred type `[([String], [String], GNode)]'

list-extras:
    Data.List.Extras.LazyLength:1:0:
        Orphan rule: "lengthCompare/compare" ALWAYS forall @ a
                                                           @ a1
                                                           $dOrd :: Ord Int
                                                           xs :: [a]
                                                           ys :: [a1]
                       compare @ Int $dOrd (length @ a xs) (length @ a1 ys)
                       = lengthCompare @ a @ a1 xs ys

    (Uses -Werror !)

logfloat:
    Data/Number/Transfinite.hs:58:0:
        Failed to load interface for `GHC.Prim':
          it is a member of package ghc-prim, which is hidden

mage
    Linking dist/build/mage/mage ...
    dist/build/mage/mage-tmp/Curses.o: In function `r8zq_info':

numeric-prelude
    src/Number/Complex.hs:3:12:
        cannot parse LANGUAGE pragma: comma-separated list expected

parameterized-data
    src/Data/Param/FSVec.hs:103:22:
        Couldn't match expected type `t -> ExpQ'
               against inferred type `FSVec s a1'

plugins:
    cabal changes

quantum-arrow:
    Control/Arrow/Quantum.hs:64:11:
        `>>>' is not a (visible) method of class `Arrow'

regex-tdfa:
    Data/IntMap/CharMap.hs:49:23:
        Couldn't match expected type `m' against inferred type `Maybe'
          `m' is a rigid type variable bound by
              the type signature for `Data.IntMap.CharMap.lookup'

streamproc
    Control/Arrow/SP.hs:40:12:
        `>>>' is not a (visible) method of class `Arrow'

stringtable-atom
    src/StringTable/AtomSet.hs:122:65:
        Couldn't match expected type `m' against inferred type `Maybe'
          `m' is a rigid type variable bound by
              the type signature for `maxView'
                at src/StringTable/AtomSet.hs:121:18

typalyze
    src/Main.hs:82:15: Not in scope: `checkModule'
    src/Main.hs:145:13: Not in scope: `newSession'

unicode-prelude
    Prelude/Unicode.hs:68:7: lexical error at character '\183'

utf8-light
    src/Codec/Binary/UTF8/Light.hs:69:0:
        Failed to load interface for `GHC.Prim':
          it is a member of package ghc-prim, which is hidden

* xmonad-utils-0.1
        src/Heval.hs:64:18:
            Not in scope: type constructor or class `Session'

* yhccore-0.9
        unknown flag in  {-# OPTIONS #-} pragma: _DERIVE

------------------------------------------------------------------------
Panics, bug reports already made:

Looks like a GHC bug:

** OpenAFP

    http://hackage.haskell.org/trac/ghc/ticket/2686

    [219 of 230] Compiling OpenAFP.Prelude.InstanceAFP.C ( src/OpenAFP/Prelude/InstanceAFP/C.hs, dist/build/OpenAFP/Prelude/InstanceAFP/C.o )
    ghc: panic! (the 'impossible' happened)
      (GHC version 6.10.0.20081007 for x86_64-unknown-linux):
        applyTypeToArgs
        OpenAFP-1.1:OpenAFP.Types.Chunk.:DRecData{v rm2C} [gid]
          @ OpenAFP-1.1:OpenAFP.Records.AFP.CFI.CFI{tc rPQH}
          @ OpenAFP-1.1:OpenAFP.Records.AFP.CFI.CFI_Data{tc rPQv}
          $dRec{v a2fWO} [lid]
          $dRec{v a2fWP} [lid]
          @ (ghc-prim:GHC.Prim.trans{(w) tc 34y}
               (ghc-prim:GHC.Prim.trans{(w) tc 34y}
                  (OpenAFP-1.1:OpenAFP.Types.Chunk.DataOf{tc rlUo}
                     OpenAFP-1.1:OpenAFP.Records.AFP.CFI.CFI{tc rPQH})
                  (ghc-prim:GHC.Prim.trans{(w) tc 34y}
                     OpenAFP-1.1:OpenAFP.Prelude.InstanceAFP.C.:CoF:R10DataOf{tc r2fJV}
                     OpenAFP-1.1:OpenAFP.Records.AFP.CFI.CFI_Data{tc rPQv}))
               OpenAFP-1.1:OpenAFP.Records.AFP.CFI.CFI_Data{tc rPQv})
          @ (ghc-prim:GHC.Prim.trans{(w) tc 34y}
               (ghc-prim:GHC.Prim.trans{(w) tc 34y}
                  (OpenAFP-1.1:OpenAFP.Types.Chunk.RecOf{tc rlUq}
                     OpenAFP-1.1:OpenAFP.Records.AFP.CFI.CFI_Data{tc rPQv})
                  (ghc-prim:GHC.Prim.trans{(w) tc 34y}
                     OpenAFP-1.1:OpenAFP.Prelude.InstanceAFP.C.:CoF:R9RecOf{tc r2fJU}
                     OpenAFP-1.1:OpenAFP.Records.AFP.CFI.CFI{tc rPQH}))
               OpenAFP-1.1:OpenAFP.Records.AFP.CFI.CFI{tc rPQH})
        (OpenAFP-1.1:OpenAFP.Types.Chunk.DataOf{tc rlUo}
           OpenAFP-1.1:OpenAFP.Records.AFP.CFI.CFI{tc rPQH}
           ~
         OpenAFP-1.1:OpenAFP.Records.AFP.CFI.CFI_Data{tc rPQv},
         OpenAFP-1.1:OpenAFP.Types.Chunk.RecOf{tc rlUq}
           OpenAFP-1.1:OpenAFP.Records.AFP.CFI.CFI_Data{tc rPQv}
           ~
         OpenAFP-1.1:OpenAFP.Records.AFP.CFI.CFI{tc rPQH},
         OpenAFP-1.1:OpenAFP.Types.Record.Rec{tc rl5e}
           OpenAFP-1.1:OpenAFP.Records.AFP.CFI.CFI{tc rPQH},
         OpenAFP-1.1:OpenAFP.Types.Record.Rec{tc rl5e}
           OpenAFP-1.1:OpenAFP.Records.AFP.CFI.CFI_Data{tc rPQv}) =>
        (OpenAFP-1.1:OpenAFP.Records.AFP.CFI.CFI{tc rPQH}
         -> [OpenAFP-1.1:OpenAFP.Types.Record.Record{tc rl5q}
               OpenAFP-1.1:OpenAFP.Records.AFP.CFI.CFI_Data{tc rPQv}])
        -> (OpenAFP-1.1:OpenAFP.Records.AFP.CFI.CFI{tc rPQH}
            -> [OpenAFP-1.1:OpenAFP.Types.Record.Record{tc rl5q}
                  OpenAFP-1.1:OpenAFP.Records.AFP.CFI.CFI_Data{tc rPQv}]
            -> OpenAFP-1.1:OpenAFP.Records.AFP.CFI.CFI{tc rPQH})
        -> OpenAFP-1.1:OpenAFP.Records.AFP.CFI.CFI{tc rPQH}
           OpenAFP-1.1:OpenAFP.Types.Chunk.:TRecData{tc rm2B} OpenAFP-1.1:OpenAFP.Records.AFP.CFI.CFI_Data{tc rPQv}

Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug

** harpy

http://hackage.haskell.org/trac/ghc/ticket/2685

ghc: panic! (the 'impossible' happened)
  (GHC version 6.10.0.20081007 for x86_64-unknown-linux):
	mkUsage
    harpy-0.4:Harpy.CodeGenMonad CodeGen{d} [(01T,
                                              base:GHC.Base.return{v 01T}),
                                             (32I, base:GHC.IOBase.IO{tc 32I}),
                                             (333, base:GHC.Word.Word32{tc 333}),
                                             (33A, base:GHC.Ptr.Ptr{tc 33A}),
                                             (33D, base:GHC.Ptr.FunPtr{tc 33D}),
                                             (40, ghc-prim:GHC.Unit.(){(w) tc 40}),
                                             (6Q, base:Data.Either.Right{d 6Q}),
                                             (r7, base:GHC.Base.${v r7}),
                                             (r4E, mtl-1.1.0.1:Control.Monad.Trans.liftIO{v r4E}),
                                             (r8S, base:GHC.Ptr.castPtrToFunPtr{v r8S}),
                                             (rO69,
                                              harpy-0.4:Harpy.CodeGenMonad.firstBuffer{v rO69}),
                                             (rO6z, harpy-0.4:Harpy.CodeGenMonad.CodeGen{d rO6z}),
                                             (rO7P, harpy-0.4:Harpy.CodeGenMonad.callDecl{v rO7P}),
                                             (rVBT, harpy-0.4:Harpy.Call.conv[aVBL]{v rVBT}),
                                             (rVDx, harpy-0.4:Harpy.Call.conv[aVDo]{v rVDx}),
                                             (rVJc, harpy-0.4:Harpy.Call.conv[aVIX]{v rVJc})]

Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug


** stream-fusion
Data/Stream.hs:575:4:
    Warning: Pattern match(es) are non-exhaustive
             In the definition of `next':
                 Patterns not matched: (_ :!: (Just (L _))) :!: S2
[2 of 3] Compiling Data.List.Stream ( Data/List/Stream.hs, dist/build/Data/List/Stream.o )
stack overflow: use +RTS -K<size> to increase it

  http://hackage.haskell.org/trac/ghc/ticket/2684

** xmonad-contrib-0.8
        ghc: panic! (the 'impossible' happened)
          (GHC version 6.10.0.20081007 for x86_64-unknown-linux): 
              ASSERT failed! file typecheck/TcUnify.lhs line 1000
              a{tv aAeS} [box]

              Please report this as a GHC bug:
              http://www.haskell.org/ghc/reportabug
   http://hackage.haskell.org/trac/ghc/ticket/2683



More information about the Glasgow-haskell-users mailing list