module Web.Slack.Types (
Color (..),
UserId (..),
ConversationId (..),
TeamId (..),
Cursor (..),
SlackTimestamp (..),
mkSlackTimestamp,
timestampFromText,
SlackMessageText (..),
) where
import Control.Monad (MonadFail (..))
import Data.Aeson
import Data.Text qualified as T
import Data.Text.Read (rational)
import Data.Time.Clock
import Data.Time.Clock.POSIX
import Web.HttpApiData
import Web.Slack.Pager.Types
import Web.Slack.Prelude
newtype Color = Color {Color -> Text
unColor :: Text}
deriving stock (Color -> Color -> Bool
(Color -> Color -> Bool) -> (Color -> Color -> Bool) -> Eq Color
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Color -> Color -> Bool
== :: Color -> Color -> Bool
$c/= :: Color -> Color -> Bool
/= :: Color -> Color -> Bool
Eq, Eq Color
Eq Color =>
(Color -> Color -> Ordering)
-> (Color -> Color -> Bool)
-> (Color -> Color -> Bool)
-> (Color -> Color -> Bool)
-> (Color -> Color -> Bool)
-> (Color -> Color -> Color)
-> (Color -> Color -> Color)
-> Ord Color
Color -> Color -> Bool
Color -> Color -> Ordering
Color -> Color -> Color
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Color -> Color -> Ordering
compare :: Color -> Color -> Ordering
$c< :: Color -> Color -> Bool
< :: Color -> Color -> Bool
$c<= :: Color -> Color -> Bool
<= :: Color -> Color -> Bool
$c> :: Color -> Color -> Bool
> :: Color -> Color -> Bool
$c>= :: Color -> Color -> Bool
>= :: Color -> Color -> Bool
$cmax :: Color -> Color -> Color
max :: Color -> Color -> Color
$cmin :: Color -> Color -> Color
min :: Color -> Color -> Color
Ord, (forall x. Color -> Rep Color x)
-> (forall x. Rep Color x -> Color) -> Generic Color
forall x. Rep Color x -> Color
forall x. Color -> Rep Color x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Color -> Rep Color x
from :: forall x. Color -> Rep Color x
$cto :: forall x. Rep Color x -> Color
to :: forall x. Rep Color x -> Color
Generic, Int -> Color -> ShowS
[Color] -> ShowS
Color -> String
(Int -> Color -> ShowS)
-> (Color -> String) -> ([Color] -> ShowS) -> Show Color
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Color -> ShowS
showsPrec :: Int -> Color -> ShowS
$cshow :: Color -> String
show :: Color -> String
$cshowList :: [Color] -> ShowS
showList :: [Color] -> ShowS
Show)
deriving newtype (Color -> ()
(Color -> ()) -> NFData Color
forall a. (a -> ()) -> NFData a
$crnf :: Color -> ()
rnf :: Color -> ()
NFData, Eq Color
Eq Color =>
(Int -> Color -> Int) -> (Color -> Int) -> Hashable Color
Int -> Color -> Int
Color -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> Color -> Int
hashWithSalt :: Int -> Color -> Int
$chash :: Color -> Int
hash :: Color -> Int
Hashable, Value -> Parser [Color]
Value -> Parser Color
(Value -> Parser Color)
-> (Value -> Parser [Color]) -> FromJSON Color
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser Color
parseJSON :: Value -> Parser Color
$cparseJSONList :: Value -> Parser [Color]
parseJSONList :: Value -> Parser [Color]
FromJSON, [Color] -> Value
[Color] -> Encoding
Color -> Value
Color -> Encoding
(Color -> Value)
-> (Color -> Encoding)
-> ([Color] -> Value)
-> ([Color] -> Encoding)
-> ToJSON Color
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: Color -> Value
toJSON :: Color -> Value
$ctoEncoding :: Color -> Encoding
toEncoding :: Color -> Encoding
$ctoJSONList :: [Color] -> Value
toJSONList :: [Color] -> Value
$ctoEncodingList :: [Color] -> Encoding
toEncodingList :: [Color] -> Encoding
ToJSON)
newtype UserId = UserId {UserId -> Text
unUserId :: Text}
deriving stock (UserId -> UserId -> Bool
(UserId -> UserId -> Bool)
-> (UserId -> UserId -> Bool) -> Eq UserId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UserId -> UserId -> Bool
== :: UserId -> UserId -> Bool
$c/= :: UserId -> UserId -> Bool
/= :: UserId -> UserId -> Bool
Eq, Eq UserId
Eq UserId =>
(UserId -> UserId -> Ordering)
-> (UserId -> UserId -> Bool)
-> (UserId -> UserId -> Bool)
-> (UserId -> UserId -> Bool)
-> (UserId -> UserId -> Bool)
-> (UserId -> UserId -> UserId)
-> (UserId -> UserId -> UserId)
-> Ord UserId
UserId -> UserId -> Bool
UserId -> UserId -> Ordering
UserId -> UserId -> UserId
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: UserId -> UserId -> Ordering
compare :: UserId -> UserId -> Ordering
$c< :: UserId -> UserId -> Bool
< :: UserId -> UserId -> Bool
$c<= :: UserId -> UserId -> Bool
<= :: UserId -> UserId -> Bool
$c> :: UserId -> UserId -> Bool
> :: UserId -> UserId -> Bool
$c>= :: UserId -> UserId -> Bool
>= :: UserId -> UserId -> Bool
$cmax :: UserId -> UserId -> UserId
max :: UserId -> UserId -> UserId
$cmin :: UserId -> UserId -> UserId
min :: UserId -> UserId -> UserId
Ord, (forall x. UserId -> Rep UserId x)
-> (forall x. Rep UserId x -> UserId) -> Generic UserId
forall x. Rep UserId x -> UserId
forall x. UserId -> Rep UserId x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. UserId -> Rep UserId x
from :: forall x. UserId -> Rep UserId x
$cto :: forall x. Rep UserId x -> UserId
to :: forall x. Rep UserId x -> UserId
Generic, Int -> UserId -> ShowS
[UserId] -> ShowS
UserId -> String
(Int -> UserId -> ShowS)
-> (UserId -> String) -> ([UserId] -> ShowS) -> Show UserId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UserId -> ShowS
showsPrec :: Int -> UserId -> ShowS
$cshow :: UserId -> String
show :: UserId -> String
$cshowList :: [UserId] -> ShowS
showList :: [UserId] -> ShowS
Show)
deriving newtype (UserId -> ()
(UserId -> ()) -> NFData UserId
forall a. (a -> ()) -> NFData a
$crnf :: UserId -> ()
rnf :: UserId -> ()
NFData, Eq UserId
Eq UserId =>
(Int -> UserId -> Int) -> (UserId -> Int) -> Hashable UserId
Int -> UserId -> Int
UserId -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> UserId -> Int
hashWithSalt :: Int -> UserId -> Int
$chash :: UserId -> Int
hash :: UserId -> Int
Hashable, Value -> Parser [UserId]
Value -> Parser UserId
(Value -> Parser UserId)
-> (Value -> Parser [UserId]) -> FromJSON UserId
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser UserId
parseJSON :: Value -> Parser UserId
$cparseJSONList :: Value -> Parser [UserId]
parseJSONList :: Value -> Parser [UserId]
FromJSON, [UserId] -> Value
[UserId] -> Encoding
UserId -> Value
UserId -> Encoding
(UserId -> Value)
-> (UserId -> Encoding)
-> ([UserId] -> Value)
-> ([UserId] -> Encoding)
-> ToJSON UserId
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: UserId -> Value
toJSON :: UserId -> Value
$ctoEncoding :: UserId -> Encoding
toEncoding :: UserId -> Encoding
$ctoJSONList :: [UserId] -> Value
toJSONList :: [UserId] -> Value
$ctoEncodingList :: [UserId] -> Encoding
toEncodingList :: [UserId] -> Encoding
ToJSON, UserId -> Text
UserId -> ByteString
UserId -> Builder
(UserId -> Text)
-> (UserId -> Builder)
-> (UserId -> ByteString)
-> (UserId -> Text)
-> (UserId -> Builder)
-> ToHttpApiData UserId
forall a.
(a -> Text)
-> (a -> Builder)
-> (a -> ByteString)
-> (a -> Text)
-> (a -> Builder)
-> ToHttpApiData a
$ctoUrlPiece :: UserId -> Text
toUrlPiece :: UserId -> Text
$ctoEncodedUrlPiece :: UserId -> Builder
toEncodedUrlPiece :: UserId -> Builder
$ctoHeader :: UserId -> ByteString
toHeader :: UserId -> ByteString
$ctoQueryParam :: UserId -> Text
toQueryParam :: UserId -> Text
$ctoEncodedQueryParam :: UserId -> Builder
toEncodedQueryParam :: UserId -> Builder
ToHttpApiData)
newtype ConversationId = ConversationId {ConversationId -> Text
unConversationId :: Text}
deriving stock (ConversationId -> ConversationId -> Bool
(ConversationId -> ConversationId -> Bool)
-> (ConversationId -> ConversationId -> Bool) -> Eq ConversationId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ConversationId -> ConversationId -> Bool
== :: ConversationId -> ConversationId -> Bool
$c/= :: ConversationId -> ConversationId -> Bool
/= :: ConversationId -> ConversationId -> Bool
Eq, Eq ConversationId
Eq ConversationId =>
(ConversationId -> ConversationId -> Ordering)
-> (ConversationId -> ConversationId -> Bool)
-> (ConversationId -> ConversationId -> Bool)
-> (ConversationId -> ConversationId -> Bool)
-> (ConversationId -> ConversationId -> Bool)
-> (ConversationId -> ConversationId -> ConversationId)
-> (ConversationId -> ConversationId -> ConversationId)
-> Ord ConversationId
ConversationId -> ConversationId -> Bool
ConversationId -> ConversationId -> Ordering
ConversationId -> ConversationId -> ConversationId
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ConversationId -> ConversationId -> Ordering
compare :: ConversationId -> ConversationId -> Ordering
$c< :: ConversationId -> ConversationId -> Bool
< :: ConversationId -> ConversationId -> Bool
$c<= :: ConversationId -> ConversationId -> Bool
<= :: ConversationId -> ConversationId -> Bool
$c> :: ConversationId -> ConversationId -> Bool
> :: ConversationId -> ConversationId -> Bool
$c>= :: ConversationId -> ConversationId -> Bool
>= :: ConversationId -> ConversationId -> Bool
$cmax :: ConversationId -> ConversationId -> ConversationId
max :: ConversationId -> ConversationId -> ConversationId
$cmin :: ConversationId -> ConversationId -> ConversationId
min :: ConversationId -> ConversationId -> ConversationId
Ord, (forall x. ConversationId -> Rep ConversationId x)
-> (forall x. Rep ConversationId x -> ConversationId)
-> Generic ConversationId
forall x. Rep ConversationId x -> ConversationId
forall x. ConversationId -> Rep ConversationId x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ConversationId -> Rep ConversationId x
from :: forall x. ConversationId -> Rep ConversationId x
$cto :: forall x. Rep ConversationId x -> ConversationId
to :: forall x. Rep ConversationId x -> ConversationId
Generic, Int -> ConversationId -> ShowS
[ConversationId] -> ShowS
ConversationId -> String
(Int -> ConversationId -> ShowS)
-> (ConversationId -> String)
-> ([ConversationId] -> ShowS)
-> Show ConversationId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ConversationId -> ShowS
showsPrec :: Int -> ConversationId -> ShowS
$cshow :: ConversationId -> String
show :: ConversationId -> String
$cshowList :: [ConversationId] -> ShowS
showList :: [ConversationId] -> ShowS
Show)
deriving newtype (ConversationId -> ()
(ConversationId -> ()) -> NFData ConversationId
forall a. (a -> ()) -> NFData a
$crnf :: ConversationId -> ()
rnf :: ConversationId -> ()
NFData, Eq ConversationId
Eq ConversationId =>
(Int -> ConversationId -> Int)
-> (ConversationId -> Int) -> Hashable ConversationId
Int -> ConversationId -> Int
ConversationId -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> ConversationId -> Int
hashWithSalt :: Int -> ConversationId -> Int
$chash :: ConversationId -> Int
hash :: ConversationId -> Int
Hashable, Value -> Parser [ConversationId]
Value -> Parser ConversationId
(Value -> Parser ConversationId)
-> (Value -> Parser [ConversationId]) -> FromJSON ConversationId
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser ConversationId
parseJSON :: Value -> Parser ConversationId
$cparseJSONList :: Value -> Parser [ConversationId]
parseJSONList :: Value -> Parser [ConversationId]
FromJSON, [ConversationId] -> Value
[ConversationId] -> Encoding
ConversationId -> Value
ConversationId -> Encoding
(ConversationId -> Value)
-> (ConversationId -> Encoding)
-> ([ConversationId] -> Value)
-> ([ConversationId] -> Encoding)
-> ToJSON ConversationId
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: ConversationId -> Value
toJSON :: ConversationId -> Value
$ctoEncoding :: ConversationId -> Encoding
toEncoding :: ConversationId -> Encoding
$ctoJSONList :: [ConversationId] -> Value
toJSONList :: [ConversationId] -> Value
$ctoEncodingList :: [ConversationId] -> Encoding
toEncodingList :: [ConversationId] -> Encoding
ToJSON, ConversationId -> Text
ConversationId -> ByteString
ConversationId -> Builder
(ConversationId -> Text)
-> (ConversationId -> Builder)
-> (ConversationId -> ByteString)
-> (ConversationId -> Text)
-> (ConversationId -> Builder)
-> ToHttpApiData ConversationId
forall a.
(a -> Text)
-> (a -> Builder)
-> (a -> ByteString)
-> (a -> Text)
-> (a -> Builder)
-> ToHttpApiData a
$ctoUrlPiece :: ConversationId -> Text
toUrlPiece :: ConversationId -> Text
$ctoEncodedUrlPiece :: ConversationId -> Builder
toEncodedUrlPiece :: ConversationId -> Builder
$ctoHeader :: ConversationId -> ByteString
toHeader :: ConversationId -> ByteString
$ctoQueryParam :: ConversationId -> Text
toQueryParam :: ConversationId -> Text
$ctoEncodedQueryParam :: ConversationId -> Builder
toEncodedQueryParam :: ConversationId -> Builder
ToHttpApiData)
newtype TeamId = TeamId {TeamId -> Text
unTeamId :: Text}
deriving stock (TeamId -> TeamId -> Bool
(TeamId -> TeamId -> Bool)
-> (TeamId -> TeamId -> Bool) -> Eq TeamId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TeamId -> TeamId -> Bool
== :: TeamId -> TeamId -> Bool
$c/= :: TeamId -> TeamId -> Bool
/= :: TeamId -> TeamId -> Bool
Eq, Eq TeamId
Eq TeamId =>
(TeamId -> TeamId -> Ordering)
-> (TeamId -> TeamId -> Bool)
-> (TeamId -> TeamId -> Bool)
-> (TeamId -> TeamId -> Bool)
-> (TeamId -> TeamId -> Bool)
-> (TeamId -> TeamId -> TeamId)
-> (TeamId -> TeamId -> TeamId)
-> Ord TeamId
TeamId -> TeamId -> Bool
TeamId -> TeamId -> Ordering
TeamId -> TeamId -> TeamId
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: TeamId -> TeamId -> Ordering
compare :: TeamId -> TeamId -> Ordering
$c< :: TeamId -> TeamId -> Bool
< :: TeamId -> TeamId -> Bool
$c<= :: TeamId -> TeamId -> Bool
<= :: TeamId -> TeamId -> Bool
$c> :: TeamId -> TeamId -> Bool
> :: TeamId -> TeamId -> Bool
$c>= :: TeamId -> TeamId -> Bool
>= :: TeamId -> TeamId -> Bool
$cmax :: TeamId -> TeamId -> TeamId
max :: TeamId -> TeamId -> TeamId
$cmin :: TeamId -> TeamId -> TeamId
min :: TeamId -> TeamId -> TeamId
Ord, (forall x. TeamId -> Rep TeamId x)
-> (forall x. Rep TeamId x -> TeamId) -> Generic TeamId
forall x. Rep TeamId x -> TeamId
forall x. TeamId -> Rep TeamId x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TeamId -> Rep TeamId x
from :: forall x. TeamId -> Rep TeamId x
$cto :: forall x. Rep TeamId x -> TeamId
to :: forall x. Rep TeamId x -> TeamId
Generic, Int -> TeamId -> ShowS
[TeamId] -> ShowS
TeamId -> String
(Int -> TeamId -> ShowS)
-> (TeamId -> String) -> ([TeamId] -> ShowS) -> Show TeamId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TeamId -> ShowS
showsPrec :: Int -> TeamId -> ShowS
$cshow :: TeamId -> String
show :: TeamId -> String
$cshowList :: [TeamId] -> ShowS
showList :: [TeamId] -> ShowS
Show)
deriving newtype (TeamId -> ()
(TeamId -> ()) -> NFData TeamId
forall a. (a -> ()) -> NFData a
$crnf :: TeamId -> ()
rnf :: TeamId -> ()
NFData, Eq TeamId
Eq TeamId =>
(Int -> TeamId -> Int) -> (TeamId -> Int) -> Hashable TeamId
Int -> TeamId -> Int
TeamId -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> TeamId -> Int
hashWithSalt :: Int -> TeamId -> Int
$chash :: TeamId -> Int
hash :: TeamId -> Int
Hashable, Value -> Parser [TeamId]
Value -> Parser TeamId
(Value -> Parser TeamId)
-> (Value -> Parser [TeamId]) -> FromJSON TeamId
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser TeamId
parseJSON :: Value -> Parser TeamId
$cparseJSONList :: Value -> Parser [TeamId]
parseJSONList :: Value -> Parser [TeamId]
FromJSON, [TeamId] -> Value
[TeamId] -> Encoding
TeamId -> Value
TeamId -> Encoding
(TeamId -> Value)
-> (TeamId -> Encoding)
-> ([TeamId] -> Value)
-> ([TeamId] -> Encoding)
-> ToJSON TeamId
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: TeamId -> Value
toJSON :: TeamId -> Value
$ctoEncoding :: TeamId -> Encoding
toEncoding :: TeamId -> Encoding
$ctoJSONList :: [TeamId] -> Value
toJSONList :: [TeamId] -> Value
$ctoEncodingList :: [TeamId] -> Encoding
toEncodingList :: [TeamId] -> Encoding
ToJSON, TeamId -> Text
TeamId -> ByteString
TeamId -> Builder
(TeamId -> Text)
-> (TeamId -> Builder)
-> (TeamId -> ByteString)
-> (TeamId -> Text)
-> (TeamId -> Builder)
-> ToHttpApiData TeamId
forall a.
(a -> Text)
-> (a -> Builder)
-> (a -> ByteString)
-> (a -> Text)
-> (a -> Builder)
-> ToHttpApiData a
$ctoUrlPiece :: TeamId -> Text
toUrlPiece :: TeamId -> Text
$ctoEncodedUrlPiece :: TeamId -> Builder
toEncodedUrlPiece :: TeamId -> Builder
$ctoHeader :: TeamId -> ByteString
toHeader :: TeamId -> ByteString
$ctoQueryParam :: TeamId -> Text
toQueryParam :: TeamId -> Text
$ctoEncodedQueryParam :: TeamId -> Builder
toEncodedQueryParam :: TeamId -> Builder
ToHttpApiData)
newtype SlackMessageText = SlackMessageText {SlackMessageText -> Text
unSlackMessageText :: Text}
deriving stock (SlackMessageText -> SlackMessageText -> Bool
(SlackMessageText -> SlackMessageText -> Bool)
-> (SlackMessageText -> SlackMessageText -> Bool)
-> Eq SlackMessageText
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SlackMessageText -> SlackMessageText -> Bool
== :: SlackMessageText -> SlackMessageText -> Bool
$c/= :: SlackMessageText -> SlackMessageText -> Bool
/= :: SlackMessageText -> SlackMessageText -> Bool
Eq, Eq SlackMessageText
Eq SlackMessageText =>
(SlackMessageText -> SlackMessageText -> Ordering)
-> (SlackMessageText -> SlackMessageText -> Bool)
-> (SlackMessageText -> SlackMessageText -> Bool)
-> (SlackMessageText -> SlackMessageText -> Bool)
-> (SlackMessageText -> SlackMessageText -> Bool)
-> (SlackMessageText -> SlackMessageText -> SlackMessageText)
-> (SlackMessageText -> SlackMessageText -> SlackMessageText)
-> Ord SlackMessageText
SlackMessageText -> SlackMessageText -> Bool
SlackMessageText -> SlackMessageText -> Ordering
SlackMessageText -> SlackMessageText -> SlackMessageText
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: SlackMessageText -> SlackMessageText -> Ordering
compare :: SlackMessageText -> SlackMessageText -> Ordering
$c< :: SlackMessageText -> SlackMessageText -> Bool
< :: SlackMessageText -> SlackMessageText -> Bool
$c<= :: SlackMessageText -> SlackMessageText -> Bool
<= :: SlackMessageText -> SlackMessageText -> Bool
$c> :: SlackMessageText -> SlackMessageText -> Bool
> :: SlackMessageText -> SlackMessageText -> Bool
$c>= :: SlackMessageText -> SlackMessageText -> Bool
>= :: SlackMessageText -> SlackMessageText -> Bool
$cmax :: SlackMessageText -> SlackMessageText -> SlackMessageText
max :: SlackMessageText -> SlackMessageText -> SlackMessageText
$cmin :: SlackMessageText -> SlackMessageText -> SlackMessageText
min :: SlackMessageText -> SlackMessageText -> SlackMessageText
Ord, (forall x. SlackMessageText -> Rep SlackMessageText x)
-> (forall x. Rep SlackMessageText x -> SlackMessageText)
-> Generic SlackMessageText
forall x. Rep SlackMessageText x -> SlackMessageText
forall x. SlackMessageText -> Rep SlackMessageText x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SlackMessageText -> Rep SlackMessageText x
from :: forall x. SlackMessageText -> Rep SlackMessageText x
$cto :: forall x. Rep SlackMessageText x -> SlackMessageText
to :: forall x. Rep SlackMessageText x -> SlackMessageText
Generic, Int -> SlackMessageText -> ShowS
[SlackMessageText] -> ShowS
SlackMessageText -> String
(Int -> SlackMessageText -> ShowS)
-> (SlackMessageText -> String)
-> ([SlackMessageText] -> ShowS)
-> Show SlackMessageText
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SlackMessageText -> ShowS
showsPrec :: Int -> SlackMessageText -> ShowS
$cshow :: SlackMessageText -> String
show :: SlackMessageText -> String
$cshowList :: [SlackMessageText] -> ShowS
showList :: [SlackMessageText] -> ShowS
Show)
deriving newtype (SlackMessageText -> ()
(SlackMessageText -> ()) -> NFData SlackMessageText
forall a. (a -> ()) -> NFData a
$crnf :: SlackMessageText -> ()
rnf :: SlackMessageText -> ()
NFData, Eq SlackMessageText
Eq SlackMessageText =>
(Int -> SlackMessageText -> Int)
-> (SlackMessageText -> Int) -> Hashable SlackMessageText
Int -> SlackMessageText -> Int
SlackMessageText -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> SlackMessageText -> Int
hashWithSalt :: Int -> SlackMessageText -> Int
$chash :: SlackMessageText -> Int
hash :: SlackMessageText -> Int
Hashable, Value -> Parser [SlackMessageText]
Value -> Parser SlackMessageText
(Value -> Parser SlackMessageText)
-> (Value -> Parser [SlackMessageText])
-> FromJSON SlackMessageText
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
$cparseJSON :: Value -> Parser SlackMessageText
parseJSON :: Value -> Parser SlackMessageText
$cparseJSONList :: Value -> Parser [SlackMessageText]
parseJSONList :: Value -> Parser [SlackMessageText]
FromJSON, [SlackMessageText] -> Value
[SlackMessageText] -> Encoding
SlackMessageText -> Value
SlackMessageText -> Encoding
(SlackMessageText -> Value)
-> (SlackMessageText -> Encoding)
-> ([SlackMessageText] -> Value)
-> ([SlackMessageText] -> Encoding)
-> ToJSON SlackMessageText
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: SlackMessageText -> Value
toJSON :: SlackMessageText -> Value
$ctoEncoding :: SlackMessageText -> Encoding
toEncoding :: SlackMessageText -> Encoding
$ctoJSONList :: [SlackMessageText] -> Value
toJSONList :: [SlackMessageText] -> Value
$ctoEncodingList :: [SlackMessageText] -> Encoding
toEncodingList :: [SlackMessageText] -> Encoding
ToJSON)
data SlackTimestamp = SlackTimestamp
{ SlackTimestamp -> Text
slackTimestampTs :: Text
, SlackTimestamp -> UTCTime
slackTimestampTime :: UTCTime
}
deriving stock (SlackTimestamp -> SlackTimestamp -> Bool
(SlackTimestamp -> SlackTimestamp -> Bool)
-> (SlackTimestamp -> SlackTimestamp -> Bool) -> Eq SlackTimestamp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SlackTimestamp -> SlackTimestamp -> Bool
== :: SlackTimestamp -> SlackTimestamp -> Bool
$c/= :: SlackTimestamp -> SlackTimestamp -> Bool
/= :: SlackTimestamp -> SlackTimestamp -> Bool
Eq, Int -> SlackTimestamp -> ShowS
[SlackTimestamp] -> ShowS
SlackTimestamp -> String
(Int -> SlackTimestamp -> ShowS)
-> (SlackTimestamp -> String)
-> ([SlackTimestamp] -> ShowS)
-> Show SlackTimestamp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SlackTimestamp -> ShowS
showsPrec :: Int -> SlackTimestamp -> ShowS
$cshow :: SlackTimestamp -> String
show :: SlackTimestamp -> String
$cshowList :: [SlackTimestamp] -> ShowS
showList :: [SlackTimestamp] -> ShowS
Show, (forall x. SlackTimestamp -> Rep SlackTimestamp x)
-> (forall x. Rep SlackTimestamp x -> SlackTimestamp)
-> Generic SlackTimestamp
forall x. Rep SlackTimestamp x -> SlackTimestamp
forall x. SlackTimestamp -> Rep SlackTimestamp x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SlackTimestamp -> Rep SlackTimestamp x
from :: forall x. SlackTimestamp -> Rep SlackTimestamp x
$cto :: forall x. Rep SlackTimestamp x -> SlackTimestamp
to :: forall x. Rep SlackTimestamp x -> SlackTimestamp
Generic)
instance NFData SlackTimestamp
instance Ord SlackTimestamp where
compare :: SlackTimestamp -> SlackTimestamp -> Ordering
compare (SlackTimestamp Text
_ UTCTime
a) (SlackTimestamp Text
_ UTCTime
b) = UTCTime -> UTCTime -> Ordering
forall a. Ord a => a -> a -> Ordering
compare UTCTime
a UTCTime
b
timestampFromText :: Text -> Either String SlackTimestamp
timestampFromText :: Text -> Either String SlackTimestamp
timestampFromText Text
t = (POSIXTime, Text) -> Either String SlackTimestamp
f ((POSIXTime, Text) -> Either String SlackTimestamp)
-> Either String (POSIXTime, Text) -> Either String SlackTimestamp
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Reader POSIXTime
forall a. Fractional a => Reader a
rational Text
t
where
f :: (POSIXTime, Text) -> Either String SlackTimestamp
f (POSIXTime
posixTime, Text
"") =
SlackTimestamp -> Either String SlackTimestamp
forall a b. b -> Either a b
Right (SlackTimestamp -> Either String SlackTimestamp)
-> (UTCTime -> SlackTimestamp)
-> UTCTime
-> Either String SlackTimestamp
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Text -> UTCTime -> SlackTimestamp
SlackTimestamp Text
t (UTCTime -> Either String SlackTimestamp)
-> UTCTime -> Either String SlackTimestamp
forall a b. (a -> b) -> a -> b
$ POSIXTime -> UTCTime
posixSecondsToUTCTime POSIXTime
posixTime
f (POSIXTime
_, Text
_left) = String -> Either String SlackTimestamp
forall a b. a -> Either a b
Left String
"Unexpected text left after timestamp"
mkSlackTimestamp :: UTCTime -> SlackTimestamp
mkSlackTimestamp :: UTCTime -> SlackTimestamp
mkSlackTimestamp UTCTime
utctime = Text -> UTCTime -> SlackTimestamp
SlackTimestamp (Text -> Text
take6DigitsAfterPoint (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (Pico -> String
forall a. Show a => a -> String
show Pico
unixts)) UTCTime
utctime
where
unixts :: Pico
unixts = POSIXTime -> Pico
nominalDiffTimeToSeconds (POSIXTime -> Pico) -> POSIXTime -> Pico
forall a b. (a -> b) -> a -> b
$ UTCTime -> POSIXTime
utcTimeToPOSIXSeconds UTCTime
utctime
take6DigitsAfterPoint :: Text -> Text
take6DigitsAfterPoint = (Text -> Text -> Text) -> (Text, Text) -> Text
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
(<>) ((Text, Text) -> Text) -> (Text -> (Text, Text)) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (Text -> Text) -> (Text, Text) -> (Text, Text)
forall b c a. (b -> c) -> (a, b) -> (a, c)
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second (Int -> Text -> Text
T.take Int
7) ((Text, Text) -> (Text, Text))
-> (Text -> (Text, Text)) -> Text -> (Text, Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (Char -> Bool) -> Text -> (Text, Text)
T.break (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'.')
instance ToHttpApiData SlackTimestamp where
toQueryParam :: SlackTimestamp -> Text
toQueryParam (SlackTimestamp Text
contents UTCTime
_) = Text
contents
instance FromJSON SlackTimestamp where
parseJSON :: Value -> Parser SlackTimestamp
parseJSON =
String
-> (Text -> Parser SlackTimestamp)
-> Value
-> Parser SlackTimestamp
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"Slack ts"
((Text -> Parser SlackTimestamp) -> Value -> Parser SlackTimestamp)
-> (Text -> Parser SlackTimestamp)
-> Value
-> Parser SlackTimestamp
forall a b. (a -> b) -> a -> b
$ (String -> Parser SlackTimestamp)
-> (SlackTimestamp -> Parser SlackTimestamp)
-> Either String SlackTimestamp
-> Parser SlackTimestamp
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (String -> Parser SlackTimestamp
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser SlackTimestamp)
-> ShowS -> String -> Parser SlackTimestamp
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (String
"Invalid Slack ts: " String -> ShowS
forall m. Monoid m => m -> m -> m
++)) SlackTimestamp -> Parser SlackTimestamp
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
(Either String SlackTimestamp -> Parser SlackTimestamp)
-> (Text -> Either String SlackTimestamp)
-> Text
-> Parser SlackTimestamp
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Text -> Either String SlackTimestamp
timestampFromText
instance ToJSON SlackTimestamp where
toJSON :: SlackTimestamp -> Value
toJSON = Text -> Value
String (Text -> Value)
-> (SlackTimestamp -> Text) -> SlackTimestamp -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. SlackTimestamp -> Text
slackTimestampTs