module Network.Linklater
(
say,
slash,
slashSimple,
Channel(..),
User(..),
Message(..),
Config(..),
Command(..),
Icon(..),
Format(..)
) where
import BasePrelude
import Data.Aeson
import qualified Data.ByteString.Lazy as BSL
import qualified Data.Map as M
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Encoding as TLE
import Network.HTTP.Types (status200)
import qualified Network.Wai as W
import Network.Wreq hiding (params, headers)
data Channel =
GroupChannel Text
| IMChannel Text
deriving (Eq, Ord, Show)
newtype User = User Text deriving (Eq, Ord, Show)
data Command = Command {
_commandName :: Text,
_commandUser :: User,
_commandChannel :: Channel,
_commandText :: Maybe Text
} deriving (Eq, Ord, Show)
newtype Icon =
EmojiIcon Text deriving (Eq, Ord, Show)
data Format =
FormatAt User
| FormatUser User Text
| FormatLink Text Text
| FormatString Text
unformat :: Format -> Text
unformat (FormatAt user@(User u)) = unformat (FormatUser user u)
unformat (FormatUser (User u) t) = "<@" <> u <> "|" <> t <> ">"
unformat (FormatLink url t) = "<" <> url <> "|" <> t <> ">"
unformat (FormatString t) = foldr (uncurry T.replace) t [("<", "<"), (">", ">"), ("&", "&")]
data Message =
SimpleMessage Icon Text Channel Text
| FormattedMessage Icon Text Channel [Format]
instance ToJSON Channel where
toJSON (GroupChannel c) =
String ("#" <> c)
toJSON (IMChannel im) =
String ("@" <> im)
instance ToJSON Message where
toJSON m = case m of
(FormattedMessage emoji username channel formats) ->
toJSON_ emoji username channel (T.intercalate " " (fmap unformat formats)) False
(SimpleMessage emoji username channel text) ->
toJSON_ emoji username channel text True
where
toJSON_ (EmojiIcon emoji) username channel raw toParse =
object [ "channel" .= channel
, "icon_emoji" .= (":" <> emoji <> ":")
, "parse" .= String (if toParse then "full" else "poop")
, "username" .= username
, "text" .= raw
, "unfurl_links" .= True
]
data Config = Config {
_configHookURL :: Text
}
say :: Message -> Config -> IO (Response BSL.ByteString)
say message Config{..} =
post (T.unpack _configHookURL) (encode message)
slashSimple :: (Maybe Command -> IO Text) -> W.Application
slashSimple f =
slash (\command _ respond -> f command >>= (respond . makeResponse . TL.fromStrict))
where
headers =
[("Content-type", "text/plain")]
makeResponse =
W.responseLBS status200 headers . TLE.encodeUtf8
channelOf :: User -> Text -> Maybe Channel
channelOf (User u) "directmessage" =
Just (IMChannel u)
channelOf _ "privategroup" =
Nothing
channelOf _ c =
Just (GroupChannel c)
slash :: (Maybe Command -> W.Application) -> W.Application
slash f req respond = f command req respond
where
command = do
user <- userOf <$> wishFor "user_name"
Command <$> (nameOf <$> wishFor "command")
<*> return user
<*> (wishFor "channel_name" >>= channelOf user)
<*> return (wishFor "text")
wishFor key =
case M.lookup (key :: TL.Text) params of
Just (Just "") ->
Nothing
Just (Just value) ->
Just (TL.toStrict value)
_ ->
Nothing
userOf = User . T.filter (/= '@')
nameOf = T.filter (/= '/')
params = M.fromList [(toText k, toText <$> v) | (k, v) <- W.queryString req]
toText = TLE.decodeUtf8 . BSL.fromChunks . return