Modules and a main function

W/r/t the code below, would somebody please explain the sense of having a main function in a module that is not named Main.hs? Michael From: http://www.haskell.org/haskellwiki/State_Monad ============ module StateGame where import Control.Monad.State -- Example use of State monad -- Passes a string of dictionary {a,b,c} -- Game is to produce a number from the string. -- By default the game is off, a C toggles the -- game on and off. A 'a' gives +1 and a b gives -1. -- E.g -- 'ab' = 0 -- 'ca' = 1 -- 'cabca' = 0 -- State = game is on or off & current score -- = (Bool, Int) type GameValue = Int type GameState = (Bool, Int) playGame :: String -> State GameState GameValue playGame [] = do (_, score) <- get return score playGame (x:xs) = do (on, score) <- get case x of 'a' | on -> put (on, score + 1) 'b' | on -> put (on, score - 1) 'c' -> put (not on, score) _ -> put (on, score) playGame xs startState = (False, 0) main = print $ evalState (playGame "abcaaacbbcabbab") startState

On Sat, Aug 27, 2011 at 15:31, michael rice
W/r/t the code below, would somebody please explain the sense of having a main function in a module that is not named Main.hs?
It's embedded test code; you can build a test program for the StateGame monad by using the --main-is parameter to GHC, or leave that off and get a library. -- brandon s allbery allbery.b@gmail.com wandering unix systems administrator (available) (412) 475-9364 vm/sms

I'm not sure how to do that. Please demonstrate.
Michael
________________________________
From: Brandon Allbery

Thanks all.
I was trying to use --main-is. I even man-ed ghc and thought I saw a double dash there.
As they say, believing is seeing.
Michael
________________________________
From: Daniel Fischer
I'm not sure how to do that. Please demonstrate.
Michael
ghc -O -main-is StateGame --make StateGame more generally, ghc -O -main-is Foo.bar --make Foo if the desired main is function bar in module Foo.

On Sat, Aug 27, 2011 at 16:24, michael rice
I'm not sure how to do that. Please demonstrate.
If you just compile it normally you have an unexported binding called "main" which is effectively (and actually, when compiled with optimization) discarded. If you do ghc --make --main-is GameState GameState.hs then GHC will use GameState.main as the entry point (instead of Main.main) and build a program instead of a library. http://www.haskell.org/ghc/docs/latest/html/users_guide/options-phases.html#... -- brandon s allbery allbery.b@gmail.com wandering unix systems administrator (available) (412) 475-9364 vm/sms
participants (3)
-
Brandon Allbery
-
Daniel Fischer
-
michael rice