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







      <br>_______________________________________________<br>
Haskell-Cafe mailing list<br>
<a href="mailto:Haskell-Cafe@haskell.org">Haskell-Cafe@haskell.org</a><br>
<a href="http://www.haskell.org/mailman/listinfo/haskell-cafe" target="_blank">http://www.haskell.org/mailman/listinfo/haskell-cafe</a><br>
<br></blockquote></div><br><br clear="all"><br>-- <br>Regards,<br>Paul Liu<br><br>
</div>