Simon Marlow wrote:
> The original version should also evaluate the expression 'cis wn' only
> once: [...]

Nice theory, but GHC's interpreter and compiler behave differently:

-- Main.hs -----------------------------------------------------------
module Main where

import Data.Complex ( Complex )
import qualified Data.Complex ( cis )
import Debug.Trace

cis :: (RealFloat a) => a -> Complex a
cis x = trace "cis" $ Data.Complex.cis x

nco1, nco2 :: RealFloat a => a -> [ Complex a ]
nco1 wn = 1 : map ((*) (cis wn)) (nco1 wn)
nco2 wn = iterate (cis wn *) 1

main :: IO ()
main = do
   let test f = print . take 5 . f $ (pi/2 :: Double)
   test nco1
   test nco2
----------------------------------------------------------------------
panne@jeanluc:~> ghci Main.hs
   ___         ___ _
  / _ \ /\  /\/ __(_)
 / /_\// /_/ / /  | |      GHC Interactive, version 5.05, for Haskell 98.
/ /_\\/ __  / /___| |      http://www.haskell.org/ghc/
\____/\/ /_/\____/|_|      Type :? for help.

Loading package base ... linking ... done.
Compiling Main             ( Main.hs, interpreted )
Ok, modules loaded: Main.
*Main> main
[1.0 :+ 0.0,cis
6.123031769111886e-17 :+ 1.0,cis
(-1.0) :+ 1.2246063538223773e-16,cis
(-1.836909530733566e-16) :+ (-1.0),cis
1.0 :+ (-2.4492127076447545e-16)]
[1.0 :+ 0.0,cis
6.123031769111886e-17 :+ 1.0,(-1.0) :+ 1.2246063538223773e-16,(-1.836909530733566e-16) :+ (-1.0),1.0 :+ (-2.4492127076447545e-16)]
*Main> :quit
Leaving GHCi.
panne@jeanluc:~> ghc -Wall -O Main.hs && ./a.out
cis
cis
cis
cis
[1.0 :+ 0.0,6.123031769111886e-17 :+ 1.0,(-1.0) :+ 1.2246063538223773e-16,(-1.836909530733566e-16) :+ (-1.0),1.0 :+ (-2.4492127076447545e-16)]
cis
[1.0 :+ 0.0,6.123031769111886e-17 :+ 1.0,(-1.0) :+ 1.2246063538223773e-16,(-1.836909530733566e-16) :+ (-1.0),1.0 :+ (-2.4492127076447545e-16)]
----------------------------------------------------------------------

???

Cheers,
   S.

_______________________________________________
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell

Reply via email to