{-# LANGUAGE MultiWayIf #-}
module Matterhorn.Types.Common
( sanitizeUserText
, sanitizeUserText'
, userIdForDMChannel
)
where
import Prelude ()
import Matterhorn.Prelude
import qualified Data.Text as T
import Data.Char ( isPrint )
import Network.Mattermost.Types ( UserText, unsafeUserText, UserId(..), Id(..) )
sanitizeUserText :: UserText -> T.Text
sanitizeUserText :: UserText -> Text
sanitizeUserText = Text -> Text
sanitizeUserText' (Text -> Text) -> (UserText -> Text) -> UserText -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UserText -> Text
unsafeUserText
sanitizeUserText' :: T.Text -> T.Text
sanitizeUserText' :: Text -> Text
sanitizeUserText' =
(Char -> Bool) -> Text -> Text
T.filter (\Char
c -> Char -> Bool
isPrint Char
c Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\n') (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Text -> Text -> Text -> Text
T.replace Text
"\ESC" Text
"<ESC>" (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Text -> Text -> Text -> Text
T.replace Text
"\t" Text
" "
userIdForDMChannel :: UserId
-> Text
-> Maybe UserId
userIdForDMChannel :: UserId -> Text -> Maybe UserId
userIdForDMChannel UserId
me Text
chanName =
let vals :: [Text]
vals = Text -> Text -> [Text]
T.splitOn Text
"__" Text
chanName
in case [Text]
vals of
[Text
u1, Text
u2] -> if | (Id -> UserId
UI (Id -> UserId) -> Id -> UserId
forall a b. (a -> b) -> a -> b
$ Text -> Id
Id Text
u1) UserId -> UserId -> Bool
forall a. Eq a => a -> a -> Bool
== UserId
me -> UserId -> Maybe UserId
forall a. a -> Maybe a
Just (UserId -> Maybe UserId) -> UserId -> Maybe UserId
forall a b. (a -> b) -> a -> b
$ Id -> UserId
UI (Id -> UserId) -> Id -> UserId
forall a b. (a -> b) -> a -> b
$ Text -> Id
Id Text
u2
| (Id -> UserId
UI (Id -> UserId) -> Id -> UserId
forall a b. (a -> b) -> a -> b
$ Text -> Id
Id Text
u2) UserId -> UserId -> Bool
forall a. Eq a => a -> a -> Bool
== UserId
me -> UserId -> Maybe UserId
forall a. a -> Maybe a
Just (UserId -> Maybe UserId) -> UserId -> Maybe UserId
forall a b. (a -> b) -> a -> b
$ Id -> UserId
UI (Id -> UserId) -> Id -> UserId
forall a b. (a -> b) -> a -> b
$ Text -> Id
Id Text
u1
| Bool
otherwise -> Maybe UserId
forall a. Maybe a
Nothing
[Text]
_ -> Maybe UserId
forall a. Maybe a
Nothing