
Hello Neil , I was using TagSoup 0.8 with great success. On upgrading to 0.9 I have this error: TQ\TagSoup\TagSoupExtensions.lhs:29:17: `Tag' is not applied to enough type arguments Expected kind `*', but `Tag' has kind `* -> *' In the type synonym declaration for `Bundle' Failed, modules loaded: TQ.Common.TextAndListHandling. where line 29 is the type declaration for 'bundle' in the following code:
module TQ.TagSoup.TagSoupExtensions where
import TQ.Common.TextAndListHandling
import Text.HTML.TagSoup
import Text.HTML.Download
import Control.Monad
import Data.List
import Data.Char
type Bundle = [Tag]
[snip]
tagsOnPage :: String -> IO(String)
tagsOnPage url = do
tags <- liftM parseTags $ openURL url
let results = unlines $ map(show) $ tags
return (results)
extractTags :: Tag -> Tag -> [Tag] -> [Tag]
extractTags fromTag toTag tags = takeWhile (~/= toTag ) $ dropWhile (~/= fromTag ) tags
extractTagsBetween :: Tag -> [Tag] -> [Tag]
extractTagsBetween _ [] = []
extractTagsBetween markerTag tags = if startTags == []
then []
else [head startTags] ++ (takeWhile (~/= markerTag ) $ tail
startTags)
where
startTags = dropWhile (~/= markerTag ) tags
I need to repair this code quickly. I am hoping you can quickly help me resolve this. Thanks. Ralph Hodgson, @ralphtq http://twitter.com/ralphtq

Neil says that the API of TagSoup changed in 0.9.
All usages of the type Tag should now take a type argument, e.g. Tag String.
Regards,
Malcolm
On Wednesday, May 19, 2010, at 08:05AM, "Ralph Hodgson"
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Thanks Malcolm, Providing a 'String' type argument worked:
type Bundle = [Tag String]
extractTags :: Tag String -> Tag String -> Bundle -> Bundle
extractTags fromTag toTag tags = takeWhile (~/= toTag ) $ dropWhile (~/= fromTag ) tags
From: Malcolm Wallace [mailto:malcolm.wallace@me.com]
Sent: Wednesday, May 19, 2010 1:48 AM
To: rhodgson@topquadrant.com
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] TagSoup 0.9
Neil says that the API of TagSoup changed in 0.9.
All usages of the type Tag should now take a type argument, e.g. Tag String.
Regards,
Malcolm
On Wednesday, May 19, 2010, at 08:05AM, "Ralph Hodgson"
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Hello Neil , I was using TagSoup 0.8 with great success. On upgrading to 0.9 I have this error: TQ\TagSoup\TagSoupExtensions.lhs:29:17: `Tag' is not applied to enough type arguments Expected kind `*', but `Tag' has kind `* -> *' In the type synonym declaration for `Bundle' Failed, modules loaded: TQ.Common.TextAndListHandling. where line 29 is the type declaration for 'bundle' in the following code:
module TQ.TagSoup.TagSoupExtensions where
import TQ.Common.TextAndListHandling
import Text.HTML.TagSoup
import Text.HTML.Download
import Control.Monad
import Data.List
import Data.Char
type Bundle = [Tag]
[snip]
tagsOnPage :: String -> IO(String)
tagsOnPage url = do
tags <- liftM parseTags $ openURL url
let results = unlines $ map(show) $ tags
return (results)
extractTags :: Tag -> Tag -> [Tag] -> [Tag]
extractTags fromTag toTag tags = takeWhile (~/= toTag ) $ dropWhile (~/= fromTag ) tags
extractTagsBetween :: Tag -> [Tag] -> [Tag]
extractTagsBetween _ [] = []
extractTagsBetween markerTag tags = if startTags == []
then []
else [head startTags] ++ (takeWhile (~/= markerTag ) $ tail startTags)
where
startTags = dropWhile (~/= markerTag ) tags
I need to repair this code quickly. I am hoping you can quickly help me resolve this. Thanks. Ralph Hodgson, @ralphtq http://twitter.com/ralphtq

Forgot to add: I now need to understand the following warnings on this line "> import Text.HTML.Download": TagSoupExtensions.lhs:24:2: Warning: In the use of `openItem' (imported from Text.HTML.Download): Deprecated: "Use package HTTP, module Network.HTTP, getResponseBody =<< simpleHTTP (getRequest url)" TagSoupExtensions.lhs:24:2: Warning: In the use of `openURL' (imported from Text.HTML.Download): Deprecated: "Use package HTTP, module Network.HTTP, getResponseBody =<< simpleHTTP (getRequest url)" Ok, modules loaded: TQ.TagSoup.TagSoupExtensions. *TQ.TagSoup.TagSoupExtensions> From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of Ralph Hodgson Sent: Wednesday, May 19, 2010 10:30 AM To: 'Malcolm Wallace' Cc: haskell-cafe@haskell.org Subject: RE: [Haskell-cafe] TagSoup 0.9 Thanks Malcolm, Providing a 'String' type argument worked:
type Bundle = [Tag String]
extractTags :: Tag String -> Tag String -> Bundle -> Bundle
extractTags fromTag toTag tags = takeWhile (~/= toTag ) $ dropWhile (~/= fromTag ) tags
From: Malcolm Wallace [mailto:malcolm.wallace@me.com]
Sent: Wednesday, May 19, 2010 1:48 AM
To: rhodgson@topquadrant.com
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] TagSoup 0.9
Neil says that the API of TagSoup changed in 0.9.
All usages of the type Tag should now take a type argument, e.g. Tag String.
Regards,
Malcolm
On Wednesday, May 19, 2010, at 08:05AM, "Ralph Hodgson"
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Hello Neil , I was using TagSoup 0.8 with great success. On upgrading to 0.9 I have this error: TQ\TagSoup\TagSoupExtensions.lhs:29:17: `Tag' is not applied to enough type arguments Expected kind `*', but `Tag' has kind `* -> *' In the type synonym declaration for `Bundle' Failed, modules loaded: TQ.Common.TextAndListHandling. where line 29 is the type declaration for 'bundle' in the following code:
module TQ.TagSoup.TagSoupExtensions where
import TQ.Common.TextAndListHandling
import Text.HTML.TagSoup
import Text.HTML.Download
import Control.Monad
import Data.List
import Data.Char
type Bundle = [Tag]
[snip]
tagsOnPage :: String -> IO(String)
tagsOnPage url = do
tags <- liftM parseTags $ openURL url
let results = unlines $ map(show) $ tags
return (results)
extractTags :: Tag -> Tag -> [Tag] -> [Tag]
extractTags fromTag toTag tags = takeWhile (~/= toTag ) $ dropWhile (~/= fromTag ) tags
extractTagsBetween :: Tag -> [Tag] -> [Tag]
extractTagsBetween _ [] = []
extractTagsBetween markerTag tags = if startTags == []
then []
else [head startTags] ++ (takeWhile (~/= markerTag ) $ tail startTags)
where
startTags = dropWhile (~/= markerTag ) tags
I need to repair this code quickly. I am hoping you can quickly help me resolve this. Thanks. Ralph Hodgson, @ralphtq http://twitter.com/ralphtq

