| 
									
										
										
										
											2014-05-22 01:08:36 +05:30
										 |  |  | {-# LANGUAGE TemplateHaskell #-} | 
					
						
							| 
									
										
										
										
											2014-05-04 04:28:08 +05:30
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2014-05-21 12:17:00 +05:30
										 |  |  | module Network.IRC.Client (runBot) where | 
					
						
							| 
									
										
										
										
											2014-05-04 04:28:08 +05:30
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2014-05-22 01:08:36 +05:30
										 |  |  | import qualified System.Log.Logger as HSL | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2014-05-11 14:01:09 +05:30
										 |  |  | import ClassyPrelude | 
					
						
							| 
									
										
										
										
											2014-05-21 12:17:00 +05:30
										 |  |  | import Control.Concurrent.Lifted (fork, newChan, threadDelay) | 
					
						
							|  |  |  | import Control.Exception.Lifted  (AsyncException (UserInterrupt)) | 
					
						
							| 
									
										
										
										
											2014-05-21 11:20:53 +05:30
										 |  |  | import Network                   (PortID (PortNumber), connectTo, withSocketsDo) | 
					
						
							| 
									
										
										
										
											2014-05-21 12:17:00 +05:30
										 |  |  | import System.IO                 (hSetBuffering, BufferMode(..)) | 
					
						
							| 
									
										
										
										
											2014-05-22 01:08:36 +05:30
										 |  |  | import System.Log.Logger.TH      (deriveLoggers) | 
					
						
							| 
									
										
										
										
											2014-05-04 04:28:08 +05:30
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2014-05-21 12:17:00 +05:30
										 |  |  | import Network.IRC.Bot | 
					
						
							| 
									
										
										
										
											2014-05-04 04:28:08 +05:30
										 |  |  | import Network.IRC.Handlers | 
					
						
							|  |  |  | import Network.IRC.Types | 
					
						
							| 
									
										
										
										
											2014-05-21 12:17:00 +05:30
										 |  |  | import Network.IRC.Util | 
					
						
							| 
									
										
										
										
											2014-05-21 00:06:37 +05:30
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2014-05-22 01:08:36 +05:30
										 |  |  | $(deriveLoggers "HSL" [HSL.DEBUG, HSL.ERROR]) | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2014-05-21 00:38:01 +05:30
										 |  |  | connect :: BotConfig -> IO (Bot, MVar BotStatus, Channel Line, Channel Command, Channel SomeEvent) | 
					
						
							| 
									
										
										
										
											2014-05-11 16:29:22 +05:30
										 |  |  | connect botConfig@BotConfig { .. } = do | 
					
						
							| 
									
										
										
										
											2014-05-22 01:08:36 +05:30
										 |  |  |   debugM "Connecting ..." | 
					
						
							| 
									
										
										
										
											2014-05-11 16:29:22 +05:30
										 |  |  |   socket <- connectToWithRetry | 
					
						
							|  |  |  |   hSetBuffering socket LineBuffering | 
					
						
							| 
									
										
										
										
											2014-05-22 01:08:36 +05:30
										 |  |  |   debugM "Connected" | 
					
						
							| 
									
										
										
										
											2014-05-13 03:02:52 +05:30
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2014-05-22 20:59:02 +05:30
										 |  |  |   lineChan        <- newChannel | 
					
						
							|  |  |  |   commandChan     <- newChannel | 
					
						
							|  |  |  |   eventChan       <- newChannel | 
					
						
							|  |  |  |   mvBotStatus     <- newMVar Connected | 
					
						
							|  |  |  |   msgHandlers     <- loadMsgHandlers (fst eventChan) | 
					
						
							|  |  |  |   msgHandlerInfo' <- foldM (\m (hn, h) -> getHelp h botConfig >>= \hm -> return $ insertMap hn hm m) | 
					
						
							|  |  |  |                        mempty (mapToList msgHandlers) | 
					
						
							|  |  |  |   let botConfig'  = botConfig { msgHandlerInfo = msgHandlerInfo'} | 
					
						
							|  |  |  |   return (Bot botConfig' socket msgHandlers, mvBotStatus, lineChan, commandChan, eventChan) | 
					
						
							| 
									
										
										
										
											2014-05-11 16:29:22 +05:30
										 |  |  |   where | 
					
						
							|  |  |  |     connectToWithRetry = connectTo (unpack server) (PortNumber (fromIntegral port)) | 
					
						
							|  |  |  |                            `catch` (\(e :: SomeException) -> do | 
					
						
							| 
									
										
										
										
											2014-05-22 01:08:36 +05:30
										 |  |  |                                       errorM ("Error while connecting: " ++ show e ++ ". Waiting.") | 
					
						
							| 
									
										
										
										
											2014-05-11 16:29:22 +05:30
										 |  |  |                                       threadDelay (5 * oneSec) | 
					
						
							|  |  |  |                                       connectToWithRetry) | 
					
						
							| 
									
										
										
										
											2014-05-11 14:01:09 +05:30
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2014-05-21 00:06:37 +05:30
										 |  |  |     newChannel = (,) <$> newChan <*> newEmptyMVar | 
					
						
							|  |  |  | 
 | 
					
						
							| 
									
										
										
										
											2014-05-22 20:59:02 +05:30
										 |  |  |     loadMsgHandlers eventChan = | 
					
						
							|  |  |  |       flip (`foldM` mempty) (mapKeys msgHandlerInfo) $ \hMap msgHandlerName -> do | 
					
						
							|  |  |  |         debugM . unpack $ "Loading msg handler: " ++ msgHandlerName | 
					
						
							|  |  |  |         mMsgHandler <- mkMsgHandler botConfig eventChan msgHandlerName | 
					
						
							|  |  |  |         case mMsgHandler of | 
					
						
							|  |  |  |           Nothing         -> do | 
					
						
							|  |  |  |             debugM . unpack $ "No msg handler found with name: " ++ msgHandlerName | 
					
						
							|  |  |  |             return hMap | 
					
						
							|  |  |  |           Just msgHandler -> return $ insertMap msgHandlerName msgHandler hMap | 
					
						
							| 
									
										
										
										
											2014-05-21 00:38:01 +05:30
										 |  |  | 
 | 
					
						
							|  |  |  | disconnect :: (Bot, MVar BotStatus, Channel Line, Channel Command, Channel SomeEvent) -> IO () | 
					
						
							|  |  |  | disconnect (Bot { .. }, mvBotStatus, (_, readLatch), (commandChan, sendLatch), (eventChan, eventLatch)) = do | 
					
						
							| 
									
										
										
										
											2014-05-22 01:08:36 +05:30
										 |  |  |   debugM "Disconnecting ..." | 
					
						
							| 
									
										
										
										
											2014-05-20 00:05:06 +05:30
										 |  |  |   sendCommand commandChan QuitCmd | 
					
						
							| 
									
										
										
										
											2014-05-13 03:02:52 +05:30
										 |  |  |   awaitLatch sendLatch | 
					
						
							|  |  |  |   swapMVar mvBotStatus Disconnected | 
					
						
							|  |  |  |   awaitLatch readLatch | 
					
						
							| 
									
										
										
										
											2014-05-21 00:06:37 +05:30
										 |  |  |   sendEvent eventChan =<< toEvent QuitEvent | 
					
						
							|  |  |  |   awaitLatch eventLatch | 
					
						
							| 
									
										
										
										
											2014-05-13 03:02:52 +05:30
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2014-05-21 00:38:01 +05:30
										 |  |  |   unloadMsgHandlers | 
					
						
							| 
									
										
										
										
											2014-05-22 01:08:36 +05:30
										 |  |  |   handle (\(_ :: SomeException) -> return ()) $ hClose socket | 
					
						
							|  |  |  |   debugM "Disconnected" | 
					
						
							| 
									
										
										
										
											2014-05-21 00:38:01 +05:30
										 |  |  |   where | 
					
						
							|  |  |  |     unloadMsgHandlers = forM_ (mapToList msgHandlers) $ \(msgHandlerName, msgHandler) -> do | 
					
						
							| 
									
										
										
										
											2014-05-22 01:08:36 +05:30
										 |  |  |       debugM . unpack $ "Unloading msg handler: " ++ msgHandlerName | 
					
						
							| 
									
										
										
										
											2014-05-21 00:38:01 +05:30
										 |  |  |       stopMsgHandler msgHandler botConfig | 
					
						
							| 
									
										
										
										
											2014-05-04 04:28:08 +05:30
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2014-05-21 12:17:00 +05:30
										 |  |  | runBot :: BotConfig -> IO () | 
					
						
							|  |  |  | runBot botConfig' = withSocketsDo $ do | 
					
						
							| 
									
										
										
										
											2014-05-11 14:01:09 +05:30
										 |  |  |   hSetBuffering stdout LineBuffering | 
					
						
							| 
									
										
										
										
											2014-05-22 01:08:36 +05:30
										 |  |  |   debugM "Running with config:" | 
					
						
							| 
									
										
										
										
											2014-05-04 16:50:19 +05:30
										 |  |  |   print botConfig | 
					
						
							| 
									
										
										
										
											2014-05-21 12:17:00 +05:30
										 |  |  |   status <- runBot_ | 
					
						
							| 
									
										
										
										
											2014-05-04 07:03:23 +05:30
										 |  |  |   case status of | 
					
						
							| 
									
										
										
										
											2014-05-22 01:08:36 +05:30
										 |  |  |     Disconnected     -> debugM "Restarting .." >> runBot botConfig | 
					
						
							|  |  |  |     Errored          -> debugM "Restarting .." >> runBot botConfig | 
					
						
							| 
									
										
										
										
											2014-05-20 00:05:06 +05:30
										 |  |  |     Interrupted      -> return () | 
					
						
							|  |  |  |     NickNotAvailable -> return () | 
					
						
							|  |  |  |     _                -> error "Unsupported status" | 
					
						
							| 
									
										
										
										
											2014-05-04 07:03:23 +05:30
										 |  |  |   where | 
					
						
							| 
									
										
										
										
											2014-05-22 20:59:02 +05:30
										 |  |  |     botConfig = botConfig' { | 
					
						
							|  |  |  |       msgHandlerInfo = | 
					
						
							|  |  |  |         foldl' (\m name -> insertMap name mempty m) mempty | 
					
						
							|  |  |  |           (hashNub $ mapKeys (msgHandlerInfo botConfig') ++ coreMsgHandlerNames) | 
					
						
							|  |  |  |     } | 
					
						
							| 
									
										
										
										
											2014-05-13 03:02:52 +05:30
										 |  |  | 
 | 
					
						
							|  |  |  |     handleErrors :: SomeException -> IO BotStatus | 
					
						
							| 
									
										
										
										
											2014-05-15 12:02:31 +05:30
										 |  |  |     handleErrors e = case fromException e of | 
					
						
							| 
									
										
										
										
											2014-05-22 01:08:36 +05:30
										 |  |  |         Just UserInterrupt -> debugM "User interrupt"          >> return Interrupted | 
					
						
							|  |  |  |         _                  -> debugM ("Exception! " ++ show e) >> return Errored | 
					
						
							| 
									
										
										
										
											2014-05-13 03:02:52 +05:30
										 |  |  | 
 | 
					
						
							| 
									
										
										
										
											2014-05-21 12:17:00 +05:30
										 |  |  |     runBot_ = bracket (connect botConfig) disconnect $ | 
					
						
							| 
									
										
										
										
											2014-05-21 00:06:37 +05:30
										 |  |  |       \(bot, mvBotStatus, (lineChan, readLatch), (commandChan, sendLatch), eventChannel) -> | 
					
						
							| 
									
										
										
										
											2014-05-13 03:02:52 +05:30
										 |  |  |         handle handleErrors $ do | 
					
						
							| 
									
										
										
										
											2014-05-20 00:05:06 +05:30
										 |  |  |           sendCommand commandChan NickCmd | 
					
						
							|  |  |  |           sendCommand commandChan UserCmd | 
					
						
							| 
									
										
										
										
											2014-05-13 03:02:52 +05:30
										 |  |  | 
 | 
					
						
							|  |  |  |           fork $ sendCommandLoop (commandChan, sendLatch) bot | 
					
						
							|  |  |  |           fork $ readLineLoop mvBotStatus (lineChan, readLatch) bot oneSec | 
					
						
							| 
									
										
										
										
											2014-05-21 00:06:37 +05:30
										 |  |  |           fork $ eventProcessLoop eventChannel lineChan commandChan bot | 
					
						
							| 
									
										
										
										
											2014-05-25 05:30:49 +05:30
										 |  |  |           runIRC bot Connected (messageProcessLoop lineChan commandChan) |