----------------------------------------------------------------------------- -- | -- Module : Windll -- Copyright : (c) Tamar Christina 2009 - 2010 -- License : GPL -- -- Maintainer : tamar@zhox.com -- Stability : experimental -- Portability : portable -- -- The main entry file for the preprocessor -- part of the WinDll suite -- ----------------------------------------------------------------------------- module Main where import Tests.Exec.CmdArgs import Tests.Exec.Analyze import WinDll.Session.Hs2lib import WinDll.Utils.Feedback import WinDll.Utils.DepScanner hiding (main) import WinDll.Parsers.Hs2lib import WinDll.Identifier import System.Info import Control.Monad.State import Control.Monad.Error -- | Determine the platform we're currently running on, so we can tweak the defaults a bit mode :: Platform mode = case os of "mingw32" -> Windows _ -> Unix main = goArgs mode bootstrap -- | Get the ball rolling on everything bootstrap :: Config -> IO () bootstrap cfg = do val <- runErrorT (evalStateT mainStart cfg) case val of (Left str) -> fail ("Program returned error in computation: '" ++ str ++ "'") (Right _) -> return () -- | Start of the main computation mainStart :: Exec () mainStart = do inform _normal "Program starting up..." session <- get -- These lines do all the needed calculations traceDeps -- Read all dependencies, so we find the tree of files which need parsing readFromFiles -- Read all datastructures from the read dependencies. enablePragmas -- Process the enabled commandline pragmas. The other pragmas are determined later on -- The following lines do actual writing of outputs value <- analyzeModule -- clean up cleanup inform _detail "Program terminating..." liftIO $ putStrLn "Done."