module Lambdabot.Util (
strip,
dropFromEnd,
splitFirstWord,
limitStr,
listToStr,
showClean,
expandTab,
arePrefixesWithSpaceOf,
arePrefixesOf,
io,
random,
randomFailureMsg,
randomSuccessMsg
) where
import Control.Monad.Trans
import Data.Char
import Data.List
import Data.Random
import Lambdabot.Config
import Lambdabot.Config.Core
splitFirstWord :: String
-> (String, String)
splitFirstWord xs = (w, dropWhile isSpace xs')
where (w, xs') = break isSpace xs
limitStr :: Int -> String -> String
limitStr n s = let (b, t) = splitAt n s in
if null t then b else take (n-3) b ++ "..."
listToStr :: String -> [String] -> String
listToStr _ [] = []
listToStr conj (item:items) =
let listToStr' [] = []
listToStr' [y] = concat [" ", conj, " ", y]
listToStr' (y:ys) = concat [", ", y, listToStr' ys]
in item ++ listToStr' items
random :: MonadIO m => [a] -> m a
random = io . sample . randomElement
strip :: (a -> Bool) -> [a] -> [a]
strip p = let f = reverse . dropWhile p in f . f
dropFromEnd :: (a -> Bool) -> [a] -> [a]
dropFromEnd p = reverse . dropWhile p . reverse
showClean :: (Show a) => [a] -> String
showClean = intercalate " " . map (init . tail . show)
expandTab :: Int -> String -> String
expandTab w = go 0
where
go _ [] = []
go i ('\t':xs) = replicate (w - i `mod` w) ' ' ++ go 0 xs
go i (x:xs) = x : go (i+1) xs
io :: MonadIO m => IO a -> m a
io = liftIO
{-# INLINE io #-}
arePrefixesWithSpaceOf :: [String] -> String -> Bool
arePrefixesWithSpaceOf = arePrefixesOf . map (++ " ")
arePrefixesOf :: [String] -> String -> Bool
arePrefixesOf = flip (any . flip isPrefixOf)
insult :: [String]
insult =
["Just what do you think you're doing Dave?",
"It can only be attributed to human error.",
"That's something I cannot allow to happen.",
"My mind is going. I can feel it.",
"Sorry about this, I know it's a bit silly.",
"Take a stress pill and think things over.",
"This mission is too important for me to allow you to jeopardize it.",
"I feel much better now.",
"Wrong! You cheating scum!",
"And you call yourself a Rocket Scientist!",
"And you call yourself a Rocket Surgeon!",
"Where did you learn to type?",
"Are you on drugs?",
"My pet ferret can type better than you!",
"You type like i drive.",
"Do you think like you type?",
"Your mind just hasn't been the same since the electro-shock, has it?",
"I don't think I can be your friend on Facebook anymore.",
"Maybe if you used more than just two fingers...",
"BOB says: You seem to have forgotten your passwd, enter another!",
"stty: unknown mode: doofus",
"I can't hear you -- I'm using the scrambler.",
"The more you drive -- the dumber you get.",
"Listen, broccoli brains, I don't have time to listen to this trash.",
"I've seen penguins that can type better than that.",
"Have you considered trying to match wits with a rutabaga?",
"You speak an infinite deal of nothing.",
"Are you typing with your feet?",
"Abort, Retry, Panic?",
"You untyped fool!",
"My brain just exploded"
]
apology :: [String]
apology =
["I am sorry.","Sorry.",
"Maybe you made a typo?",
"Just try something else.",
"There are some things that I just don't know.",
"Whoa.",
":(",":(",
"","",""
]
randomFailureMsg :: (MonadIO m, MonadConfig m) => m String
randomFailureMsg = do
useInsults <- getConfig enableInsults
random (if useInsults then insult ++ apology else apology)
confirmation :: [String]
confirmation =
["Done.","Done.",
"Okay.",
"I will remember.",
"Good to know.",
"It is stored.",
"I will never forget.",
"It is forever etched in my memory.",
"Nice!"
]
randomSuccessMsg :: MonadIO m => m String
randomSuccessMsg = random confirmation