Fixed nasty error involving GHCi, ghc and bytestring
[infinity.git] / Main.hs
blobaaed5e01e14ddca4c65390308207281925dba283
1 {-# LANGUAGE CPP #-}
2 module Main where
3 import Control.Concurrent
4 import System.Environment
5 import Control.Monad
6 import System.Exit
7 #ifdef STATIC_BUILD
8 import Infinity
9 #else
10 import System.Plugins
11 #endif
13 ghcargs = []
15 -- | Main entry point, if the bot is dynamically built
16 -- it will load the code appropriately and start, otherwise
17 -- it will just jump to a static main that we will execute with.
18 -- If executed with '-offline' it will go into offline mode where
19 -- you can just experiment with the plugin interface and whatnot.
20 main :: IO ()
21 main = do
22 av <- getArgs
23 let offline = if (null av) then False
24 else (if head av == "-offline" then True
25 else False)
26 putStrLn "infinity starting..."
27 #ifndef STATIC_BUILD
28 m <- makeAll "Infinity.hs" ghcargs
29 (mod,imain) <- case m of
30 MakeSuccess _ _ -> do
31 -- apparently there's some sort of limitation in regards to having modules
32 -- that re-export other modules and their symbols with hs-plugins. that is,
33 -- we cannot load Infinity.o and get the symbols from there such as imain,
34 -- instead we have to directly load Infinity/Main.o and get the syms from that
35 -- we run makeAll over Infinity.hs since it keeps the project hierarchy nice,
36 -- and it will cause all these modules to be reloaded anyway.
37 when offline $ do
38 stat <- load_ "Infinity/Main.o" [".","Infinity","Infinity/Plugins"] "offlinemode"
39 case stat of
40 LoadSuccess v m -> m
41 LoadFailure e -> do
42 putStrLn "Couldn't load Infinity.Main.offlinemode:"
43 mapM_ putStrLn e
44 exitWith $ ExitFailure 127
45 ldstat <- load_ "Infinity/Main.o" [".","Infinity","Infinity/Plugins"] "imain"
46 case ldstat of
47 LoadSuccess v m -> return (v,m)
48 LoadFailure e -> do
49 putStrLn "Couldn't load Infinity.Main.imain:"
50 mapM_ putStrLn e
51 exitWith $ ExitFailure 127
52 MakeFailure e -> do
53 putStrLn "FATAL: Couldn't compile Infinity.hs:"
54 mapM_ putStrLn e
55 exitWith $ ExitFailure 127
57 putStrLn "Compiled & Loaded Infinity.Main.imain..."
58 imain mod reboot
59 #else
60 when offline offlinemode
61 staticmain
62 #endif
64 #ifndef STATIC_BUILD
65 -- | Dynamic rebooting function
66 reboot :: Module -> a -> IO ()
67 reboot mod st = do
68 mkstat <- makeAll "Infinity.hs" ghcargs
69 case mkstat of
70 MakeSuccess _ o -> do
71 unloadAll mod
72 ldstat <- load_ "Infinity/Main.o" [".","Infinity","Infinity/Plugins"] "imain'"
73 case ldstat of
74 LoadFailure e -> fatality e
75 LoadSuccess v imain' -> do
76 putStrLn "REBOOT: Successful recompilation & reloading, rebooting..."
77 imain' v reboot st
78 MakeFailure e -> fatality e
79 where
80 fatality errs = do
81 putStrLn $ "REBOOT: FATAL: Couldn't reboot thread, err:"
82 mapM_ putStrLn errs
83 #else
84 -- | Dynamic rebooting function
85 -- Note: This is the static build so this
86 -- function does nothing.
87 reboot :: a -> a -> IO ()
88 reboot _ _ = return ()
89 #endif