aboutsummaryrefslogtreecommitdiffstats
path: root/src/Reaktor/Plugins
diff options
context:
space:
mode:
Diffstat (limited to 'src/Reaktor/Plugins')
-rw-r--r--src/Reaktor/Plugins/Mention.hs6
-rw-r--r--src/Reaktor/Plugins/Register.hs22
-rw-r--r--src/Reaktor/Plugins/System.hs42
-rw-r--r--src/Reaktor/Plugins/System/Internal.hs9
4 files changed, 41 insertions, 38 deletions
diff --git a/src/Reaktor/Plugins/Mention.hs b/src/Reaktor/Plugins/Mention.hs
index 379bd38..b3cdbb8 100644
--- a/src/Reaktor/Plugins/Mention.hs
+++ b/src/Reaktor/Plugins/Mention.hs
@@ -4,8 +4,8 @@
module Reaktor.Plugins.Mention (new) where
import Prelude.Extended
-import qualified Data.ByteString.Char8.Extended as BS
import qualified Data.Char
+import qualified Data.Text as T
import Reaktor
@@ -19,5 +19,5 @@ new Actions{..} = do
_ -> return ()
where
isMention nick text =
- not (BS.isPrefixOf (nick <> ":") text) &&
- any (==nick) (BS.splitWith (not . Data.Char.isAlphaNum) text)
+ not (T.isPrefixOf (nick <> ":") text) &&
+ any (==nick) (T.split (not . Data.Char.isAlphaNum) text)
diff --git a/src/Reaktor/Plugins/Register.hs b/src/Reaktor/Plugins/Register.hs
index 0809006..ff420f0 100644
--- a/src/Reaktor/Plugins/Register.hs
+++ b/src/Reaktor/Plugins/Register.hs
@@ -7,15 +7,15 @@ module Reaktor.Plugins.Register where
import Blessings
import Prelude.Extended
import Data.Aeson
-import Data.ByteString.Char8.Extended (ByteString)
-import qualified Data.ByteString.Char8.Extended as BS
+import qualified Data.Text as T
+import qualified Data.Text.IO as T
import qualified Reaktor.Nick as Nick
import Reaktor
import System.Environment (lookupEnv)
data ConfigNickServ = ConfigNickServ
{ cnsPassFile :: FilePath
- , cnsPrefix :: ByteString
+ , cnsPrefix :: Text
}
instance FromJSON ConfigNickServ where
parseJSON = \case
@@ -26,10 +26,10 @@ instance FromJSON ConfigNickServ where
_ -> undefined
data Config = Config
- { cNick :: Maybe ByteString
- , cUser :: Maybe ByteString
- , cReal :: ByteString
- , cChannels :: [ByteString]
+ { cNick :: Maybe Text
+ , cUser :: Maybe Text
+ , cReal :: Text
+ , cChannels :: [Text]
, cNickServ :: Maybe ConfigNickServ
}
instance Default Config where
@@ -54,18 +54,18 @@ new Config{..} Actions{..} = do
regain nick pass = do
aSend (privmsg "NickServ" ["REGAIN", nick, pass])
- channelsArg = BS.intercalate "," cChannels
+ channelsArg = T.intercalate "," cChannels
-- TODO make this similar to privmsg (i.e. don't aSend)
join = do
-- TODO JOIN only if not already joined
-- i.e. not during subsequent nick changes
- unless (BS.null channelsArg) $
+ unless (T.null channelsArg) $
aSend (Message Nothing "JOIN" [channelsArg])
start = do
nick <- maybe aGetNick pure cNick
user <-
- maybe (maybe nick BS.pack <$> lookupEnv "LOGNAME") pure cUser
+ maybe (maybe nick T.pack <$> lookupEnv "LOGNAME") pure cUser
aSetNick nick
aSend (Message Nothing "NICK" [nick])
aSend (Message Nothing "USER" [user, "*", "0", cReal])
@@ -103,7 +103,7 @@ new Config{..} Actions{..} = do
else do
-- TODO do not fail, but disable NicServ
- [pass] <- BS.lines <$> BS.readFile cnsPassFile
+ [pass] <- T.lines <$> T.readFile cnsPassFile
pure $ \case
Start -> start
Message (Just _self) "NICK" (newnick:[]) -> onNick newnick
diff --git a/src/Reaktor/Plugins/System.hs b/src/Reaktor/Plugins/System.hs
index 8154423..f31f640 100644
--- a/src/Reaktor/Plugins/System.hs
+++ b/src/Reaktor/Plugins/System.hs
@@ -9,11 +9,10 @@ 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.Text.Extended as T
+import qualified Data.Text.IO as T
import qualified Data.Vector as V
import Prelude.Extended
import Reaktor
@@ -42,7 +41,7 @@ new config@Config{..} actions@Actions{..} = do
_ -> pure ()
-run1 :: Config -> Actions -> Hook -> ByteString -> ByteString -> ByteString -> IO ()
+run1 :: Config -> Actions -> Hook -> Text -> Text -> Text -> IO ()
run1 Config{..} Actions{..} Hook{..} prefix msgtarget text = do
nick <- aGetNick
@@ -56,16 +55,16 @@ run1 Config{..} Actions{..} Hook{..} prefix msgtarget text = do
Just pat ->
let
result = RE.scan patternRE text
- patternRE = RE.compile pat []
+ patternRE = RE.compile pat [RE.utf8]
in
if null result
then Nothing
else Just ""
Query ->
if
- | BS.isPrefixOf (nick <> ":") text ->
+ | T.isPrefixOf (nick <> ":") text ->
Just (nick <> ":")
- | BS.isPrefixOf "*:" text ->
+ | T.isPrefixOf "*:" text ->
Just "*:"
| isQuery ->
Just ""
@@ -73,7 +72,8 @@ run1 Config{..} Actions{..} Hook{..} prefix msgtarget text = do
Nothing
audience = if isQuery then from else msgtarget
- from = BS.takeWhile (/='!') prefix
+
+ from = T.takeWhile (/='!') prefix
-- TODO check if msgtarget is one of our channels?
-- what if our nick has changed?
@@ -82,14 +82,14 @@ run1 Config{..} Actions{..} Hook{..} prefix msgtarget text = do
case isActivated of
Just trigger -> do
let
- cmdline = BS.dropWhile (==' ') $ BS.drop (BS.length trigger) text
+ cmdline = T.dropWhile (==' ') $ T.drop (T.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 []
+ patternRE = RE.compile pat [RE.utf8]
captures =
V.fromList $
@@ -102,7 +102,7 @@ run1 Config{..} Actions{..} Hook{..} prefix msgtarget text = do
name =
case hCommand of
Capture i -> fromMaybe "<unnamed>" (capture i)
- CaptureOr Command{..} -> BS.pack $ takeBaseName $ commandPath
+ CaptureOr Command{..} -> T.pack $ takeBaseName $ commandPath
command =
case hCommand of
@@ -110,7 +110,7 @@ run1 Config{..} Actions{..} Hook{..} prefix msgtarget text = do
CaptureOr c -> Just c
args =
- map (maybe "" BS.unpack)
+ map (maybe "" T.unpack)
$ L.dropWhileEnd isNothing
-- $ map getArgument hArguments
$ flip map hArguments
@@ -124,7 +124,7 @@ run1 Config{..} Actions{..} Hook{..} prefix msgtarget text = do
let
onExit code = do
- let s = BS.show code
+ let s = T.show code
(sig, col) =
if code == ExitSuccess
then (SGR [38,5,235] "* ", SGR [38,5,107])
@@ -133,8 +133,8 @@ run1 Config{..} Actions{..} Hook{..} prefix msgtarget text = do
onExcept :: SomeException -> IO ()
onExcept e = do
- let s0 = BS.show e
- s = BL.toStrict $ BS.replace (BS.pack commandPath) name s0
+ let s0 = T.show e
+ s = T.replace (T.pack commandPath) name s0
aLog $ SGR [38,5,235] "! "
<> SGR [31,1] (Plain $ name <> ": " <> s0)
aSend (privmsg audience (resultPrefix <> [s]))
@@ -144,8 +144,8 @@ run1 Config{..} Actions{..} Hook{..} prefix msgtarget text = do
onOutLine s = aSend (privmsg audience [s])
extraEnv =
- [ ("_prefix", BS.unpack prefix)
- , ("_from", BS.unpack from)
+ [ ("_prefix", T.unpack prefix)
+ , ("_from", T.unpack from)
]
env =
@@ -171,8 +171,8 @@ fork :: FilePath
-> Maybe FilePath
-> Maybe [(String, String)]
-> String
- -> (ByteString -> IO ())
- -> (ByteString -> IO ())
+ -> (Text -> IO ())
+ -> (Text -> IO ())
-> (ExitCode -> IO ())
-> IO ()
fork path args cwd env input onOutLine onErrLine onExit = do
@@ -196,7 +196,7 @@ fork path args cwd env input onOutLine onErrLine onExit = do
waitForProcess ph >>= onExit
-hWithLines :: Handle -> (ByteString -> IO ()) -> IO ()
+hWithLines :: Handle -> (Text -> IO ()) -> IO ()
hWithLines h f = do
hSetBuffering h LineBuffering
go `finally` hClose h
@@ -204,4 +204,4 @@ hWithLines h f = do
go =
hIsEOF h >>= \case
True -> return ()
- False -> BS.hGetLine h >>= f >> go
+ False -> T.hGetLine h >>= f >> go
diff --git a/src/Reaktor/Plugins/System/Internal.hs b/src/Reaktor/Plugins/System/Internal.hs
index ac707ae..9b1b8de 100644
--- a/src/Reaktor/Plugins/System/Internal.hs
+++ b/src/Reaktor/Plugins/System/Internal.hs
@@ -18,6 +18,7 @@ instance FromJSON a => FromJSON (CaptureOr a) where
-- TODO query means via direct privmsg and <nick>:
data Activate = Always | Match | Query
+ deriving Show
instance FromJSON Activate where
parseJSON = \case
@@ -28,8 +29,9 @@ instance FromJSON Activate where
data Config = Config
{ cWorkDir :: Maybe FilePath
- , cHooks :: HashMap ByteString [Hook]
+ , cHooks :: HashMap Text [Hook]
}
+ deriving Show
instance Default Config where
def = Config Nothing mempty
@@ -46,10 +48,11 @@ data Hook = Hook
{ hActivate :: Activate
, hPattern :: Maybe ByteString
, hCommand :: CaptureOr Command
- , hArguments :: [CaptureOr ByteString]
+ , hArguments :: [CaptureOr Text]
, hWorkDir :: Maybe FilePath
- , hCommands :: HashMap ByteString Command
+ , hCommands :: HashMap Text Command
}
+ deriving Show
instance FromJSON Hook where
parseJSON = \case