On Wednesday 19 May 2010 19:46:57, Ralph Hodgson wrote:
Forgot to add: I now need to understand the following warnings on this line "> import Text.HTML.Download":
In Text.HTML.Download, there's the following: {-| /DEPRECATED/: Use the HTTP package instead: > import Network.HTTP > openURL x = getResponseBody =<< simpleHTTP (getRequest x) This module simply downloads a page off the internet. It is very restricted, and it not intended for proper use. The original version was by Alistair Bayley, with additional help from Daniel McAllansmith. It is taken from the Haskell-Cafe mailing list \"Simple HTTP lib for Windows?\", 18 Jan 2007. http://thread.gmane.org/gmane.comp.lang.haskell.cafe/18443/ -} and {-# DEPRECATED openItem, openURL "Use package HTTP, module Network.HTTP, getResponseBody =<< simpleHTTP (getRequest url)" #-} So, don't use Text.HTML.Download anymore, instead use the functions from the HTTP package. Deprecated stuff will probably be removed in one of the next releases.

Or use things from the download-curl package, which provides a nice openURL function. daniel.is.fischer:
On Wednesday 19 May 2010 19:46:57, Ralph Hodgson wrote:
Forgot to add: I now need to understand the following warnings on this line "> import Text.HTML.Download":
In Text.HTML.Download, there's the following:
{-| /DEPRECATED/: Use the HTTP package instead:
> import Network.HTTP > openURL x = getResponseBody =<< simpleHTTP (getRequest x)

Hi Ralph,
I was using TagSoup 0.8 with great success. On upgrading to 0.9 I have this error:
TQ\TagSoup\TagSoupExtensions.lhs:29:17: `Tag' is not applied to enough type arguments Expected kind `*', but `Tag' has kind `* -> *' In the type synonym declaration for `Bundle' Failed, modules loaded: TQ.Common.TextAndListHandling.
My change notes have this being a change between 0.6 and 0.8. As Malcolm says, any old uses of "Tag" should become "Tag String". The reason is that Tag is now parameterised, and you can use Tag ByteString etc. However, I should point out that Tag ByteString won't be any faster than Tag String in this version (it's in the future work pile).
Forgot to add: I now need to understand the following warnings on this line "> import Text.HTML.Download":
Everyone's comments have been right. I previously included Text.HTML.Download so that it was easy to test tagsoup against the web. Since I first wrote that snippet the HTTP downloading libraries have improved substantially, so people should use those in favour of the version in tagsoup - you'll be able to connect to more websites in more reliable ways, go through proxies etc. I don't intend to remove the Download module any time soon, but I will do eventually. Thanks, Neil

I was using TagSoup 0.8 with great success. On upgrading to 0.9 I have
Thanks Neil, Using Network.HTTP worked. However something else I have just run into concerns some web pages that start with: <?xml version="1.0" encoding="iso-8859-1"?> <!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> I get the following bad result: TagText "HTTP/1.1 200 OK\r\nContent-Type: text/html\r\nLast-Modified: Tue, 27 Oct 2009 19:30:40 GMT\r\nETag: \"6f248cf73b57ca1:25e2\"\r\nDate: Sun, 23 May 2010 22:46:41 GMT\r\nTransfer-Encoding: chunked\r\nConnection: close\r\nConnection: Transfer-Encoding\r\n\r\n00004000\r\n\255\254<\NUL?\NULx\NULm\NULl\NUL \NULv\NULe\NULr\NULs\NULi\NULo\NULn\NUL=\NUL\"\NUL1\NUL.\NUL0\NUL\"\NUL \NULe\NULn\NULc\NULo\NULd\NULi\NULn\NULg\NUL=\NUL\"\NULi\NULs\NULo\NUL-\NUL8 \NUL8\NUL5\NUL9\NUL-\NUL1\NUL\"\NUL etc etc Is this an easy thing to fix? I've started to look over the code. -----Original Message----- From: Neil Mitchell [mailto:ndmitchell@gmail.com] Sent: Wednesday, May 19, 2010 12:19 PM To: Ralph Hodgson Cc: Daniel Fischer; haskell-cafe@haskell.org; Don Stewart Subject: Re: [Haskell-cafe] TagSoup 0.9 Hi Ralph, this error:
TQ\TagSoup\TagSoupExtensions.lhs:29:17:
`Tag' is not applied to enough type arguments
Expected kind `*', but `Tag' has kind `* -> *'
In the type synonym declaration for `Bundle'
Failed, modules loaded: TQ.Common.TextAndListHandling.
My change notes have this being a change between 0.6 and 0.8. As Malcolm says, any old uses of "Tag" should become "Tag String". The reason is that Tag is now parameterised, and you can use Tag ByteString etc. However, I should point out that Tag ByteString won't be any faster than Tag String in this version (it's in the future work pile).
Forgot to add: I now need to understand the following warnings on this
line "> import Text.HTML.Download":
Everyone's comments have been right. I previously included Text.HTML.Download so that it was easy to test tagsoup against the web. Since I first wrote that snippet the HTTP downloading libraries have improved substantially, so people should use those in favour of the version in tagsoup - you'll be able to connect to more websites in more reliable ways, go through proxies etc. I don't intend to remove the Download module any time soon, but I will do eventually. Thanks, Neil

