[Haskell-cafe] Battling laziness

Joel Reymont joelr1 at gmail.com
Fri Dec 16 11:18:17 EST 2005


On Dec 16, 2005, at 3:47 PM, Simon Marlow wrote:

> I'm a bit mystified though, because looking at the code for
> Script.Array, all your arrays are unboxed, so I don't know where  
> all the
> Word8s and Ints are coming from.  It might be useful to do "+RTS
> -hyWord8 -hc" to see who generated the Word8s.

Done. http://wagerlabs.com/randomplay.word8.ps

        {-# SCC "launchScripts#8" #-}launch host $! script (bot, bot,  
affid)

The xx, xx, are Word8. affiliateIDs is all Word8 and looks like this:

affiliateIDs = [ [xx,xx,xx,xx,xx,xx,xx],
                  99 more like the above ]

I guess the whole affid list of lists is being pulled into script?  
How do I prevent this?

-----
launchScripts  :: Int
                -> NamePick
                -> TMVar (ClockTime, (Event CustomEvent))
                -> IO ()
launchScripts 0 _ _ = return ()
launchScripts n pick mbx =
     do n' <- case pick of
                Random -> {-# SCC "launchScripts#1" #-}liftIO $  
randomRIO (0, 8500)
                Straight -> {-# SCC "launchScripts#2" #-}return n
        let botnum = {-# SCC "launchScripts#3" #-}firstbot + n'
            bot = {-# SCC "launchScripts#4" #-}"m" ++ show botnum
            cell = {-# SCC "launchScripts#5" #-}botnum `mod` 100 - 1
            affid = {-# SCC "launchScripts#6" #-}if cell == -1
                       then [xx,xx,xx,xx,xx,xx,xx]
                       else affiliateIDs !! cell
        {-# SCC "launchScripts#7" #-}trace_ $ "Launching bot..." ++  
show n
        {-# SCC "launchScripts#8" #-}launch host $! script (bot, bot,  
affid)
        {-# SCC "launchScripts#9" #-}liftIO $ sleep_ 1000
        -- quit if we have been told to
        empty <- {-# SCC "launchScripts#10" #-}atomically $  
isEmptyTMVar mbx
        {-# SCC "launchScripts#11" #-}unless empty $ trace_  
"launchScripts: Done, exiting"
        {-# SCC "launchScripts#12" #-}when empty $ launchScripts (n -  
1) pick mbx


--
http://wagerlabs.com/







More information about the Haskell-Cafe mailing list