module Network.Mattermost.Util
( assertE
, noteE
, hoistE
, (~=)
, dropTrailingChar
, withConnection
, mkConnection
, connectionGetExact
) where
import Data.Char ( toUpper )
import qualified Data.ByteString.Char8 as B
import qualified Data.Text as T
import Control.Exception ( Exception
, throwIO
, bracket )
import Network.Connection ( Connection
, ConnectionParams(..)
, TLSSettings(..)
, connectionGet
, connectionClose
, connectTo )
import Network.Mattermost.Types.Internal
noteE :: Exception e => Maybe r -> e -> IO r
noteE Nothing e = throwIO e
noteE (Just r) _ = pure r
hoistE :: Exception e => Either e r -> IO r
hoistE (Left e) = throwIO e
hoistE (Right r) = pure r
assertE :: Exception e => Bool -> e -> IO ()
assertE True _ = pure ()
assertE False e = throwIO e
(~=) :: String -> String -> Bool
a ~= b = map toUpper a == map toUpper b
dropTrailingChar :: B.ByteString -> B.ByteString
dropTrailingChar bs | not (B.null bs) = B.init bs
dropTrailingChar _ = ""
withConnection :: ConnectionData -> (Connection -> IO a) -> IO a
withConnection cd action =
bracket (mkConnection cd)
connectionClose
action
mkConnection :: ConnectionData -> IO Connection
mkConnection cd = do
connectTo (cdConnectionCtx cd) $ ConnectionParams
{ connectionHostname = T.unpack $ cdHostname cd
, connectionPort = fromIntegral (cdPort cd)
, connectionUseSecure = if cdUseTLS cd
then Just (TLSSettingsSimple False False False)
else Nothing
, connectionUseSocks = Nothing
}
connectionGetExact :: Connection -> Int -> IO B.ByteString
connectionGetExact con n = loop B.empty 0
where loop bs y
| y == n = return bs
| otherwise = do
next <- connectionGet con (n y)
loop (B.append bs next) (y + (B.length next))