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