{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE MultiWayIf #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RecordWildCards #-} module Reaktor.Plugins.System (new) where import Blessings import Control.Applicative import Control.Concurrent (forkIO) import Control.Exception import qualified Data.ByteString.Char8.Extended as BS import qualified Data.ByteString.Lazy as BL import qualified Data.ByteString.Search as BS import qualified Data.HashMap.Lazy as M import qualified Data.List as L import qualified Data.Vector as V import Prelude.Extended import Reaktor import Reaktor.Plugins.System.Internal import System.Environment (getEnvironment) import System.Exit import System.FilePath.Posix (takeBaseName) import System.IO (BufferMode(LineBuffering),hSetBuffering) import System.IO (Handle,hClose,hPutStr,hIsEOF) import System.Process import qualified Text.Regex.PCRE.Heavy as RE import qualified Text.Regex.PCRE.Light as RE new :: Config -> Actions -> IO (Message -> IO ()) new config@Config{..} actions@Actions{..} = do pure $ \case Message (Just prefix) cmd (msgtarget:text:[]) | elem cmd ["PRIVMSG", "JOIN"] -> do let hooks = maybe [] id (M.lookup cmd cHooks) mapM_ (\h -> run1 config actions h prefix msgtarget text) hooks Message (Just prefix) "JOIN" (channel:[]) -> do let hooks = maybe [] id (M.lookup "JOIN" cHooks) mapM_ (\h -> run1 config actions h prefix channel "") hooks _ -> pure () run1 :: Config -> Actions -> Hook -> ByteString -> ByteString -> ByteString -> IO () run1 Config{..} Actions{..} Hook{..} prefix msgtarget text = do nick <- aGetNick let isActivated = case hActivate of Always -> Just "" Match -> case hPattern of Nothing -> Nothing Just pat -> let result = RE.scan patternRE text patternRE = RE.compile pat [] in if null result then Nothing else Just "" Query -> if | BS.isPrefixOf (nick <> ":") text -> Just (nick <> ":") | BS.isPrefixOf "*:" text -> Just "*:" | isQuery -> Just "" | otherwise -> Nothing audience = if isQuery then from else msgtarget from = BS.takeWhile (/='!') prefix -- TODO check if msgtarget is one of our channels? -- what if our nick has changed? isQuery = msgtarget == nick case isActivated of Just trigger -> do let cmdline = BS.dropWhile (==' ') $ BS.drop (BS.length trigger) text resultPrefix = if isQuery then [] else [from <> ":"] parseCommandLine' pat s = if null result then [] else snd (head result) where result = RE.scan patternRE s patternRE = RE.compile pat [] captures = V.fromList $ case hPattern of Nothing -> [] -- TODO everything? Just pat -> parseCommandLine' pat cmdline capture i = captures V.!? (i - 1) name = case hCommand of Capture i -> fromMaybe "" (capture i) CaptureOr Command{..} -> BS.pack $ takeBaseName $ commandPath command = case hCommand of Capture i -> (`M.lookup` hCommands) =<< capture i CaptureOr c -> Just c args = map (maybe "" BS.unpack) $ L.dropWhileEnd isNothing -- $ map getArgument hArguments $ flip map hArguments $ \case Capture i -> capture i CaptureOr s -> Just s case command of Just Command{..} -> do baseEnv <- getEnvironment let onExit code = do let s = BS.show code (sig, col) = if code == ExitSuccess then (SGR [38,5,235] "* ", SGR [38,5,107]) else (SGR [38,5,235] "! ", SGR [31,1]) aLog $ sig <> col (Plain $ name <> ": " <> s) onExcept :: SomeException -> IO () onExcept e = do let s0 = BS.show e s = BL.toStrict $ BS.replace (BS.pack commandPath) name s0 aLog $ SGR [38,5,235] "! " <> SGR [31,1] (Plain $ name <> ": " <> s0) aSend (privmsg audience (resultPrefix <> [s])) -- TODO use differenct colors onErrLine s = aSend (privmsg audience [s]) onOutLine s = aSend (privmsg audience [s]) extraEnv = [ ("_prefix", BS.unpack prefix) , ("_from", BS.unpack from) ] env = M.toList $ mconcat [ M.fromList extraEnv , maybe mempty id commandEnv , M.fromList baseEnv ] cwd = commandWorkDir <|> hWorkDir <|> cWorkDir fork commandPath args cwd (Just env) "" onOutLine onErrLine onExit `catch` onExcept Nothing -> do let s = name <> ": command not found" aSend (privmsg audience (resultPrefix <> [s])) Nothing -> return () fork :: FilePath -> [String] -> Maybe FilePath -> Maybe [(String, String)] -> String -> (ByteString -> IO ()) -> (ByteString -> IO ()) -> (ExitCode -> IO ()) -> IO () fork path args cwd env input onOutLine onErrLine onExit = do let p = (proc path args) { cwd = cwd , env = env , std_in = CreatePipe , std_out = CreatePipe , std_err = CreatePipe , close_fds = True , create_group = True , new_session = True } withCreateProcess p $ \(Just inh) (Just outh) (Just errh) ph -> do mapM_ forkIO [ hPutStr inh input `finally` hClose inh, hWithLines outh onOutLine, hWithLines errh onErrLine ] waitForProcess ph >>= onExit hWithLines :: Handle -> (ByteString -> IO ()) -> IO () hWithLines h f = do hSetBuffering h LineBuffering go `finally` hClose h where go = hIsEOF h >>= \case True -> return () False -> BS.hGetLine h >>= f >> go