Evaluation Question

Simon Marlow simonmar@microsoft.com
Mon, 20 Jan 2003 15:49:46 -0000


[ moved to haskell-caf=E9 ]

> Simon Marlow wrote:
>  > The original version should also evaluate the expression=20
> 'cis wn' only
>  > once: [...]
>=20
> Nice theory, but GHC's interpreter and compiler behave differently:
>=20
> -- Main.hs -----------------------------------------------------------
> module Main where
>=20
> import Data.Complex ( Complex )
> import qualified Data.Complex ( cis )
> import Debug.Trace
>=20
> cis :: (RealFloat a) =3D> a -> Complex a
> cis x =3D trace "cis" $ Data.Complex.cis x
>=20
> nco1, nco2 :: RealFloat a =3D> a -> [ Complex a ]
> nco1 wn =3D 1 : map ((*) (cis wn)) (nco1 wn)
> nco2 wn =3D iterate (cis wn *) 1
>=20
> main :: IO ()
> main =3D do
>     let test f =3D print . take 5 . f $ (pi/2 :: Double)
>     test nco1
>     test nco2
> ----------------------------------------------------------------------

Oops, I didn't notice that nco1 was recursive.  I should have said the =
expression (cis wn) is evaluated once for each call to nco1.  It is not =
evaluated once for each element of the list in map's second argument, =
which is what I thought was being asked.

> panne@jeanluc:~> ghci Main.hs
>     ___         ___ _
>    / _ \ /\  /\/ __(_)
>   / /_\// /_/ / /  | |      GHC Interactive, version 5.05,=20
> for Haskell 98.
> / /_\\/ __  / /___| |      http://www.haskell.org/ghc/
> \____/\/ /_/\____/|_|      Type :? for help.
>=20
> 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) :+=20
> 1.2246063538223773e-16,(-1.836909530733566e-16) :+ (-1.0),1.0=20
> :+ (-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) :+=20
> 1.2246063538223773e-16,(-1.836909530733566e-16) :+ (-1.0),1.0=20
> :+ (-2.4492127076447545e-16)]
> cis
> [1.0 :+ 0.0,6.123031769111886e-17 :+ 1.0,(-1.0) :+=20
> 1.2246063538223773e-16,(-1.836909530733566e-16) :+ (-1.0),1.0=20
> :+ (-2.4492127076447545e-16)]
> ----------------------------------------------------------------------

This difference is due to the different buffering behaviour on =
stdout/stderr between compiled and interpreted programs.  GHCi sets =
these handles to unbuffered by default, which tends to be more useful =
for an interpreter.

Cheers,
	Simon