| Copyright | (c) The Linklaterteers |
|---|---|
| License | BSD-style |
| Stability | experimental |
| Portability | GHC |
| Safe Haskell | None |
| Language | Haskell2010 |
Network.Linklater
Description
Features:
- Uses
Texteverywhere so you can send your slash commands crazy Unicode characters all day long. - Lovely documentation.
- Battle-tested.
Here's a /jpgto bot! If you run this program and then tell Slack
about your server (incoming hook and custom slash command) and then
type /jpgto diplomatico in one of your channels, you'll get the
image from http://diplomatico.jpg.to. How, you say? Screen scraping.
urlParser :: Parser B.ByteString
urlParser = p
where
p = garbage *> url
garbage = string "src="" | (P.take 1 *> garbage)
url = takeTill (== _quotedbl)
urlFor :: Text -> IO Text
urlFor search = do
r <- get (T.unpack $ F.format "http://{}.jpg.to/" [search])
(return . handle . parse urlParser . strictly) (r ^. responseBody)
where
strictly = B.concat . L.toChunks
handle (Fail i ctxs s) = error (show (i, ctxs, s))
handle (Partial f) = handle (f "")
handle (Done _ r) = toText r
jpgto :: Maybe Command -> Application
jpgto (Just (Command (User user) channel text)) req respond = do
url <- urlFor (maybe "spolsky" id text)
say (Message channel (response url) (EmojiIcon "gift")) config
(respond . responseLBS status200 headers) ""
where
response url = F.format "@{} {}" (user, url)
config = Config token "trello.slack.com"
headers = [(Content-Type, "text/plain")]
main :: IO ()
main = do
let port = 80
putStrLn (F.format "+ Listening on port {}" [port])
run port (slash jpgto)
return ()
For the full example (since this one is missing a ton of imports),
see the examples/ directory on GitHub.
Documentation
say :: Message -> Config -> IO (Response ByteString) Source
The say function posts a Message, with a capital M, to Slack.
It'll, ahem, need your token first though.
slash :: (Maybe Command -> Application) -> Application Source
A bot server! As if by magic. This acts like a WAI middleware in that you let us wrap around your application.
Where slash commands can come from, and where messages can go.
Constructors
| GroupChannel Text | A public or private group. |
| IMChannel Text | A private conversation with your best friend (or lover?). |
A username: no at-signs, just text!
Here's how you talk.
Constructors
| Message | |
Fields
| |
Like a curiosity about the world, you'll need one of these to say something.
Constructors
| Config | |
Fields
| |
Incoming HTTP requests to the slash function get parsed into one of these babies.
Constructors
| Command | |
Fields
| |