module Web.Codepad where
import Control.Applicative ((<$>))
import Control.Monad.Trans (MonadIO,liftIO)
import Data.Char (isSpace)
import Data.Monoid (mconcat)
import qualified Network.Curl as C
import Network.URI (escapeURIString)
import Text.HTML.TagSoup (Tag(..),parseTags)
type URL = String
type Code = String
type PasteId = String
type PasteOutput = String
type LangName = String
codepadUrl :: URL
codepadUrl = "http://codepad.org/"
codepadLangsURL :: URL
codepadLangsURL = "http://hpaste.codepad.org/"
pasteURL :: PasteId
-> URL
pasteURL pid = codepadUrl ++ pid
pasteAndRun :: MonadIO m
=> Code
-> LangName
-> Bool
-> m (Maybe (PasteId,PasteOutput))
pasteAndRun code lang private = do
result <- pasteCode code lang True private
case result of
Nothing -> return Nothing
Just pid -> do
out <- pasteOutput pid
case out of
Nothing -> return Nothing
Just output -> return $ Just (pid,output)
pasteCode :: MonadIO m
=> Code
-> LangName
-> Bool
-> Bool
-> m (Maybe PasteId)
pasteCode code lang run private = do
r <- liftIO $ C.withCurlDo $ getResponse codepadUrl [C.CurlPostFields assocs]
if C.respStatus r == 302
then return $ getId <$> lookup "Location" (C.respHeaders r)
else return Nothing
where getResponse :: C.URLString -> [C.CurlOption]
-> IO (C.CurlResponse_ [(String,String)] String)
getResponse = C.curlGetResponse_
getId = reverse . takeWhile (/='/') . reverse
assocs = ["code=" ++ encode code
,"lang=" ++ encode lang
,"run=" ++ show run
,"private=" ++ show private
,"submit=Submit"]
encode = escapeURIString (const False)
pasteOutput :: MonadIO m
=> PasteId
-> m (Maybe PasteOutput)
pasteOutput pid = do
(code,t) <- liftIO $ C.withCurlDo $ C.curlGetString_ (pasteURL pid) []
case code of
C.CurlOK -> return $ parseOutput t
_ -> return Nothing
supportedLangs :: MonadIO m => m (Maybe [LangName])
supportedLangs = do
(code,t) <- liftIO $ C.withCurlDo $ C.curlGetString_ codepadLangsURL []
case code of
C.CurlOK -> return $ Just $ parseLangs t
_ -> return Nothing
parseOutput :: String
-> Maybe PasteOutput
parseOutput = toHeading . parseTags where
toHeading (TagOpen "span" [("class","heading")]
:TagText "Output:":xs) = skipLines xs
toHeading (_:xs) = toHeading xs
toHeading [] = Nothing
skipLines (TagClose "pre":xs) = toPre xs
skipLines (_:xs) = skipLines xs
skipLines [] = Nothing
toPre (TagOpen "pre" _:xs) = cleanUp <$> mconcat (collect xs)
toPre (_:xs) = toPre xs
toPre [] = Nothing
collect (TagText t:xs) = Just t : collect xs
collect (TagClose "pre":_) = []
collect (_:xs) = collect xs
collect [] = []
cleanUp s = dropWhile isSpace $ take (length s1) s
parseLangs :: String
-> [LangName]
parseLangs = toSelect . parseTags where
toSelect (TagOpen "select" ((_,"lang"):_):xs) = options xs
toSelect (_:xs) = toSelect xs
toSelect [] = []
options (TagOpen "option" _:TagText lang:xs) = lang : options xs
options (_:xs) = options xs
options [] = []