[Haskell-cafe] Fwd: hGetContents Illegal byte sequence / ghc-pkg
Benjamin Edwards
edwards.benj at gmail.com
Sat Aug 11 18:41:47 CEST 2012
Responding to the list..
---------- Forwarded message ----------
From: Benjamin Edwards <edwards.benj at gmail.com>
Date: 11 August 2012 17:37
Subject: Re: [Haskell-cafe] hGetContents Illegal byte sequence / ghc-pkg
To: David McBride <toad3k at gmail.com>
Thank you Gents,
Most useful. One thing that had escaped me is that of course, even if
hGetContents and friends are respecting *my* locale, I have a binary distro
and the package database probably isn't in my locale. I will try and find
that.
Thanks,
Ben
On 11 August 2012 15:26, David McBride <toad3k at gmail.com> wrote:
> I had this same problem a couple weeks ago when trying to install
> virthualenv and I don't really understand it got into a bad state, but the
> way I solved it was by fixing the locale settings on my gentoo machine so
> that I'm using UTF8. That just involved a few changes in /etc and then the
> problem went away.
>
> On Sat, Aug 11, 2012 at 7:13 AM, Benjamin Edwards <edwards.benj at gmail.com>wrote:
>
>> Hello café,
>>
>> I have a program that is crashing, and I have no idea why:
>>
>> module Main
>> where
>>
>> import System.Process (readProcessWithExitCode)
>>
>>
>> main :: IO ()
>> main = do _ <- readProcessWithExitCode "ghc-pkg" ["describe", "hoopl"] ""
>> putStrLn "Should never get here"
>>
>> this is using the process package from hackage. The program crashes with
>>
>> minimal-test: fd:5: hGetContents: invalid argument (invalid byte sequence)
>> minimal-test: thread blocked indefinitely in an MVar operation
>>
>> inspecting the source of readProcessWithExitCode yields an obvious
>> explanation to the MVar problem, but I don't understand why hGetContents is
>> so offended.
>>
>> For the lazy it is defined as follows:
>>
>> readProcessWithExitCode
>> :: FilePath -- ^ command to run
>> -> [String] -- ^ any arguments
>> -> String -- ^ standard input
>> -> IO (ExitCode,String,String) -- ^ exitcode, stdout, stderr
>> readProcessWithExitCode cmd args input = do
>> (Just inh, Just outh, Just errh, pid) <-
>> createProcess (proc cmd args){ std_in = CreatePipe,
>> std_out = CreatePipe,
>> std_err = CreatePipe }
>>
>> outMVar <- newEmptyMVar
>>
>> -- fork off a thread to start consuming stdout
>> out <- hGetContents outh
>> _ <- forkIO $ C.evaluate (length out) >> putMVar outMVar ()
>>
>> -- fork off a thread to start consuming stderr
>> err <- hGetContents errh
>> _ <- forkIO $ C.evaluate (length err) >> putMVar outMVar ()
>>
>> -- now write and flush any input
>> when (not (null input)) $ do hPutStr inh input; hFlush inh
>> hClose inh -- done with stdin
>>
>> -- wait on the output
>> takeMVar outMVar
>> takeMVar outMVar
>> hClose outh
>> hClose errh
>>
>> -- wait on the process
>> ex <- waitForProcess pid
>>
>> return (ex, out, err)
>>
>> Now having looked at the source of ghc-pkg it is dumping it's output
>> using putStr and friends, so that should be using my local encoding on the
>> system, right? and so should hGetContents in my program..?
>>
>> Now, for the curious: the reason I care is that this problem has
>> effectively prevented me from using virthualenv. Sadness and woe.
>>
>> _______________________________________________
>> Haskell-Cafe mailing list
>> Haskell-Cafe at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20120811/7c41f60e/attachment.htm>
More information about the Haskell-Cafe
mailing list