[Hackage] #181: cabal update fails to download package list

Hackage trac at galois.com
Sat Dec 15 14:50:07 EST 2007


#181: cabal update fails to download package list
----------------------------+-----------------------------------------------
  Reporter:  guest          |        Owner:         
      Type:  defect         |       Status:  new    
  Priority:  normal         |    Milestone:         
 Component:  cabal-install  |      Version:  HEAD   
  Severity:  major          |   Resolution:         
  Keywords:  cabal update   |   Difficulty:  normal 
Ghcversion:  6.6            |     Platform:  Windows
----------------------------+-----------------------------------------------
Comment (by guest):

 I think I've tracked this down.

 The failure's happening at Hackage/Update.hs. The 00-index.tar.gz in
 cabal/packages/hackage.haskell.org/ is around 180KB. If I change
 updateRepo as follows:

 {{{
 updateRepo cfg repo =
     do printf "Downloading package list from server '%s'\n" (repoURL repo)
        indexPath <- downloadIndex cfg repo
        file <- BS.readFile indexPath
        printf "length is %d" $ BS.length file

        -- should be the raw bits
        BS.writeFile "c:/foo.tar.gz" file
        BS.writeFile (dropExtension indexPath) (gunzip file)
        return ()
 }}}

 The foo.tar.gz file has 105 bytes. The 106th byte of 00-index.tar.gz is a
 {{{^Z}}}, which I think is getting interpreted as the Windows EOF
 character. If you change "Data.ByteString.Lazy.Char8" to
 "Data.ByteString.Lazy" I think you get the right semantics. Here's a
 patch. I'm not happy about the c2w and w2c calls everywhere, but it works
 on Windows now.

 {{{
 #!diff
 diff -r 225b3427562f Hackage/Index.hs
 --- a/Hackage/Index.hs  Sat Dec 15 14:19:33 2007 -0500
 +++ b/Hackage/Index.hs  Sat Dec 15 14:48:46 2007 -0500
 @@ -18,8 +18,9 @@ import Hackage.Tar

  import Prelude hiding (catch)
  import Control.Exception (catch, Exception(IOException))
 -import qualified Data.ByteString.Lazy.Char8 as BS
 -import Data.ByteString.Lazy.Char8 (ByteString)
 +import qualified Data.ByteString.Lazy as BS
 +import Data.ByteString.Internal (w2c)
 +import Data.ByteString.Lazy (ByteString)
  import System.FilePath ((</>), takeExtension, splitDirectories,
 normalise)
  import System.IO (hPutStrLn, stderr)
  import System.IO.Error (isDoesNotExistError)
 @@ -48,7 +49,7 @@ parseRepoIndex repo s =
         if takeExtension (tarFileName hdr) == ".cabal"
           then case splitDirectories (normalise (tarFileName hdr)) of
                  [pkgname,vers,_] ->
 -                  let descr = case parsePackageDescription (BS.unpack
 content) of
 +                  let descr = case parsePackageDescription (map w2c
 (BS.unpack content)) of
                          ParseOk _ d -> d
                          _           -> error $ "Couldn't read cabal file
 "
                                              ++ show (tarFileName hdr)
 diff -r 225b3427562f Hackage/Tar.hs
 --- a/Hackage/Tar.hs    Sat Dec 15 14:19:33 2007 -0500
 +++ b/Hackage/Tar.hs    Sat Dec 15 14:48:46 2007 -0500
 @@ -3,8 +3,9 @@ module Hackage.Tar (TarHeader(..), TarFi
                                           readTarArchive,
 extractTarArchive,
                                           extractTarGzFile, gunzip) where

 -import qualified Data.ByteString.Lazy.Char8 as BS
 -import Data.ByteString.Lazy.Char8 (ByteString)
 +import qualified Data.ByteString.Lazy as BS
 +import Data.ByteString.Internal(c2w,w2c)
 +import Data.ByteString.Lazy (ByteString)
  import Data.Bits ((.&.))
  import Data.Char (ord)
  import Data.Int (Int8, Int64)
 @@ -134,11 +135,11 @@ checkChkSum hdr s = s == chkSum hdr' ||
  checkChkSum hdr s = s == chkSum hdr' || s == signedChkSum hdr'
    where
      -- replace the checksum with spaces
 -    hdr' = BS.concat [BS.take 148 hdr, BS.replicate 8 ' ', BS.drop 156
 hdr]
 +    hdr' = BS.concat [BS.take 148 hdr, BS.replicate 8 (c2w ' '), BS.drop
 156 hdr]
      -- tar.info says that Sun tar is buggy and
      -- calculates the checksum using signed chars
 -    chkSum = BS.foldl' (\x y -> x + ord y) 0
 -    signedChkSum = BS.foldl' (\x y -> x + (ordSigned y)) 0
 +    chkSum = BS.foldl' (\x y -> x + ord (w2c y)) 0
 +    signedChkSum = BS.foldl' (\x y -> x + (ordSigned (w2c y))) 0

  ordSigned :: Char -> Int
  ordSigned c = fromIntegral (fromIntegral (ord c) :: Int8)
 @@ -156,7 +157,7 @@ getBytes off len = BS.take len . BS.drop
  getBytes off len = BS.take len . BS.drop off

  getByte :: Int64 -> ByteString -> Char
 -getByte off bs = BS.index bs off
 +getByte off bs = w2c $ BS.index bs off

  getString :: Int64 -> Int64 -> ByteString -> String
 -getString off len = BS.unpack . BS.takeWhile (/='\0') . getBytes off len
 +getString off len = \x -> map w2c ((BS.unpack . BS.takeWhile (/= (c2w
 '\0')) . getBytes off len) x)
 diff -r 225b3427562f Hackage/Update.hs
 --- a/Hackage/Update.hs Sat Dec 15 14:19:33 2007 -0500
 +++ b/Hackage/Update.hs Sat Dec 15 14:48:46 2007 -0500
 @@ -18,7 +18,7 @@ import Hackage.Fetch
  import Hackage.Fetch
  import Hackage.Tar

 -import qualified Data.ByteString.Lazy.Char8 as BS
 +import qualified Data.ByteString.Lazy as BS
  import System.FilePath (dropExtension)
  import Text.Printf
 }}}

 -- greg at gregorycollins.net

-- 
Ticket URL: <http://hackage.haskell.org/trac/hackage/ticket/181#comment:1>
Hackage <http://haskell.org/cabal/>
Hackage: Cabal and related projects


More information about the cabal-devel mailing list