module Lambdabot.Plugin.Novelty.Filter (filterPlugin) where
import Lambdabot.Plugin
import Lambdabot.Util
import Control.Applicative
import Data.Maybe
import System.Directory (findExecutable)
import System.Process
filterPlugin :: Module [(String, FilePath, String)]
filterPlugin :: Module [(String, String, String)]
filterPlugin = Module [(String, String, String)]
forall st. Module st
newModule
{ moduleDefState :: LB [(String, String, String)]
moduleDefState = [Maybe (String, String, String)] -> [(String, String, String)]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe (String, String, String)] -> [(String, String, String)])
-> LB [Maybe (String, String, String)]
-> LB [(String, String, String)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [LB (Maybe (String, String, String))]
-> LB [Maybe (String, String, String)]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence
[ do
Maybe String
mbPath <- IO (Maybe String) -> LB (Maybe String)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (String -> IO (Maybe String)
findExecutable String
name)
Maybe (String, String, String)
-> LB (Maybe (String, String, String))
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe (String, String, String)
-> LB (Maybe (String, String, String)))
-> Maybe (String, String, String)
-> LB (Maybe (String, String, String))
forall a b. (a -> b) -> a -> b
$! do
String
path <- Maybe String
mbPath
(String, String, String) -> Maybe (String, String, String)
forall a. a -> Maybe a
Just (String
name, String
path, String
descr)
| (String
name, String
descr) <- [(String, String)]
filters
]
, moduleCmds :: ModuleT
[(String, String, String)]
LB
[Command (ModuleT [(String, String, String)] LB)]
moduleCmds = do
[(String, String, String)]
activeFilters <- ModuleT [(String, String, String)] LB [(String, String, String)]
forall (m :: * -> *). MonadLBState m => m (LBState m)
readMS
[Command (ModuleT [(String, String, String)] LB)]
-> ModuleT
[(String, String, String)]
LB
[Command (ModuleT [(String, String, String)] LB)]
forall (m :: * -> *) a. Monad m => a -> m a
return
[ (String -> Command Identity
command String
name)
{ help :: Cmd (ModuleT [(String, String, String)] LB) ()
help = String -> Cmd (ModuleT [(String, String, String)] LB) ()
forall (m :: * -> *). Monad m => String -> Cmd m ()
say String
descr
, process :: String -> Cmd (ModuleT [(String, String, String)] LB) ()
process = \String
s -> do
case String -> [String]
words String
s of
[] -> String -> Cmd (ModuleT [(String, String, String)] LB) ()
forall (m :: * -> *). Monad m => String -> Cmd m ()
say (String
"usage: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
name String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" <phrase>")
[String]
t -> IO String -> Cmd (ModuleT [(String, String, String)] LB) ()
forall (m :: * -> *). MonadIO m => IO String -> Cmd m ()
ios80 (String -> String -> IO String
runFilter String
path ([String] -> String
unwords [String]
t))
}
| (String
name, String
path, String
descr) <- [(String, String, String)]
activeFilters
]
}
filters :: [(String, String)]
filters :: [(String, String)]
filters =
[ (String
"austro", String
"austro <phrase>. Talk like Ahhhnold")
, (String
"b1ff", String
"b1ff <phrase>. B1ff of usenet yore")
, (String
"brooklyn", String
"brooklyn <phrase>. Yo")
, (String
"chef", String
"chef <phrase>. Bork bork bork")
, (String
"cockney", String
"cockney <phrase>. Londoner accent")
, (String
"drawl", String
"drawl <phrase>. Southern drawl")
, (String
"dubya", String
"dubya <phrase>. Presidential filter")
, (String
"fudd", String
"fudd <phrase>. Fudd, Elmer")
, (String
"funetak", String
"funetak <phrase>. Southern drawl")
, (String
"jethro", String
"jethro <phrase>. Now listen to a story 'bout a man named Jed...")
, (String
"jive", String
"jive <phrase>. Slap ma fro")
, (String
"kraut", String
"kraut <phrase>. German accent")
, (String
"pansy", String
"pansy <phrase>. Effeminate male")
, (String
"pirate", String
"pirate <phrase>. Talk like a pirate")
, (String
"postmodern", String
"postmodern <phrase>. Feminazi")
, (String
"redneck", String
"redneck <phrase>. Deep south")
, (String
"valspeak", String
"valley <phrase>. Like, ya know?")
, (String
"warez", String
"warez <phrase>. H4x0r")
]
runFilter :: String -> String -> IO String
runFilter :: String -> String -> IO String
runFilter String
f String
s = do
String
out <- String -> [String] -> String -> IO String
readProcess String
f [] String
s
String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> IO String) -> String -> IO String
forall a b. (a -> b) -> a -> b
$ String -> String
result String
out
where result :: String -> String
result [] = String
"Couldn't run the filter."
result String
xs = [String] -> String
unlines ([String] -> String) -> (String -> [String]) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (String -> Bool) -> String -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> String -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==Char
' ')) ([String] -> [String])
-> (String -> [String]) -> String -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
lines (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
xs