Hi,
From what I can tell of your example you've managed to get the raw HTTP response in Unicode, which isn't suitable for sending to tagsoup. I've not used the Network.HTTP library for downloading much, but when I did I thought it stripped the headers automatically.
Can you just print the first few lines of the output you get from the
HTTP library, without passing them through tagsoup. That should show
the problem independent of tagsoup.
Thanks, Neil
On Mon, May 24, 2010 at 3:24 AM, Ralph Hodgson
Thanks Neil,
Using Network.HTTP worked.
However something else I have just run into concerns some web pages that start with:
<?xml version="1.0" encoding="iso-8859-1"?>
<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd">
I get the following bad result:
TagText "HTTP/1.1 200 OK\r\nContent-Type: text/html\r\nLast-Modified: Tue, 27 Oct 2009 19:30:40 GMT\r\nETag: \"6f248cf73b57ca1:25e2\"\r\nDate: Sun, 23 May 2010 22:46:41 GMT\r\nTransfer-Encoding: chunked\r\nConnection: close\r\nConnection: Transfer-Encoding\r\n\r\n00004000\r\n\255\254<\NUL?\NULx\NULm\NULl\NUL \NULv\NULe\NULr\NULs\NULi\NULo\NULn\NUL=\NUL\"\NUL1\NUL.\NUL0\NUL\"\NUL \NULe\NULn\NULc\NULo\NULd\NULi\NULn\NULg\NUL=\NUL\"\NULi\NULs\NULo\NUL-\NUL8\NUL8\NUL5\NUL9\NUL-\NUL1\NUL\"\NUL
etc etc
Is this an easy thing to fix? I've started to look over the code.
-----Original Message----- From: Neil Mitchell [mailto:ndmitchell@gmail.com] Sent: Wednesday, May 19, 2010 12:19 PM To: Ralph Hodgson Cc: Daniel Fischer; haskell-cafe@haskell.org; Don Stewart Subject: Re: [Haskell-cafe] TagSoup 0.9
Hi Ralph,
I was using TagSoup 0.8 with great success. On upgrading to 0.9 I have this error:
TQ\TagSoup\TagSoupExtensions.lhs:29:17:
`Tag' is not applied to enough type arguments
Expected kind `*', but `Tag' has kind `* -> *'
In the type synonym declaration for `Bundle'
Failed, modules loaded: TQ.Common.TextAndListHandling.
My change notes have this being a change between 0.6 and 0.8. As
Malcolm says, any old uses of "Tag" should become "Tag String". The
reason is that Tag is now parameterised, and you can use Tag
ByteString etc. However, I should point out that Tag ByteString won't
be any faster than Tag String in this version (it's in the future work
pile).
Forgot to add: I now need to understand the following warnings on this
line "> import Text.HTML.Download":
Everyone's comments have been right. I previously included
Text.HTML.Download so that it was easy to test tagsoup against the
web. Since I first wrote that snippet the HTTP downloading libraries
have improved substantially, so people should use those in favour of
the version in tagsoup - you'll be able to connect to more websites in
more reliable ways, go through proxies etc. I don't intend to remove
the Download module any time soon, but I will do eventually.
Thanks, Neil

Don Stewart schrieb:
Or use things from the download-curl package, which provides a nice openURL function.
The openURL function from TagSoup is lazy, which the proposed replacement 'getResponseBody =<< simpleHTTP (getRequest x)' is not. Is the openURL function from download-curl lazy?

schlepptop:
Don Stewart schrieb:
Or use things from the download-curl package, which provides a nice openURL function.
The openURL function from TagSoup is lazy, which the proposed replacement 'getResponseBody =<< simpleHTTP (getRequest x)' is not. Is the openURL function from download-curl lazy?
Yes, see: Network.Curl.Download.Lazy.openLazyURI though I think it is possible that I strictified the code. Have a play around with it if it doesn't meet your needs -- should be /trivial/ to ensure it is chunk-wise lazy.

