profiling problems
Hal Daume III
hdaume@ISI.EDU
Tue, 25 Feb 2003 18:08:42 -0800 (PST)
Have you removed the .o and .hi files before compiling with -prof? These
are not compatible.
--
Hal Daume III
"Computer science is no more about computers | hdaume@isi.edu
than astronomy is about telescopes." -Dijkstra | www.isi.edu/~hdaume
On Tue, 25 Feb 2003, Damien R. Sullivan wrote:
> I have this code which compiles and runs normally, but gives bus errors or
> segfaults at run time when compiled with -prof -auto-all. ghc-5.04
> SunOS cownose.cs.indiana.edu 5.8 Generic_108528-18 sun4u sparc SUNW,Ultra-5_10
>
> What's wrong?
>
> import Numeric
> import Ratio
> import System
>
> top 1 = 1
> top n = 9*n*top (n-2) + oddfact (n-2)
>
> lfact :: [Integer]
> lfact = 1 : zipWith (*) [3,5 .. ] lfact
>
> oddfact :: Integer -> Integer
> oddfact n = lfact!!ni
> where
> ni = nint `div` 2
> nint = fromInteger n
>
> log_two :: Int -> Rational
> log_two lim = 2* top n % (3^lim * oddfact n)
> where n = fromIntegral lim
>
> log_tup :: Int -> (Rational, Rational)
> log_tup lim =
> -- TODO any chance I can drop the br? Would it get me more than a digit?
> (l + lo_err, l + hi_err)
> where
> l = log_two lim
> -- TODO double check these
> lo_err = (2)/(n+1)*(d/(1+c))^(lim+1)
> hi_err = (2)/(n+1)*d^(lim+1)
> -- original logs
> -- lo_err = (-2)/(n+1)*(d/(1+c))^(lim+1)
> -- hi_err = -lo_err
> -- lo_err = (-1)/(n+1)*x^(lim+1)
> -- c = 0
> n = toRational lim
> d = 1%3
> c = d
>
> log_tup_str lim =
> (floatlo, floathi, diff)
> where
> (lo, hi) = log_tup lim
> floatlo = floatRat lo lim
> floathi = floatRat hi lim
> diff = floathi - floatlo
>
>
> floatRat :: Rational -> Int -> Integer
> floatRat r lim =
> num*10^lim `div` den
> where
> num = numerator r
> den = denominator r
>
> main :: IO ()
> main =
> do
> args <- System.getArgs
> let lim :: Int
> lim = read (args!!0)
> let (s1, s2, s3) = log_tup_str lim
> let sh1 = show s1
> let l1 = length sh1
> let shd = show s3
> let ld = length shd
> putStrLn (show s1)
> putStrLn (show s2)
> putStrLn (show s3)
> putStr "digits: "
> putStrLn (show (l1-ld))
> _______________________________________________
> Haskell mailing list
> Haskell@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell
>