Run "ghc-pkg check", and do a "cabal install --reinstall" for all packages that it says need to be rebuilt at the bottom.
On 17 September 2010 13:44, Peter Schmitz <[email protected]> wrote: > This gets a little hilarious (but better to laugh than cry). > > Well, I decided to try Parsec version 3 (i.e., 3.1.0) after all, and > edited my cabal config to include: > > preference: parsec >= 3 > > I did not include "base >= 4"; hope that is not a problem. > > I did "cabal upgrade parsec", which went great. > > It added the new dirs: > > ...\cabal\parsec-3.1.0 > ...\cabal\mtl-1.1.1.0 > ...\cabal\bytestring-0.9.1.7 > > I recompiled my little parsec demo.hs using various appropriate > Text.Parsec modules (instead of Text.ParserCombinators.Parsec), and > it worked great. Wonderful! > > So, I tried to recompile another program I have that uses: > >> module Main where >> import Control.Monad.Trans ( liftIO ) >> import Data.IORef >> import Graphics.UI.Gtk >> import Graphics.UI.Gtk.Gdk.GC >> import Graphics.UI.Gtk.Gdk.EventM >> import Graphics.UI.Gtk.Glade >> import List ( delete, nub ) > > For this code (which previously compiled okay): > >> on canvas exposeEvent $ do >> -- drawWindow <- eventWindow >> -- region <- eventRegion >> liftIO $ do -- <<< this is line 135 >> updateCanvas canvas currentPattern pattern2CanvasOffset zoomFactor id >> (w,h) <- widgetGetSize canvas -- get (width,height) of DrawingArea >> putStrLn $ "DrawingArea redrawn; (width, height) = " ++ show (w,h) >> return True > > I get: > >> life.hs:135:6: >> No instance for (Control.Monad.Trans.MonadIO >> (mtl-1.1.0.2:Control.Monad.Reader.ReaderT >> (GHC.Ptr.Ptr EExpose) IO)) >> arising from a use of `liftIO' at life.hs:135:6-11 >> Possible fix: >> add an instance declaration for >> (Control.Monad.Trans.MonadIO >> (mtl-1.1.0.2:Control.Monad.Reader.ReaderT >> (GHC.Ptr.Ptr EExpose) IO)) >> In the first argument of `($)', namely `liftIO' >> In the expression: >> liftIO >> $ do { updateCanvas >> canvas currentPattern pattern2CanvasOffset zoomFactor id; >> (w, h) <- widgetGetSize canvas; >> putStrLn >> $ "DrawingArea redrawn; (width, height) = " ++ show (w, h); >> return True } >> In the second argument of `($)', namely >> `do { liftIO >> $ do { updateCanvas >> canvas currentPattern pattern2CanvasOffset zoomFactor >> id; >> (w, h) <- widgetGetSize canvas; >> .... } }' > > > When I did: "ghc --make life.hs -v", I saw among the output: > > "hiding package mtl-1.1.0.2 to avoid conflict with later version > mtl-1.1.1.0" > > I guess that the parsec upgrade installed the newer mtl, and I'm > wondering if that is what is making life.hs fail to compile. (?) > > Silly me, I noticed my gtk package was not up to date: > >> * gtk >> Synopsis: Binding to the Gtk+ graphical user interface library. >> Latest version available: 0.11.2 >> Latest version installed: 0.11.0 <<< >> Homepage: http://www.haskell.org/gtk2hs/ >> License: LGPL-2.1 > > So!, thinking it might help, I did: "cabal upgrade gtk" too. (In the > past I have successfully done "cabal install gtk", so I thought this > would be okay. :-) I got: > >> H:\proc\dev\cmd>cabal upgrade gtk >> Resolving dependencies... >> Configuring old-time-1.0.0.5... >> cabal: The package has a './configure' script. This requires a Unix >> compatibility toolchain such as MinGW+MSYS or Cygwin. >> Configuring random-1.0.0.2... >> Preprocessing library random-1.0.0.2... >> Building random-1.0.0.2... >> [1 of 1] Compiling System.Random ( System\Random.hs, >> dist\build\System\Random.o ) >> Registering random-1.0.0.2... >> Installing library in H:\proc\tools\cabal\random-1.0.0.2\ghc-6.12.1 >> Registering random-1.0.0.2... >> cabal: Error: some packages failed to install: >> cairo-0.11.1 depends on old-time-1.0.0.5 which failed to install. >> directory-1.0.1.2 depends on old-time-1.0.0.5 which failed to install. >> gio-0.11.1 depends on old-time-1.0.0.5 which failed to install. >> glib-0.11.2 depends on old-time-1.0.0.5 which failed to install. >> gtk-0.11.2 depends on old-time-1.0.0.5 which failed to install. >> haskell98-1.0.1.1 depends on old-time-1.0.0.5 which failed to install. >> old-time-1.0.0.5 failed during the configure step. The exception was: >> ExitFailure 1 >> pango-0.11.2 depends on old-time-1.0.0.5 which failed to install. >> process-1.0.1.3 depends on old-time-1.0.0.5 which failed to install. > > (This is where I began laughing instead of crying :-) > > I don't recall ever having problems with old-time in the past. > > If anyone has any suggestions, I would appreciate it. > > I am willing to either keep parsec 3 and resolve the life.hs compile > errors, or to revert to parsec 2 and somehow undo my package > installation problems. (E.g., is there a > "cabal uninstall <package-version>" command?) > > Thanks again very much. > -- Peter > > > > > p.s., trying to compile the parsec 3 demo yields (sorry about the formatting): > > H:\proc\dev\AAA\LC>ghc --make demo.hs -v > Glasgow Haskell Compiler, Version 6.12.1, for Haskell 98, stage 2 > booted by GHC version 6.10.4 > Using binary package database: H:\proc\tools\Haskell > Platform\2010.1.0.0\lib\package.conf.d\package > .cache > Using binary package database: C:\Documents and > Settings\pschmitz\Application Data\ghc\i386-mingw32 > -6.12.1\package.conf.d\package.cache > package QuickCheck-2.1.0.3-bf62d0a8213b04c27e0b8600c172a8b1 is > unusable due to missing or recursive > dependencies: > random-1.0.0.2-156803737564049405b3380fdb96ac75 > package cairo-0.11.0-72dde87f1e0a5c90fea5cd07ed797405 is unusable due > to missing or recursive depen > dencies: > haskell98-1.0.1.1-0fdaf3b26bc38c43ce8371edf538dbf6 > package containers-0.3.0.0-339506fe3cdbf89bbfb2d85bb3085ace is > shadowed by package containers-0.3.0 > .0-409fe3b8f0dda25b98e03716d26be411 > package dph-base-0.4.0-385a36312e9cc9bc5a672eb91d4e2be8 is unusable > due to missing or recursive dep > endencies: > random-1.0.0.2-156803737564049405b3380fdb96ac75 > package dph-par-0.4.0-6be3d558b460028d063187e304761859 is unusable due > to missing or recursive depe > ndencies: > dph-base-0.4.0-385a36312e9cc9bc5a672eb91d4e2be8 > dph-prim-par-0.4.0-a2411981a52bb04ae3b57a3bcf0824 > c6 random-1.0.0.2-156803737564049405b3380fdb96ac75 > package dph-prim-interface-0.4.0-523625c6a333b8571d7942e5861b066f is > unusable due to missing or rec > ursive dependencies: > dph-base-0.4.0-385a36312e9cc9bc5a672eb91d4e2be8 > random-1.0.0.2-156803737564049405b3380fdb96ac75 > package dph-prim-par-0.4.0-a2411981a52bb04ae3b57a3bcf0824c6 is > unusable due to missing or recursive > dependencies: > dph-base-0.4.0-385a36312e9cc9bc5a672eb91d4e2be8 > dph-prim-interface-0.4.0-523625c6a333b8571d7942e5 > 861b066f dph-prim-seq-0.4.0-23150bc82f21bd4268b1551af7a32901 > random-1.0.0.2-156803737564049405b3380 > fdb96ac75 > package dph-prim-seq-0.4.0-23150bc82f21bd4268b1551af7a32901 is > unusable due to missing or recursive > dependencies: > dph-base-0.4.0-385a36312e9cc9bc5a672eb91d4e2be8 > dph-prim-interface-0.4.0-523625c6a333b8571d7942e5 > 861b066f random-1.0.0.2-156803737564049405b3380fdb96ac75 > package dph-seq-0.4.0-1f5167ea371010387123b68e975177b2 is unusable due > to missing or recursive depe > ndencies: > dph-base-0.4.0-385a36312e9cc9bc5a672eb91d4e2be8 > dph-prim-seq-0.4.0-23150bc82f21bd4268b1551af7a329 > 01 random-1.0.0.2-156803737564049405b3380fdb96ac75 > package gio-0.11.0-a1b8e449598cebc0a1f5ede5721c9050 is unusable due to > missing or recursive depende > ncies: > glib-0.11.0-4a94b9bb6be01708fc9318c4a89fc135 > haskell98-1.0.1.1-0fdaf3b26bc38c43ce8371edf538dbf6 > package glade-0.11.1-269f5460770f38fd3611e7f0b744d3bd is unusable due > to missing or recursive depen > dencies: > cairo-0.11.0-72dde87f1e0a5c90fea5cd07ed797405 > glib-0.11.0-4a94b9bb6be01708fc9318c4a89fc135 gtk-0. > 11.0-36d58b0031e689175c433813944b65c5 > haskell98-1.0.1.1-0fdaf3b26bc38c43ce8371edf538dbf6 pango-0.11 > .0-d05d9f0e9c5b738a67ed0d24e084fb0d > package glib-0.11.0-4a94b9bb6be01708fc9318c4a89fc135 is unusable due > to missing or recursive depend > encies: > haskell98-1.0.1.1-0fdaf3b26bc38c43ce8371edf538dbf6 > package gtk-0.11.0-36d58b0031e689175c433813944b65c5 is unusable due to > missing or recursive depende > ncies: > cairo-0.11.0-72dde87f1e0a5c90fea5cd07ed797405 > gio-0.11.0-a1b8e449598cebc0a1f5ede5721c9050 glib-0. > 11.0-4a94b9bb6be01708fc9318c4a89fc135 > haskell98-1.0.1.1-0fdaf3b26bc38c43ce8371edf538dbf6 pango-0.11 > .0-d05d9f0e9c5b738a67ed0d24e084fb0d > package gtkglext-0.11.1-987eb12e32dcc852ba498eec3a29196f is unusable > due to missing or recursive de > pendencies: > cairo-0.11.0-72dde87f1e0a5c90fea5cd07ed797405 > glib-0.11.0-4a94b9bb6be01708fc9318c4a89fc135 gtk-0. > 11.0-36d58b0031e689175c433813944b65c5 > haskell98-1.0.1.1-0fdaf3b26bc38c43ce8371edf538dbf6 pango-0.11 > .0-d05d9f0e9c5b738a67ed0d24e084fb0d > package haskell-platform-2010.1.0.0-d41d8cd98f00b204e9800998ecf8427e > is unusable due to missing or > recursive dependencies: > QuickCheck-2.1.0.3-bf62d0a8213b04c27e0b8600c172a8b1 > haskell-src-1.0.1.3-6f583e83bf54a6ca0d07a352d > e5e8f4d > package haskell-src-1.0.1.3-6f583e83bf54a6ca0d07a352de5e8f4d is > unusable due to missing or recursiv > e dependencies: > haskell98-1.0.1.1-0fdaf3b26bc38c43ce8371edf538dbf6 > package haskell98-1.0.1.1-0fdaf3b26bc38c43ce8371edf538dbf6 is unusable > due to missing or recursive > dependencies: > random-1.0.0.2-156803737564049405b3380fdb96ac75 > package pango-0.11.0-d05d9f0e9c5b738a67ed0d24e084fb0d is unusable due > to missing or recursive depen > dencies: > cairo-0.11.0-72dde87f1e0a5c90fea5cd07ed797405 > glib-0.11.0-4a94b9bb6be01708fc9318c4a89fc135 haskel > l98-1.0.1.1-0fdaf3b26bc38c43ce8371edf538dbf6 > package random-1.0.0.2-156803737564049405b3380fdb96ac75 is shadowed by > package random-1.0.0.2-b570f > 45bd00b7a1bc98159f55cd12ecc > package soegtk-0.11.1-f55bac8cb473da3d88f7d16b3ff09cc2 is unusable due > to missing or recursive depe > ndencies: > cairo-0.11.0-72dde87f1e0a5c90fea5cd07ed797405 > glib-0.11.0-4a94b9bb6be01708fc9318c4a89fc135 gtk-0. > 11.0-36d58b0031e689175c433813944b65c5 > haskell98-1.0.1.1-0fdaf3b26bc38c43ce8371edf538dbf6 > hiding package OpenGL-2.2.3.0 to avoid conflict with later version > OpenGL-2.4.0.1 > hiding package Win32-2.2.0.1 to avoid conflict with later version > Win32-2.2.0.2 > hiding package array-0.3.0.0 to avoid conflict with later version > array-0.3.0.1 > hiding package base-3.0.3.2 to avoid conflict with later version base-4.2.0.0 > hiding package bytestring-0.9.1.5 to avoid conflict with later version > bytestring-0.9.1.7 > hiding package filepath-1.1.0.3 to avoid conflict with later version > filepath-1.1.0.4 > hiding package mtl-1.1.0.2 to avoid conflict with later version mtl-1.1.1.0 > hiding package parsec-2.1.0.1 to avoid conflict with later version > parsec-3.1.0 > hiding package time-1.1.4 to avoid conflict with later version time-1.2.0.3 > hiding package utf8-string-0.3.4 to avoid conflict with later version > utf8-string-0.3.6 > wired-in package ghc-prim mapped to > ghc-prim-0.2.0.0-d062610a70b26dce7f0809a3a984e0b8 > wired-in package integer-gmp mapped to > integer-gmp-0.2.0.0-fa82a0df93dc30b4a7c5654dd7c68cf4 > wired-in package base mapped to base-4.2.0.0-f9f9ffe572130b994c2080b74a5b4e68 > wired-in package rts mapped to builtin_rts > wired-in package haskell98 not found. > wired-in package template-haskell mapped to > template-haskell-2.4.0.0-4e889e188d5d6909681d875bc63a59 > f2 > wired-in package dph-seq not found. > wired-in package dph-par not found. > Hsc static flags: -static > *** Chasing dependencies: > Chasing modules from: *demo.hs > > demo.hs:10:7: > Could not find module `System.Glib.GError': > locations searched: > System\Glib\GError.hs > System\Glib\GError.lhs > *** Deleting temp files: > Deleting: > *** Deleting temp dirs: > Deleting: > > -- > _______________________________________________ > Haskell-Cafe mailing list > [email protected] > http://www.haskell.org/mailman/listinfo/haskell-cafe > -- Ivan Lazar Miljenovic [email protected] IvanMiljenovic.wordpress.com _______________________________________________ Haskell-Cafe mailing list [email protected] http://www.haskell.org/mailman/listinfo/haskell-cafe