Don, More angst with Windows 7 permissions. I hope this is a simple thing for you or someone else to help me with. I have successfully installed other packages into my private cabal area. When it came to the Haskell curl package, I got permission errors. Just to prove that things go to the right places, here is a successful run with the Parseargs Package. C:\Users\Ralph>cabal install parseargs Resolving dependencies... Downloading parseargs-0.1.3... Configuring parseargs-0.1.3... Preprocessing library parseargs-0.1.3... Preprocessing executables for parseargs-0.1.3... Building parseargs-0.1.3... [1 of 1] Compiling System.Console.ParseArgs ( System\Console\ParseArgs.hs, dist\ build\System\Console\ParseArgs.o ) Registering parseargs-0.1.3... [1 of 2] Compiling System.Console.ParseArgs ( System\Console\ParseArgs.hs, dist\ build\parseargs-example\parseargs-example-tmp\System\Console\ParseArgs.o ) [2 of 2] Compiling Main ( parseargs-example.hs, dist\build\parseargs -example\parseargs-example-tmp\Main.o ) Linking dist\build\parseargs-example\parseargs-example.exe ... Installing library in C:\Users\Ralph\AppData\Roaming\cabal\parseargs-0.1.3\ghc-6.10.4 Installing executable(s) in C:\Users\Ralph\AppData\Roaming\cabal\bin Registering parseargs-0.1.3... Parseargs installed fine and the package list shows it in my cabal directory. C:\Users\Ralph>ghc-pkg list C:/Program Files (x86)/Haskell Platform/2009.2.0.2\package.conf: Cabal-1.6.0.3, GLUT-2.1.1.2, HTTP-4000.0.6, HUnit-1.2.0.3, OpenGL-2.2.1.1, QuickCheck-1.2.0.0, Win32-2.2.0.0, array-0.2.0.0, base-3.0.3.1, base-4.1.0.0, bytestring-0.9.1.4, cgi-3001.1.7.1, containers-0.2.0.1, directory-1.0.0.3, (dph-base-0.3), (dph-par-0.3), (dph-prim-interface-0.3), (dph-prim-par-0.3), (dph-prim-seq-0.3), (dph-seq-0.3), extensible-exceptions-0.1.1.0, fgl-5.4.2.2, filepath-1.1.0.2, (ghc-6.10.4), ghc-prim-0.1.0.0, haddock-2.4.2, haskell-src-1.0.1.3, haskell98-1.0.1.0, hpc-0.5.0.3, html-1.0.1.2, integer-0.1.0.1, mtl-1.1.0.2, network-2.2.1.4, old-locale-1.0.0.1, old-time-1.0.0.2, packedstring-0.1.0.1, parallel-1.1.0.1, parsec-2.1.0.1, pretty-1.0.1.0, process-1.0.1.1, random-1.0.0.1, regex-base-0.72.0.2, regex-compat-0.71.0.1, regex-posix-0.72.0.3, rts-1.0, stm-2.1.1.2, syb-0.1.0.1, template-haskell-2.3.0.1, time-1.1.2.4, xhtml-3000.2.0.1, zlib-0.5.0.0 C:\Users\Ralph\AppData\Roaming\ghc\i386-mingw32-6.10.4\package.conf: Cabal-1.8.0.4, ListZipper-1.1.1.0, QuickCheck-2.1.0.3, bytestring-0.9.1.6, deepseq-1.1.0.0, parseargs-0.1.3, tagsoup-0.9 C:\Users\Ralph> Now for curl. I installed Mingw32 (following the advice at http://old.nabble.com/cURL-under-Windows-again-td21789068.html#a21789068) This is what happened when I went to my windows shell: C:\Users\Ralph\AppData\Roaming\cabal\curl-1.3.5>runhaskell setup build Preprocessing library curl-1.3.5... Building curl-1.3.5... Registering curl-1.3.5... C:\Users\Ralph\AppData\Roaming\cabal\curl-1.3.5>runhaskell setup install setup: permission denied I am wondering if the curl package is trying to put things in system folders? Help much appreciated - tight deadlines Ralph -----Original Message----- From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of Don Stewart Sent: Wednesday, May 19, 2010 1:37 PM To: Henning Thielemann Cc: haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] TagSoup 0.9 schlepptop:
Don Stewart schrieb:
Or use things from the download-curl package, which provides a nice
openURL function.
The openURL function from TagSoup is lazy, which the proposed
replacement 'getResponseBody =<< simpleHTTP (getRequest x)' is not. Is
the openURL function from download-curl lazy?
Yes, see: Network.Curl.Download.Lazy.openLazyURI though I think it is possible that I strictified the code. Have a play around with it if it doesn't meet your needs -- should be /trivial/ to ensure it is chunk-wise lazy. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 31 May 2010 22:50, Ralph Hodgson
This is what happened when I went to my windows shell:
C:\Users\Ralph\AppData\Roaming\cabal\curl-1.3.5>runhaskell setup build
Preprocessing library curl-1.3.5...
Building curl-1.3.5...
Registering curl-1.3.5...
C:\Users\Ralph\AppData\Roaming\cabal\curl-1.3.5>runhaskell setup install
setup: permission denied
Don't you want to be installing the curl binding through MinGW's shell rather than going back to the Windows shell? Best wishes Stephen

Thanks - Yes that is what I did. I have curl working fine on the MAC - I
will have to devote more time to Windows 7.
The MAC work has revealed a strange problem in download-curl. I'll have more
to say about that later.
-----Original Message-----
From: Stephen Tetley [mailto:stephen.tetley@gmail.com]
Sent: Tuesday, June 01, 2010 10:25 AM
To: rhodgson@topquadrant.com
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Installing Curl on Windows 7 - permissions
problem
On 31 May 2010 22:50, Ralph Hodgson
This is what happened when I went to my windows shell:
C:\Users\Ralph\AppData\Roaming\cabal\curl-1.3.5>runhaskell setup build
Preprocessing library curl-1.3.5...
Building curl-1.3.5...
Registering curl-1.3.5...
C:\Users\Ralph\AppData\Roaming\cabal\curl-1.3.5>runhaskell setup install
setup: permission denied
Don't you want to be installing the curl binding through MinGW's shell rather than going back to the Windows shell? Best wishes Stephen

On Monday 31 May 2010 23:50:58, Ralph Hodgson wrote:
Don,
More angst with Windows 7 permissions. I hope this is a simple thing for you or someone else to help me with.
I have successfully installed other packages into my private cabal area.
When it came to the Haskell curl package, I got permission errors.
Just to prove that things go to the right places, here is a successful run with the Parseargs Package.
C:\Users\Ralph>cabal install parseargs
<snip>
Now for curl.
This is what happened when I went to my windows shell:
C:\Users\Ralph\AppData\Roaming\cabal\curl-1.3.5>runhaskell setup build
Preprocessing library curl-1.3.5...
Building curl-1.3.5...
Registering curl-1.3.5...
C:\Users\Ralph\AppData\Roaming\cabal\curl-1.3.5>runhaskell setup install
setup: permission denied
I am wondering if the curl package is trying to put things in system folders?
It's not the library, it's runhaskell ./Setup.hs ... versus cabal install The previous defaults to global installs, the latter to user installs. So you can either - run cabal install in the package directory (if you don't give a package name to install, it installs [tries to install] the package from the current directory) - pass the --user flag to runhaskell ./Setup.hs, runhaskell ./Setup.hs configure --user --prefix=C:\Users\Ralph\... Getting into the habit of always using cabal install prevents such predicaments.
Help much appreciated - tight deadlines
Ralph

Yes - I understand more now - thanks. -----Original Message----- From: daniel.is.fischer@web.de [mailto:daniel.is.fischer@web.de] Sent: Tuesday, June 01, 2010 10:49 AM To: haskell-cafe@haskell.org; rhodgson@topquadrant.com Cc: 'Don Stewart'; 'Henning Thielemann' Subject: Re: [Haskell-cafe] Installing Curl on Windows 7 - permissions problem On Monday 31 May 2010 23:50:58, Ralph Hodgson wrote:
Don,
More angst with Windows 7 permissions. I hope this is a simple thing for you or someone else to help me with.
I have successfully installed other packages into my private cabal area.
When it came to the Haskell curl package, I got permission errors.
Just to prove that things go to the right places, here is a successful run with the Parseargs Package.
C:\Users\Ralph>cabal install parseargs
<snip>
Now for curl.
This is what happened when I went to my windows shell:
C:\Users\Ralph\AppData\Roaming\cabal\curl-1.3.5>runhaskell setup build
Preprocessing library curl-1.3.5...
Building curl-1.3.5...
Registering curl-1.3.5...
C:\Users\Ralph\AppData\Roaming\cabal\curl-1.3.5>runhaskell setup install
setup: permission denied
I am wondering if the curl package is trying to put things in system folders?
It's not the library, it's runhaskell ./Setup.hs ... versus cabal install The previous defaults to global installs, the latter to user installs. So you can either - run cabal install in the package directory (if you don't give a package name to install, it installs [tries to install] the package from the current directory) - pass the --user flag to runhaskell ./Setup.hs, runhaskell ./Setup.hs configure --user --prefix=C:\Users\Ralph\... Getting into the habit of always using cabal install prevents such predicaments.
Help much appreciated - tight deadlines
Ralph

Permissions issue was straight-forward to resolve. Yesterday I tracked this down to a conflict with versions of bytestring. ghc.6.10.4 needs bytestring-0.9.1.4 ghc-pkg: unregistering bytestring-0.9.1.4 would break the following packages: ha ddock-2.4.2 ghc-6.10.4 Win32-2.2.0.0 regex-base-0.72.0.2 regex-posix-0.72.0.3 re gex-compat-0.71.0.1 zlib-0.5.0.0 HTTP-4000.0.6 cgi-3001.1.7.1 curl-1.3.5 QuickCh eck-2.1.0.3 tagsoup-0.9 feed-0.3.7 tagsoup-0.10 utf8-string-0.3.6 xml-1.3.7 (use --force to override) other libraries need bytestring-09.1.6 ghc-pkg: unregistering bytestring-0.9.1.6 would break the following packages: Wi n32-2.2.0.0 Win32-2.2.0.2 HTTP-4000.0.9 (use --force to override) Yesterday I could not access haskell.org to see if I can install a newer version of GHC - network or server is done. Today I am upgrading everything to ghc-6.12.2 There must be a tool somewhere that can assess potential conflicts : A needs B (>2) A needs C (>1) but C needs B (<2) I will look once I get passed these install issues From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of Ralph Hodgson Sent: Monday, May 31, 2010 2:51 PM To: 'Don Stewart' Cc: 'Henning Thielemann'; haskell-cafe@haskell.org Subject: [Haskell-cafe] Installing Curl on Windows 7 - permissions problem Don, More angst with Windows 7 permissions. I hope this is a simple thing for you or someone else to help me with. I have successfully installed other packages into my private cabal area. When it came to the Haskell curl package, I got permission errors. Just to prove that things go to the right places, here is a successful run with the Parseargs Package. C:\Users\Ralph>cabal install parseargs Resolving dependencies... Downloading parseargs-0.1.3... Configuring parseargs-0.1.3... Preprocessing library parseargs-0.1.3... Preprocessing executables for parseargs-0.1.3... Building parseargs-0.1.3... [1 of 1] Compiling System.Console.ParseArgs ( System\Console\ParseArgs.hs, dist\ build\System\Console\ParseArgs.o ) Registering parseargs-0.1.3... [1 of 2] Compiling System.Console.ParseArgs ( System\Console\ParseArgs.hs, dist\ build\parseargs-example\parseargs-example-tmp\System\Console\ParseArgs.o ) [2 of 2] Compiling Main ( parseargs-example.hs, dist\build\parseargs -example\parseargs-example-tmp\Main.o ) Linking dist\build\parseargs-example\parseargs-example.exe ... Installing library in C:\Users\Ralph\AppData\Roaming\cabal\parseargs-0.1.3\ghc-6.10.4 Installing executable(s) in C:\Users\Ralph\AppData\Roaming\cabal\bin Registering parseargs-0.1.3... Parseargs installed fine and the package list shows it in my cabal directory. C:\Users\Ralph>ghc-pkg list C:/Program Files (x86)/Haskell Platform/2009.2.0.2\package.conf: Cabal-1.6.0.3, GLUT-2.1.1.2, HTTP-4000.0.6, HUnit-1.2.0.3, OpenGL-2.2.1.1, QuickCheck-1.2.0.0, Win32-2.2.0.0, array-0.2.0.0, base-3.0.3.1, base-4.1.0.0, bytestring-0.9.1.4, cgi-3001.1.7.1, containers-0.2.0.1, directory-1.0.0.3, (dph-base-0.3), (dph-par-0.3), (dph-prim-interface-0.3), (dph-prim-par-0.3), (dph-prim-seq-0.3), (dph-seq-0.3), extensible-exceptions-0.1.1.0, fgl-5.4.2.2, filepath-1.1.0.2, (ghc-6.10.4), ghc-prim-0.1.0.0, haddock-2.4.2, haskell-src-1.0.1.3, haskell98-1.0.1.0, hpc-0.5.0.3, html-1.0.1.2, integer-0.1.0.1, mtl-1.1.0.2, network-2.2.1.4, old-locale-1.0.0.1, old-time-1.0.0.2, packedstring-0.1.0.1, parallel-1.1.0.1, parsec-2.1.0.1, pretty-1.0.1.0, process-1.0.1.1, random-1.0.0.1, regex-base-0.72.0.2, regex-compat-0.71.0.1, regex-posix-0.72.0.3, rts-1.0, stm-2.1.1.2, syb-0.1.0.1, template-haskell-2.3.0.1, time-1.1.2.4, xhtml-3000.2.0.1, zlib-0.5.0.0 C:\Users\Ralph\AppData\Roaming\ghc\i386-mingw32-6.10.4\package.conf: Cabal-1.8.0.4, ListZipper-1.1.1.0, QuickCheck-2.1.0.3, bytestring-0.9.1.6, deepseq-1.1.0.0, parseargs-0.1.3, tagsoup-0.9 C:\Users\Ralph> Now for curl. I installed Mingw32 (following the advice at http://old.nabble.com/cURL-under-Windows-again-td21789068.html#a21789068) This is what happened when I went to my windows shell: C:\Users\Ralph\AppData\Roaming\cabal\curl-1.3.5>runhaskell setup build Preprocessing library curl-1.3.5... Building curl-1.3.5... Registering curl-1.3.5... C:\Users\Ralph\AppData\Roaming\cabal\curl-1.3.5>runhaskell setup install setup: permission denied I am wondering if the curl package is trying to put things in system folders? Help much appreciated - tight deadlines Ralph -----Original Message----- From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of Don Stewart Sent: Wednesday, May 19, 2010 1:37 PM To: Henning Thielemann Cc: haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] TagSoup 0.9 schlepptop:
Don Stewart schrieb:
Or use things from the download-curl package, which provides a nice
openURL function.
The openURL function from TagSoup is lazy, which the proposed
replacement 'getResponseBody =<< simpleHTTP (getRequest x)' is not. Is
the openURL function from download-curl lazy?
Yes, see: Network.Curl.Download.Lazy.openLazyURI though I think it is possible that I strictified the code. Have a play around with it if it doesn't meet your needs -- should be /trivial/ to ensure it is chunk-wise lazy. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

"base-3.0.3.2-b2241f4c659fe250ebb821a4173f40c9" doesn't exist (use --force to override) Having installed GHC 6.12.2, I am hitting these problems with every package I tried to install: C:\Users\Ralph>cabal install parsec Resolving dependencies... Configuring parsec-2.1.0.1... Preprocessing library parsec-2.1.0.1... Building parsec-2.1.0.1... [ 1 of 10] Compiling Text.ParserCombinators.Parsec.Pos ( Text\ParserCombinators\ Parsec\Pos.hs, dist\build\Text\ParserCombinators\Parsec\Pos.o ) [snip] [ 9 of 10] Compiling Text.ParserCombinators.Parsec.Perm ( Text\ParserCombinators \Parsec\Perm.hs, dist\build\Text\ParserCombinators\Parsec\Perm.o ) Text\ParserCombinators\Parsec\Perm.hs:1:0: Warning: Module `Prelude' is deprecated: You are using the old package `base' version 3.x. Future GHC versions will not support base version 3.x. You should update your code to use the new base version 4.x. [10 of 10] Compiling Text.ParserCombinators.Parsec.Language ( Text\ParserCombina tors\Parsec\Language.hs, dist\build\Text\ParserCombinators\Parsec\Language.o ) Text\ParserCombinators\Parsec\Language.hs:1:0: Warning: Module `Prelude' is deprecated: You are using the old package `base' version 3.x. Future GHC versions will not support base version 3.x. You should update your code to use the new base version 4.x. Registering parsec-2.1.0.1... Installing library in C:\Users\Ralph\AppData\Roaming\cabal\parsec-2.1.0.1\ghc-6.12.2 Registering parsec-2.1.0.1... cabal: parsec-2.1.0.1: dependency "base-3.0.3.2-b2241f4c659fe250ebb821a4173f40c9" doesn't exist (use --force to override) cabal: Error: some packages failed to install: parsec-2.1.0.1 failed during the final install step. The exception was: exit: ExitFailure 1 I wonder what to do next? From: Ralph Hodgson [mailto:rhodgson@topquadrant.com] Sent: Tuesday, June 01, 2010 11:19 AM To: rhodgson@topquadrant.com; 'Don Stewart' Cc: 'Henning Thielemann'; haskell-cafe@haskell.org Subject: RE: [Haskell-cafe] Installing Curl on Windows 7 - no longer a permissions problem - due to dependency conflicts Permissions issue was straight-forward to resolve. Yesterday I tracked this down to a conflict with versions of bytestring. ghc.6.10.4 needs bytestring-0.9.1.4 ghc-pkg: unregistering bytestring-0.9.1.4 would break the following packages: ha ddock-2.4.2 ghc-6.10.4 Win32-2.2.0.0 regex-base-0.72.0.2 regex-posix-0.72.0.3 re gex-compat-0.71.0.1 zlib-0.5.0.0 HTTP-4000.0.6 cgi-3001.1.7.1 curl-1.3.5 QuickCh eck-2.1.0.3 tagsoup-0.9 feed-0.3.7 tagsoup-0.10 utf8-string-0.3.6 xml-1.3.7 (use --force to override) other libraries need bytestring-09.1.6 ghc-pkg: unregistering bytestring-0.9.1.6 would break the following packages: Wi n32-2.2.0.0 Win32-2.2.0.2 HTTP-4000.0.9 (use --force to override) Yesterday I could not access haskell.org to see if I can install a newer version of GHC - network or server is done. Today I am upgrading everything to ghc-6.12.2 There must be a tool somewhere that can assess potential conflicts : A needs B (>2) A needs C (>1) but C needs B (<2) I will look once I get passed these install issues From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of Ralph Hodgson Sent: Monday, May 31, 2010 2:51 PM To: 'Don Stewart' Cc: 'Henning Thielemann'; haskell-cafe@haskell.org Subject: [Haskell-cafe] Installing Curl on Windows 7 - permissions problem Don, More angst with Windows 7 permissions. I hope this is a simple thing for you or someone else to help me with. I have successfully installed other packages into my private cabal area. When it came to the Haskell curl package, I got permission errors. Just to prove that things go to the right places, here is a successful run with the Parseargs Package. C:\Users\Ralph>cabal install parseargs Resolving dependencies... Downloading parseargs-0.1.3... Configuring parseargs-0.1.3... Preprocessing library parseargs-0.1.3... Preprocessing executables for parseargs-0.1.3... Building parseargs-0.1.3... [1 of 1] Compiling System.Console.ParseArgs ( System\Console\ParseArgs.hs, dist\ build\System\Console\ParseArgs.o ) Registering parseargs-0.1.3... [1 of 2] Compiling System.Console.ParseArgs ( System\Console\ParseArgs.hs, dist\ build\parseargs-example\parseargs-example-tmp\System\Console\ParseArgs.o ) [2 of 2] Compiling Main ( parseargs-example.hs, dist\build\parseargs -example\parseargs-example-tmp\Main.o ) Linking dist\build\parseargs-example\parseargs-example.exe ... Installing library in C:\Users\Ralph\AppData\Roaming\cabal\parseargs-0.1.3\ghc-6.10.4 Installing executable(s) in C:\Users\Ralph\AppData\Roaming\cabal\bin Registering parseargs-0.1.3... Parseargs installed fine and the package list shows it in my cabal directory. C:\Users\Ralph>ghc-pkg list C:/Program Files (x86)/Haskell Platform/2009.2.0.2\package.conf: Cabal-1.6.0.3, GLUT-2.1.1.2, HTTP-4000.0.6, HUnit-1.2.0.3, OpenGL-2.2.1.1, QuickCheck-1.2.0.0, Win32-2.2.0.0, array-0.2.0.0, base-3.0.3.1, base-4.1.0.0, bytestring-0.9.1.4, cgi-3001.1.7.1, containers-0.2.0.1, directory-1.0.0.3, (dph-base-0.3), (dph-par-0.3), (dph-prim-interface-0.3), (dph-prim-par-0.3), (dph-prim-seq-0.3), (dph-seq-0.3), extensible-exceptions-0.1.1.0, fgl-5.4.2.2, filepath-1.1.0.2, (ghc-6.10.4), ghc-prim-0.1.0.0, haddock-2.4.2, haskell-src-1.0.1.3, haskell98-1.0.1.0, hpc-0.5.0.3, html-1.0.1.2, integer-0.1.0.1, mtl-1.1.0.2, network-2.2.1.4, old-locale-1.0.0.1, old-time-1.0.0.2, packedstring-0.1.0.1, parallel-1.1.0.1, parsec-2.1.0.1, pretty-1.0.1.0, process-1.0.1.1, random-1.0.0.1, regex-base-0.72.0.2, regex-compat-0.71.0.1, regex-posix-0.72.0.3, rts-1.0, stm-2.1.1.2, syb-0.1.0.1, template-haskell-2.3.0.1, time-1.1.2.4, xhtml-3000.2.0.1, zlib-0.5.0.0 C:\Users\Ralph\AppData\Roaming\ghc\i386-mingw32-6.10.4\package.conf: Cabal-1.8.0.4, ListZipper-1.1.1.0, QuickCheck-2.1.0.3, bytestring-0.9.1.6, deepseq-1.1.0.0, parseargs-0.1.3, tagsoup-0.9 C:\Users\Ralph> Now for curl. I installed Mingw32 (following the advice at http://old.nabble.com/cURL-under-Windows-again-td21789068.html#a21789068) This is what happened when I went to my windows shell: C:\Users\Ralph\AppData\Roaming\cabal\curl-1.3.5>runhaskell setup build Preprocessing library curl-1.3.5... Building curl-1.3.5... Registering curl-1.3.5... C:\Users\Ralph\AppData\Roaming\cabal\curl-1.3.5>runhaskell setup install setup: permission denied I am wondering if the curl package is trying to put things in system folders? Help much appreciated - tight deadlines Ralph -----Original Message----- From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of Don Stewart Sent: Wednesday, May 19, 2010 1:37 PM To: Henning Thielemann Cc: haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] TagSoup 0.9 schlepptop:
Don Stewart schrieb:
Or use things from the download-curl package, which provides a nice
openURL function.
The openURL function from TagSoup is lazy, which the proposed
replacement 'getResponseBody =<< simpleHTTP (getRequest x)' is not. Is
the openURL function from download-curl lazy?
Yes, see: Network.Curl.Download.Lazy.openLazyURI though I think it is possible that I strictified the code. Have a play around with it if it doesn't meet your needs -- should be /trivial/ to ensure it is chunk-wise lazy. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Tuesday 01 June 2010 22:31:21, Ralph Hodgson wrote:
"base-3.0.3.2-b2241f4c659fe250ebb821a4173f40c9" doesn't exist (use --force to override)
You probably have a package.conf from the previous GHC still lying around. If your new GHC is in the system space, it'll probably be enough to remove all package.conf files from the user space, if your new GHC lives in user space, remove all package.conf files from the user space *except the one ghc-6.12.2 created* (that's the one containing the package ghc-6.12.2).
Having installed GHC 6.12.2, I am hitting these problems with every package I tried to install:
C:\Users\Ralph>cabal install parsec
Resolving dependencies...
Configuring parsec-2.1.0.1...
Preprocessing library parsec-2.1.0.1...
Building parsec-2.1.0.1...
[ 1 of 10] Compiling Text.ParserCombinators.Parsec.Pos ( Text\ParserCombinators\
Parsec\Pos.hs, dist\build\Text\ParserCombinators\Parsec\Pos.o )
[snip]
[ 9 of 10] Compiling Text.ParserCombinators.Parsec.Perm ( Text\ParserCombinators
\Parsec\Perm.hs, dist\build\Text\ParserCombinators\Parsec\Perm.o )
Text\ParserCombinators\Parsec\Perm.hs:1:0:
Warning: Module `Prelude' is deprecated:
You are using the old package `base' version 3.x.
Future GHC versions will not support base version 3.x. You
should update your code to use the new base version 4.x.
[10 of 10] Compiling Text.ParserCombinators.Parsec.Language ( Text\ParserCombina
tors\Parsec\Language.hs, dist\build\Text\ParserCombinators\Parsec\Language.o )
Text\ParserCombinators\Parsec\Language.hs:1:0:
Warning: Module `Prelude' is deprecated:
You are using the old package `base' version 3.x.
Future GHC versions will not support base version 3.x. You
should update your code to use the new base version 4.x.
Registering parsec-2.1.0.1...
Installing library in
C:\Users\Ralph\AppData\Roaming\cabal\parsec-2.1.0.1\ghc-6.12.2
Registering parsec-2.1.0.1...
cabal: parsec-2.1.0.1: dependency
"base-3.0.3.2-b2241f4c659fe250ebb821a4173f40c9" doesn't exist (use --force to
override)
cabal: Error: some packages failed to install:
parsec-2.1.0.1 failed during the final install step. The exception was:
exit: ExitFailure 1
I wonder what to do next?

Thanks Daniel, I will give it a try I just did some work on the MAC to verify that everything worked there. And all is well with MAC GHC 6.12.1 -----Original Message----- From: daniel.is.fischer@web.de [mailto:daniel.is.fischer@web.de] Sent: Tuesday, June 01, 2010 2:03 PM To: haskell-cafe@haskell.org; rhodgson@topquadrant.com Subject: Re: [Haskell-cafe] Dependency issues with GHC 6.12.2 installing parsec and others On Tuesday 01 June 2010 22:31:21, Ralph Hodgson wrote:
"base-3.0.3.2-b2241f4c659fe250ebb821a4173f40c9" doesn't exist (use --force to override)
You probably have a package.conf from the previous GHC still lying around. If your new GHC is in the system space, it'll probably be enough to remove all package.conf files from the user space, if your new GHC lives in user space, remove all package.conf files from the user space *except the one ghc-6.12.2 created* (that's the one containing the package ghc-6.12.2).
Having installed GHC 6.12.2, I am hitting these problems with every package I tried to install:
C:\Users\Ralph>cabal install parsec
Resolving dependencies...
Configuring parsec-2.1.0.1...
Preprocessing library parsec-2.1.0.1...
Building parsec-2.1.0.1...
[ 1 of 10] Compiling Text.ParserCombinators.Parsec.Pos ( Text\ParserCombinators\
Parsec\Pos.hs, dist\build\Text\ParserCombinators\Parsec\Pos.o )
[snip]
[ 9 of 10] Compiling Text.ParserCombinators.Parsec.Perm ( Text\ParserCombinators
\Parsec\Perm.hs, dist\build\Text\ParserCombinators\Parsec\Perm.o )
Text\ParserCombinators\Parsec\Perm.hs:1:0:
Warning: Module `Prelude' is deprecated:
You are using the old package `base' version 3.x.
Future GHC versions will not support base version 3.x. You
should update your code to use the new base version 4.x.
[10 of 10] Compiling Text.ParserCombinators.Parsec.Language ( Text\ParserCombina
tors\Parsec\Language.hs, dist\build\Text\ParserCombinators\Parsec\Language.o )
Text\ParserCombinators\Parsec\Language.hs:1:0:
Warning: Module `Prelude' is deprecated:
You are using the old package `base' version 3.x.
Future GHC versions will not support base version 3.x. You
should update your code to use the new base version 4.x.
Registering parsec-2.1.0.1...
Installing library in
C:\Users\Ralph\AppData\Roaming\cabal\parsec-2.1.0.1\ghc-6.12.2
Registering parsec-2.1.0.1...
cabal: parsec-2.1.0.1: dependency
"base-3.0.3.2-b2241f4c659fe250ebb821a4173f40c9" doesn't exist (use --force to
override)
cabal: Error: some packages failed to install:
parsec-2.1.0.1 failed during the final install step. The exception was:
exit: ExitFailure 1
I wonder what to do next?

