{-# LANGUAGE PatternGuards #-}
module Lambdabot.Plugin.Reference.Spell (spellPlugin) where
import Lambdabot.Config.Reference
import Lambdabot.Plugin
import Lambdabot.Util
import Control.Monad.Trans
import Data.Char
import Data.List.Split
import Data.Maybe
import System.Process
import Text.Regex.TDFA
type Spell = ModuleT Bool LB
spellPlugin :: Module Bool
spellPlugin = newModule
{ moduleCmds = return
[ (command "spell")
{ help = say helpStr
, process = doSpell
}
, (command "spell-all")
{ help = say helpStr
, process = spellAll
}
, (command "nazi-on")
{ privileged = True
, help = say helpStr
, process = const (nazi True)
}
, (command "nazi-off")
{ privileged = True
, help = say helpStr
, process = const (nazi False)
}
]
, moduleDefState = return False
, contextual = \txt -> do
alive <- readMS
binary <- getConfig aspellBinary
if alive then io (spellingNazi binary txt) >>= mapM_ say
else return ()
}
helpStr :: String
helpStr = "spell <word>. Show spelling of word"
doSpell :: [Char] -> Cmd Spell ()
doSpell [] = say "No word to spell."
doSpell s = do
binary <- getConfig aspellBinary
(say . showClean . take 5) =<< (io (spell binary s))
spellAll :: [Char] -> Cmd Spell ()
spellAll [] = say "No phrase to spell."
spellAll s = do
binary <- getConfig aspellBinary
liftIO (spellingNazi binary s) >>= mapM_ say
nazi :: Bool -> Cmd (ModuleT Bool LB) ()
nazi True = lift on >> say "Spelling nazi engaged."
nazi False = lift off >> say "Spelling nazi disengaged."
on :: Spell ()
on = writeMS True
off :: Spell ()
off = writeMS False
args :: [String]
args = ["pipe"]
spellingNazi :: String -> String -> IO [String]
spellingNazi binary lin = fmap (take 1 . concat) (mapM correct (words lin))
where correct word = do
var <- take 5 `fmap` spell binary word
return $ if null var || any (equating' (map toLower) word) var
then []
else ["Did you mean " ++ listToStr "or" var ++ "?"]
equating' f x y = f x == f y
spell :: String -> String -> IO [String]
spell binary word = spellWithArgs binary word []
spellWithArgs :: String -> String -> [String] -> IO [String]
spellWithArgs binary word ex = do
(_,out,err) <- readProcessWithExitCode binary (args++ex) word
let o = fromMaybe [word] ((clean_ . lines) out)
e = fromMaybe e ((clean_ . lines) err)
return $ case () of {_
| null o && null e -> []
| null o -> e
| otherwise -> o
}
clean_ :: [String] -> Maybe [String]
clean_ (('@':'(':'#':')':_):rest) = clean' rest
clean_ s = clean' s
clean' :: [String] -> Maybe [String]
clean' (('*':_):_) = Nothing
clean' (('#':_):_) = Just []
clean' (('&':rest):_) = Just $ splitOn ", " (clean'' rest)
clean' _ = Just []
clean'' :: String -> String
clean'' s = maybe s mrAfter (s =~~ pat)
where pat = "[^:]*: "