{-# LANGUAGE PatternGuards #-}
module Lambdabot.Plugin.Reference.Url (urlPlugin) where
import Lambdabot.Plugin
import Lambdabot.Util.Browser
import Control.Monad
import Control.Monad.Trans
import Data.List
import Data.Maybe
import Network.Browser
import Network.HTTP
import Text.Regex.TDFA
urlPlugin :: Module Bool
urlPlugin = newModule
{ moduleCmds = return
[ (command "url-title")
{ help = say "url-title <url>. Fetch the page title."
, process =
maybe (say "Url not valid.") (mbSay <=< fetchTitle)
. containsUrl
}
, (command "tiny-url")
{ help = say "tiny-url <url>. Shorten <url>."
, process =
maybe (say "Url not valid.") (mbSay <=< fetchTiny)
. containsUrl
}
, (command "url-on")
{ privileged = True
, help = say "url-on: enable automatic URL summaries"
, process = const $ do
writeMS True
say "Url enabled"
}
, (command "url-off")
{ privileged = True
, help = say "url-off: disable automatic URL summaries"
, process = const $ do
writeMS False
say "Url disabled"
}
]
, moduleDefState = return True
, moduleSerialize = Just stdSerial
, contextual = \text -> do
alive <- lift readMS
if alive && (not $ areSubstringsOf ignoredStrings text)
then case containsUrl text of
Nothing -> return ()
Just url
| length url > 60 -> do
title <- fetchTitle url
tiny <- fetchTiny url
say (intercalate ", " (catMaybes [title, tiny]))
| otherwise -> mbSay =<< fetchTitle url
else return ()
}
mbSay :: Maybe String -> Cmd (ModuleT Bool LB) ()
mbSay = maybe (return ()) say
urlTitlePrompt :: String
urlTitlePrompt = "Title: "
fetchTitle :: MonadLB m => String -> m (Maybe String)
fetchTitle url = fmap (fmap (urlTitlePrompt ++)) (browseLB (urlPageTitle url))
tinyurl :: String
tinyurl = "http://tinyurl.com/api-create.php?url="
fetchTiny :: MonadLB m => String -> m (Maybe String)
fetchTiny url = do
(_, response) <- browseLB (request (getRequest (tinyurl ++ url)))
case rspCode response of
(2,0,0) -> return $ findTiny (rspBody response)
_ -> return Nothing
findTiny :: String -> Maybe String
findTiny text = do
mr <- matchM begreg text
let kind = mrMatch mr
rest = mrAfter mr
url = takeWhile (/=' ') rest
return $ stripSuffixes ignoredUrlSuffixes $ kind ++ url
where
begreg :: Regex
begreg = makeRegexOpts opts defaultExecOpt "http://tinyurl.com/"
opts = defaultCompOpt {caseSensitive = False}
ignoredStrings :: [String]
ignoredStrings =
["paste",
"cpp.sourcforge.net",
"HaskellIrcPastePage",
"title of that page",
urlTitlePrompt]
ignoredUrlSuffixes :: [String]
ignoredUrlSuffixes = [".", ",", ";", ")", "\"", "\1", "\n"]
containsUrl :: String -> Maybe String
containsUrl text = do
mr <- matchM begreg text
let kind = mrMatch mr
rest = mrAfter mr
url = takeWhile (`notElem` " \n\t\v") rest
return $ stripSuffixes ignoredUrlSuffixes $ kind ++ url
where
begreg = makeRegexOpts opts defaultExecOpt "https?://"
opts = defaultCompOpt { caseSensitive = False }
stripSuffixes :: [String] -> String -> String
stripSuffixes [] str = str
stripSuffixes (s:ss) str
| isSuffixOf s str = take (length str - length s) $ str
| otherwise = stripSuffixes ss str
areSubstringsOf :: [String] -> String -> Bool
areSubstringsOf = flip (any . flip isSubstringOf)
where
isSubstringOf s str = any (isPrefixOf s) (tails str)