[Haskell-cafe] Re: Trying to figure out a segfault caused by
haskeline.
ryan winkelmaier
syfran92 at gmail.com
Wed Mar 31 23:47:15 EDT 2010
Hi,
Nobody seems to have any idea what is happening yet. Though thanks for
trying dagit (forgot to add haskell-cafe to my repliess to him).
Quick update incase it helps, compiling with profiling and running with the
-xc option results in,
<Main.CAF:runInputT_rOA><System.Posix.Files.CAF>Segmentation fault
I'm still working on it but could it be the configuration file? thats the
thing the haskeline accesses files for right?
On Mon, Mar 29, 2010 at 8:28 PM, ryan winkelmaier <syfran92 at gmail.com>wrote:
> Hey everyone,
>
> I'm looking for help with a seg fault that takes out both my ghci and darcs
> as well as anything that uses haskeline. A bug on the haskeline trac hasn't
> gotten any response so I figured I might as well figure this out myself and
> get ghci up and running again.
>
> Using the test program below I get the same segmentation fault, so I run it
> using gdb and get the following,
>
> Program received signal SIGSEGV, Segmentation fault.
> 0x000000000053fdce in base_ForeignziCziString_zdwa_info ()
>
> My knowledge of this is very limited from here on out so here is what I was
> able to get together.
>
> On the 20th call of base_ForeignziCziString_zdwa_info
> r14 is 0 so
>
> 0x000000000053fdce <+22>: movsbq (%r14),%rax
>
> produces the segfault.
> From what I understand this is happening in the Foreign.C.String module but
> thats as much as I know.
> Anyone have advice on where to go next?
>
> System info:
> Distribution: gentoo amd64
> Ghc version: currently 6.12.1 (though the segfault happends on any of the
> ones with haskeline)
> Haskeline version: 0.6.2.2
>
> Here is the test program
>
>
> ----------------------------------------------------------------------------------------------------
> module Main where
>
> import System.Console.Haskeline
> import System.Environment
>
> {--
> Testing the line-input functions and their interaction with ctrl-c signals.
>
> Usage:
> ./Test (line input)
> ./Test chars (character input)
> --}
>
> mySettings :: Settings IO
> mySettings = defaultSettings {historyFile = Just "myhist"}
>
> main :: IO ()
> main = do
> args <- getArgs
> let inputFunc = case args of
> ["chars"] -> fmap (fmap (\c -> [c])) . getInputChar
> _ -> getInputLine
> runInputT mySettings $ withInterrupt $ loop inputFunc 0
> where
> loop inputFunc n = do
> minput <- handleInterrupt (return (Just "Caught interrupted"))
> $ inputFunc (show n ++ ":")
> case minput of
> Nothing -> return ()
> Just "quit" -> return ()
> Just "q" -> return ()
> Just s -> do
> outputStrLn ("line " ++ show n ++ ":" ++ s)
> loop inputFunc (n+1)
>
> ------------------------------------------------------------------------------------------------------------------------
>
>
> Syfran
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20100331/9ea8a994/attachment.html
More information about the Haskell-Cafe
mailing list