[Haskell-cafe] Re: hmatrix's fitModel function crashes ghc(i)

Alberto Ruiz aruiz at um.es
Sat Nov 6 16:12:25 EDT 2010


Hello Roel,

Roel van Dijk wrote:
> Hello,
> 
> I would like to use hmatrix to do some function fitting with the
> Levenberg Marquardt algorithm. As an example I would like to fit the
> very simple function "f x = a*x + b" on some data points. The problem
> is that executing the 'fitModel' function crashes GHC(i) with a
> segmentation fault.

Can you reproduce it on a 32 bit machine?

There is a known problem with some hmatrix GSL wrappers on 64 bit in 
interpreted mode. This is mentioned at the end of the install page:

http://code.haskell.org/hmatrix/install.html

In this case the segmentation fault happens inside a foreign GSL 
function, only in interpreted code, and only in 64 bit. It does not 
happen in compiled code. (Although I have a report of a similar 
segmentation fault with compiled code if the output is redirected). I 
don't really know how to debug this kind of problem. As a first step I 
will try to obtain a minimal test case without any package dependencies.

This makes debugging difficult. Can anyone spot
> what I am doing wrong?

Your are doing nothing wrong. I will create a new, more visible page for 
the known problems.

Given all the lists of Double's it seems very
> easy to make an error regarding the number of arguments with the model
> function or the derivative.

Static argument checking would be ideal, but at least they are normal 
runtime errors and should never crash the program.

> Try to evaluate the 'test' function in the small program listed below.
> I would expect an output of [1, 0] (y = 1*x + 0) instead of a
> segmentation fault.

It works for me in 32 bit:

$ ghci Test.hs
GHCi, version 6.12.3: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Loading package ffi-1.0 ... linking ... done.
[1 of 1] Compiling Test             ( Test.hs, interpreted )
Ok, modules loaded: Test.
*Test> test
Loading package filepath-1.1.0.4 ... linking ... done.
Loading package old-locale-1.0.0.2 ... linking ... done.
Loading package old-time-1.0.0.5 ... linking ... done.
Loading package unix-2.4.0.2 ... linking ... done.
Loading package directory-1.0.1.1 ... linking ... done.
Loading package process-1.0.1.3 ... linking ... done.
Loading package array-0.3.0.1 ... linking ... done.
Loading package storable-complex-0.2.1 ... linking ... done.
Loading package hmatrix-0.10.0.1 ... linking ... done.
([1.0,0.0],(1><4)
  [ 1.0, 0.0, 1.0, 0.0 ])


> Relevant versions:
>  - hmatrix-0.10.0.0
>  - gsl-1.14
>  - ghc-6.12.3 (64 bit)
> 
> 
> Small program:
> 
> module Test where
> 
> -- from base:
> import Control.Arrow         ( second )
> import Control.Applicative   ( pure )
> 
> -- from hmatrix:
> import Data.Packed.Matrix    ( Matrix )
> import Numeric.GSL.Fitting   ( FittingMethod(LevenbergMarquardt), fitModel )
> 
> 
> -- input list of (x, y) pairs, output coefficients of "f x = a x * b"
> fitLinear :: [(Double, Double)] -> ([Double], Matrix Double)
> fitLinear samples = fitModel 1
>                              1
>                              10
>                              (linearModel, linearDer)
>                              (map (second pure) samples)
>                              [0, 0]
> 
> linearModel :: [Double] -> Double -> [Double]
> linearModel [a, b] x = [a*x + b, 0]
> linearModel _      x = error "wrong arguments"
> 
> linearDer :: [Double] -> Double -> [[Double]]
> linearDer [_, _] x = [[x, 0]]
> linearDer _      _ = error "wrong arguments"
> 
> test = fitLinear [(0,0), (1,1), (2,2)]



More information about the Haskell-Cafe mailing list