-- | GNU Talk Filters
-- needs: http://www.hyperrealm.com/main.php?s=talkfilters
-- Edward Kmett 2006

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

-- State consists of a map from filter name to executable path

filterPlugin :: Module [(String, FilePath, String)]
filterPlugin :: Module [(String, String, String)]
filterPlugin = forall st. Module st
newModule
    { moduleDefState :: LB [(String, String, String)]
moduleDefState = forall a. [Maybe a] -> [a]
catMaybes forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence
        [ do
            Maybe String
mbPath <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
io (String -> IO (Maybe String)
findExecutable String
name)
            forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$! do
                String
path <- Maybe String
mbPath
                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 <- forall (m :: * -> *). MonadLBState m => m (LBState m)
readMS
        forall (m :: * -> *) a. Monad m => a -> m a
return
            [ (String -> Command Identity
command String
name)
                { help :: Cmd (ModuleT [(String, String, String)] LB) ()
help = 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
                            [] -> forall (m :: * -> *). Monad m => String -> Cmd m ()
say (String
"usage: " forall a. [a] -> [a] -> [a]
++ String
name forall a. [a] -> [a] -> [a]
++ String
" <phrase>")
                            [String]
t -> 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
    forall (m :: * -> *) a. Monad m => a -> m a
return 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 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (forall a. Eq a => a -> a -> Bool
==Char
' ')) forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
lines forall a b. (a -> b) -> a -> b
$ String
xs