On Wednesday 20 April 2011 21:55:51, Dan Doel wrote:
> 
> It's not a statistics bug. I'm reproducing it here using just
> vector-algorithms.

Yep. Attached a simple testcasewhich reproduces it and uses only vector and 
vector-algorithms.

> 
> Fill a vector of size N with [N..1], and (intro) sort it, and you get
> NaNs. But only with -O or above.

However, for me the NaNs disappear with the -msse2 option.

> Without optimization it doesn't
> happen (and nothing seems to be reading/writing out of bounds, as I
> compiled vector with UnsafeChecks earlier and it didn't complain).

Nor does it happen here with 7.0.2 or 7.0.1.

> 
> Filling the vector with [1..N] also doesn't trigger the NaNs. [0,0..0]
> and [0,0..1] trigger it.
> 
> I don't know what's going on yet. I have trouble believing it's a bug
> in vector-algorithms code, though, as I don't think I've written any
> RULEs (just INLINEs), and that's the one thing that comes to mind in
> library code that could cause a difference between -O0 and -O. So I'd
> tentatively suggest it's a vector, base or compiler bug.
> 
> The above testing is on 64-bit windows running a 32-bit copy of GHC,
> for reference.

32-bit linux here

> 
> My ability to investigate this will be a bit limited for the near
> future. If someone definitively tracks it down to bugs in my code,
> though, let me know, and I'll try and push a new release up on
> hackage.
> 
> -- Dan
{-# LANGUAGE BangPatterns #-}
module Main where

import qualified Data.Vector.Unboxed.Mutable as MU
import Data.Vector.Unboxed.Mutable (IOVector, unsafeRead, unsafeWrite, new)
import qualified Data.Vector.Algorithms.Intro as I

import Control.Monad (when)
import System.Environment (getArgs)

countNaNs :: IOVector Double -> IO Int
countNaNs a = go 0 0
  where
    len = MU.length a
    go !ct i
        | i < len = do
            x <- unsafeRead a i
            go (if isNaN x then ct+1 else ct) (i+1)
        | otherwise = return ct

sample :: Int -> IO (IOVector Double)
sample k = do
    a <- new k
    let foo :: Double -> Double
        foo x = 1.0 + sin x / x
        fill i x
            | i < k = do
                unsafeWrite a i (foo x)
                fill (i+1) (x+1.0)
            | otherwise = return a
    fill 0 (fromIntegral k * 10)

main :: IO ()
main = do
    args <- getArgs
    let k = case args of
              (arg:_) -> read arg
              _       -> 10000
    a <- sample k
    b <- countNaNs a
    when (b /= 0) (putStrLn $ "Before sorting: " ++ show b ++ " NaNs.")
    I.sort a
    c <- countNaNs a
    when (c /= 0) (putStrLn $ "After sorting: " ++ show c ++ " NaNs.")
_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to