I decided to remove everything and start again with the Haskell Platform. I am back up and running enough to make progress. -----Original Message----- From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of Ralph Hodgson Sent: Tuesday, June 01, 2010 4:34 PM To: daniel.is.fischer@web.de; haskell-cafe@haskell.org Subject: RE: [Haskell-cafe] Dependency issues with GHC 6.12.2 installing parsec and others Thanks Daniel, I will give it a try I just did some work on the MAC to verify that everything worked there. And all is well with MAC GHC 6.12.1 -----Original Message----- From: daniel.is.fischer@web.de [mailto:daniel.is.fischer@web.de] Sent: Tuesday, June 01, 2010 2:03 PM To: haskell-cafe@haskell.org; rhodgson@topquadrant.com Subject: Re: [Haskell-cafe] Dependency issues with GHC 6.12.2 installing parsec and others On Tuesday 01 June 2010 22:31:21, Ralph Hodgson wrote:
"base-3.0.3.2-b2241f4c659fe250ebb821a4173f40c9" doesn't exist (use --force to override)
You probably have a package.conf from the previous GHC still lying around. If your new GHC is in the system space, it'll probably be enough to remove all package.conf files from the user space, if your new GHC lives in user space, remove all package.conf files from the user space *except the one ghc-6.12.2 created* (that's the one containing the package ghc-6.12.2).
Having installed GHC 6.12.2, I am hitting these problems with every package I tried to install:
C:\Users\Ralph>cabal install parsec
Resolving dependencies...
Configuring parsec-2.1.0.1...
Preprocessing library parsec-2.1.0.1...
Building parsec-2.1.0.1...
[ 1 of 10] Compiling Text.ParserCombinators.Parsec.Pos ( Text\ParserCombinators\
Parsec\Pos.hs, dist\build\Text\ParserCombinators\Parsec\Pos.o )
[snip]
[ 9 of 10] Compiling Text.ParserCombinators.Parsec.Perm ( Text\ParserCombinators
\Parsec\Perm.hs, dist\build\Text\ParserCombinators\Parsec\Perm.o )
Text\ParserCombinators\Parsec\Perm.hs:1:0:
Warning: Module `Prelude' is deprecated:
You are using the old package `base' version 3.x.
Future GHC versions will not support base version 3.x. You
should update your code to use the new base version 4.x.
[10 of 10] Compiling Text.ParserCombinators.Parsec.Language ( Text\ParserCombina
tors\Parsec\Language.hs, dist\build\Text\ParserCombinators\Parsec\Language.o )
Text\ParserCombinators\Parsec\Language.hs:1:0:
Warning: Module `Prelude' is deprecated:
You are using the old package `base' version 3.x.
Future GHC versions will not support base version 3.x. You
should update your code to use the new base version 4.x.
Registering parsec-2.1.0.1...
Installing library in
C:\Users\Ralph\AppData\Roaming\cabal\parsec-2.1.0.1\ghc-6.12.2
Registering parsec-2.1.0.1...
cabal: parsec-2.1.0.1: dependency
"base-3.0.3.2-b2241f4c659fe250ebb821a4173f40c9" doesn't exist (use --force to
override)
cabal: Error: some packages failed to install:
parsec-2.1.0.1 failed during the final install step. The exception was:
exit: ExitFailure 1
I wonder what to do next?
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

