Haskell Gurus,

I have tried to use profiling to tell me what's going on here, but it hasn't helped much, probably because I'm not interpreting the results correctly.

Empirically I have determined that the show's are pretty slow, so an alternative to them would be helpful. I replaced the show's with "", and compiled with -O2 and not much improvement.

I need to write _a lot_ of code in this style. A few words about how best to do this would be helpful. Laziness, infinite lists, uvector ??

Help...

Thanks,

Brian


import Complex
import System.IO

genData :: Double -> Int -> (Double -> Complex Double) -> ([Double], [Complex Double])
genData tstop n f =
    let deltat = tstop / (fromIntegral n)
        t = [ fromIntegral(i) * deltat | i <- [0..n-1]]
    in
      (t, map f t)

main =
    do let (t, y) = genData 100.0E-6 (2 ^ 15) (\x -> x :+ 0.0)
       h <- openFile "data.txt" WriteMode
       mapM_ (\(x, y) ->
                  do hPutStr h (show t)
                     hPutStr h " "
                     hPutStrLn h (show (realPart y)))
                 (zip t y)
       hClose h
_______________________________________________
Haskell-Cafe mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to