Maybe you want to remove Snowflake.o (or even *.o) and then try compiling it again.
Regards, Paul Liu On Sun, Jan 30, 2011 at 4:11 PM, michael rice <nowg...@yahoo.com> wrote: > SimpleGraphics has a bunch of main programs: main0, main1, main2, main3, > and main3book. I sequentially changed each to main and ran all five > successfully. > > Then I did the same for Snowflake.lhs (see code below) which already had a > single main function. > > Michael > > ============== > > [michael@localhost src]$ ghc --make Snowflake -main-is Snowflake > Linking Snowflake ... > /usr/lib/ghc-6.12.3/libHSrtsmain.a(Main.o): In function `main': > (.text+0x10): undefined reference to `ZCMain_main_closure' > /usr/lib/ghc-6.12.3/libHSrtsmain.a(Main.o): In function `main': > (.text+0x18): undefined reference to `__stginit_ZCMain' > collect2: ld returned 1 exit status > [michael@localhost src]$ > > ============== > > > This code was automatically extracted from a .lhs file that > uses the following convention: > > -- lines beginning with ">" are executable > -- lines beginning with "<" are in the text, > but not necessarily executable > -- lines beginning with "|" are also in the text, > but are often just expressions or code fragments. > > > module Snowflake where > > import SOE > > > m = 81 :: Int -- multiple of 3 for triangle size > > x = 250 :: Int -- x and y coordinates of > > y = 250 :: Int -- center of snowflake > > colors = [ Magenta, Blue, Green, Red, Yellow ] > > > snowflake :: Window -> IO () > > snowflake w = do > > drawTri w x y m 0 False -- draw first triangle w/flat top > > flake w x y m 0 True -- begin recursion to complete job > > > flake :: Window -> Int -> Int -> Int -> Int -> Bool -> IO () > > flake w x y m c o = do > > drawTri w x y m c o -- draw second triangle > > let c1 = (c+1)`mod`5 -- get next color > > if (m<=3) then return () -- if too small, we're done > > else do > > flake w (x-2*m) (y-m) (m`div`3) c1 True -- NW > > flake w (x+2*m) (y-m) (m`div`3) c1 True -- NE > > flake w x (y+2*m) (m`div`3) c1 True -- S > > flake w (x-2*m) (y+m) (m`div`3) c1 False -- SW > > flake w (x+2*m) (y+m) (m`div`3) c1 False -- SE > > flake w x (y-2*m) (m`div`3) c1 False -- N > > > drawTri :: Window -> Int -> Int -> Int -> Int -> Bool -> IO () > > drawTri w x y m c o = > > let d = (3*m) `div` 2 > > ps = if o > > then [(x,y-3*m), (x-3*m,y+d), (x+3*m,y+d)] -- side at bottom > > else [ (x,y+3*m), (x-3*m,y-d), (x+3*m,y-d)] -- side at top > > in drawInWindow w > > (withColor (colors !! c) > > (polygon ps)) > > > main > > = runGraphics ( > > do w <- openWindow "Snowflake Fractal" (500,500) > > drawInWindow w (withColor White > > (polygon [(0,0),(499,0),(499,499),(0,499)])) > > snowflake w > > spaceClose w > > ) > > > spaceClose :: Window -> IO () > > spaceClose w > > = do k <- getKey w > > if k==' ' || k == '\x0' > > then closeWindow w > > else spaceClose w > > > --- On *Sun, 1/30/11, Daniel Fischer <daniel.is.fisc...@googlemail.com>*wrote: > > > From: Daniel Fischer <daniel.is.fisc...@googlemail.com> > Subject: Re: [Haskell-cafe] Code from Haskell School of Expression hanging. > To: haskell-cafe@haskell.org, "michael rice" <nowg...@yahoo.com> > Date: Sunday, January 30, 2011, 6:48 PM > > > On Monday 31 January 2011 00:27:41, michael rice wrote: > > And here's the same with GHC. It never gets to linking and creating an > > executable the way the GLFW sample program does. > > > > Michael > > > > =============== > > > > [michael@localhost ~]$ cd ./SOE/SOE/src > > [michael@localhost src]$ ghc --make SimpleGraphics.lhs > > [2 of 2] Compiling SimpleGraphics ( SimpleGraphics.lhs, > > SimpleGraphics.o ) [michael@localhost src]$ > > The module name is not Main, so to get an executable, you have to tell ghc > what the Main module is. > Assuming SimpleGraphics.lhs contains a main function, > > $ ghc --make SimpleGraphics -main-is SimpleGraphics > > should do it. > > Cheers, > Daniel > > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -- Regards, Paul Liu
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe