[Haskell-cafe] segfault depending on code position in source file

Damien Mattei damien.mattei at gmail.com
Fri Feb 22 09:55:17 UTC 2019


well i understand the difficulty, i just pos because ,really some times i
get incredible help that i coulmdn not even think it possible.
i admit the code is and the database connection is a stop help.
for the database i cannot do ,for the code i commented a lot  and i can
resume with this concise code that recreate the problem:

it's quite simple i noticed that after one lines (see in code the lines and
the upper case comments) the query to DB in getAlphaDelta does not works
anymore (as it worked before ) but other functions making queries works
that what is strange...

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
import Database.MySQL.Simple
import Database.MySQL.Simple.QueryResults
import Database.MySQL.Simple.Result

import Database.MySQL.Simple.QueryParams
import Database.MySQL.Simple.Param


import Control.Monad
import qualified Data.Text as Tx
import Debug.Trace
import Data.Maybe as Maybe
import Text.Read
import Data.Tuple.Extra


getAlphaDelta :: Connection -> String -> IO (Double,Double)
getAlphaDelta conn name = do
            let qry_head_AlphaDelta_AngularDistance = "select alpha,delta
from AngularDistance where Nom = ?" :: Query
            (alpha_delta_rows :: [(Double,Double)]) <- query conn
qry_head_AlphaDelta_AngularDistance (Only (name::String))
            return (head alpha_delta_rows)


main :: IO ()

main =

  do
    conn <- connect defaultConnectInfo
      { connectHost = "moita",
        connectUser = "mattei",
        connectPassword = "sidonie2",
        connectDatabase = "sidonie" }


-- check getAlphaDelta works:
-- HERE getAlphaDelta WORKS
    let name = "WOR   7"
    putStrLn $ show name
    ad <- getAlphaDelta conn name
    putStr "ad ="
    putStrLn $ show ad

    (names ::[Only Tx.Text])<- query_ conn "SELECT Nom FROM AngularDistance
WHERE distance > 0.000278"

-- AFTER THE PREVIOUS LINE getAlphaDelta WILL NOT WORKS AND ISSUE A
SEGFAULT IN GHCI
    let name3 = "A     7"
    putStrLn $ show name3
    ad3 <- getAlphaDelta conn name3
    putStr "ad3 ="
    putStrLn $ show ad3


close conn


here is the output:

[mattei at localhost Haskell]$ ghci
GHCi, version 8.2.2: http://www.haskell.org/ghc/  :? for help
Prelude> :load UpdateSidonie.hs
[1 of 1] Compiling Main             ( UpdateSidonie.hs, interpreted )
Ok, one module loaded.
*Main> main
"WOR   7"
ad =(17386.0,7120.0)
"A     7"
Segmentation fault (core dumped)

as you see the first call to getAlphaDelta is ok but the second issue a
Segmentation fault.

i will try now with ghci 8.4 .... and hiope to give you some news...

Damien

On Thu, Feb 21, 2019 at 8:15 PM Sven Panne <svenpanne at gmail.com> wrote:

> Am Do., 21. Feb. 2019 um 19:22 Uhr schrieb Damien Mattei <
> damien.mattei at gmail.com>:
>
>> i had attached the whole file, so anyone can read the whole code,
>> perheaps it could help, saying me if there is compilation error on other
>> ghc versions, with mine no error at compilation.
>>
>
> I very much doubt that anyone likes to read >500 lines of Haskell code
> with lots of external dependencies to help you with your problem. A good
> hint for Open Source SW in general: If you think you might have found a
> bug, cut down your example as much as possible, throw out as many external
> dependencies as you can while still reproducing your problem, then, and
> only then, post it to other people. You simply can't expect that other
> people will do that debugging work for you in their spare time. The code
> you post doesn't really have to make sense, it should just be the minimum
> amount of code needed to reproduce the problem.
>
> In a nutshell: The probability that you get some help is inversely
> proportional to the size of your example, and even more inversely
> proportional to the number of external dependencies (libraries etc.).
>
>
>> The problem to test is that without the database connection which is
>> behind a firewall of course ,the code can not be executed. [...]
>>
>
> Well, that is basically a show stopper for getting help...
>
>  I don't want to be mean, quite the opposite: I just want to explain why
> you probably won't receive any help in the current form. This is not
> special to the Haskell community, the situation would be very much the same
> if you posted an equivalent problem of similar size to the
> Racket/Python/... community. I'm quite sure that most maintainer would be
> happy to have a look e.g. at a program consisting of a dozen lines without
> external dependencies.
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20190222/66b74c70/attachment-0001.html>


More information about the Haskell-Cafe mailing list