This appeared to be the case - re-installing the Haskell Platform as opposed to the latest GHC got things working again. -----Original Message----- From: daniel.is.fischer@web.de [mailto:daniel.is.fischer@web.de] Sent: Tuesday, June 01, 2010 2:03 PM To: haskell-cafe@haskell.org; rhodgson@topquadrant.com Subject: Re: [Haskell-cafe] Dependency issues with GHC 6.12.2 installing parsec and others On Tuesday 01 June 2010 22:31:21, Ralph Hodgson wrote:
"base-3.0.3.2-b2241f4c659fe250ebb821a4173f40c9" doesn't exist (use --force to override)
You probably have a package.conf from the previous GHC still lying around. If your new GHC is in the system space, it'll probably be enough to remove all package.conf files from the user space, if your new GHC lives in user space, remove all package.conf files from the user space *except the one ghc-6.12.2 created* (that's the one containing the package ghc-6.12.2).
Having installed GHC 6.12.2, I am hitting these problems with every package I tried to install:
C:\Users\Ralph>cabal install parsec
Resolving dependencies...
Configuring parsec-2.1.0.1...
Preprocessing library parsec-2.1.0.1...
Building parsec-2.1.0.1...
[ 1 of 10] Compiling Text.ParserCombinators.Parsec.Pos ( Text\ParserCombinators\
Parsec\Pos.hs, dist\build\Text\ParserCombinators\Parsec\Pos.o )
[snip]
[ 9 of 10] Compiling Text.ParserCombinators.Parsec.Perm ( Text\ParserCombinators
\Parsec\Perm.hs, dist\build\Text\ParserCombinators\Parsec\Perm.o )
Text\ParserCombinators\Parsec\Perm.hs:1:0:
Warning: Module `Prelude' is deprecated:
You are using the old package `base' version 3.x.
Future GHC versions will not support base version 3.x. You
should update your code to use the new base version 4.x.
[10 of 10] Compiling Text.ParserCombinators.Parsec.Language ( Text\ParserCombina
tors\Parsec\Language.hs, dist\build\Text\ParserCombinators\Parsec\Language.o )
Text\ParserCombinators\Parsec\Language.hs:1:0:
Warning: Module `Prelude' is deprecated:
You are using the old package `base' version 3.x.
Future GHC versions will not support base version 3.x. You
should update your code to use the new base version 4.x.
Registering parsec-2.1.0.1...
Installing library in
C:\Users\Ralph\AppData\Roaming\cabal\parsec-2.1.0.1\ghc-6.12.2
Registering parsec-2.1.0.1...
cabal: parsec-2.1.0.1: dependency
"base-3.0.3.2-b2241f4c659fe250ebb821a4173f40c9" doesn't exist (use --force to
override)
cabal: Error: some packages failed to install:
parsec-2.1.0.1 failed during the final install step. The exception was:
exit: ExitFailure 1
I wonder what to do next?
participants (7)
-
Daniel Fischer
-
Don Stewart
-
Henning Thielemann
-
Malcolm Wallace
-
Neil Mitchell
-
Ralph Hodgson
-
Stephen Tetley