module Signet.Unstable.Type.Timestamp where

import qualified Data.ByteString as ByteString
import qualified Data.Text as Text
import qualified Data.Text.Encoding as Text
import qualified Data.Time as Time
import qualified Signet.Unstable.Exception.InvalidTimestamp as InvalidTimestamp
import qualified Signet.Unstable.Extra.Either as Either
import qualified Signet.Unstable.Extra.Maybe as Maybe

newtype Timestamp
  = MkTimestamp Time.UTCTime
  deriving (Timestamp -> Timestamp -> Bool
(Timestamp -> Timestamp -> Bool)
-> (Timestamp -> Timestamp -> Bool) -> Eq Timestamp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Timestamp -> Timestamp -> Bool
== :: Timestamp -> Timestamp -> Bool
$c/= :: Timestamp -> Timestamp -> Bool
/= :: Timestamp -> Timestamp -> Bool
Eq, Int -> Timestamp -> ShowS
[Timestamp] -> ShowS
Timestamp -> String
(Int -> Timestamp -> ShowS)
-> (Timestamp -> String)
-> ([Timestamp] -> ShowS)
-> Show Timestamp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Timestamp -> ShowS
showsPrec :: Int -> Timestamp -> ShowS
$cshow :: Timestamp -> String
show :: Timestamp -> String
$cshowList :: [Timestamp] -> ShowS
showList :: [Timestamp] -> ShowS
Show)

unwrap :: Timestamp -> Time.UTCTime
unwrap :: Timestamp -> UTCTime
unwrap (MkTimestamp UTCTime
utcTime) = UTCTime
utcTime

format :: String
format :: String
format = String
"%s"

parse :: ByteString.ByteString -> Either InvalidTimestamp.InvalidTimestamp Timestamp
parse :: ByteString -> Either InvalidTimestamp Timestamp
parse ByteString
byteString = InvalidTimestamp
-> Maybe Timestamp -> Either InvalidTimestamp Timestamp
forall e a. e -> Maybe a -> Either e a
Maybe.note (ByteString -> InvalidTimestamp
InvalidTimestamp.MkInvalidTimestamp ByteString
byteString) (Maybe Timestamp -> Either InvalidTimestamp Timestamp)
-> Maybe Timestamp -> Either InvalidTimestamp Timestamp
forall a b. (a -> b) -> a -> b
$ do
  text <- Either UnicodeException Text -> Maybe Text
forall x a. Either x a -> Maybe a
Either.hush (Either UnicodeException Text -> Maybe Text)
-> Either UnicodeException Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ ByteString -> Either UnicodeException Text
Text.decodeUtf8' ByteString
byteString
  fmap MkTimestamp
    . Time.parseTimeM False Time.defaultTimeLocale format
    $ Text.unpack text

render :: Timestamp -> ByteString.ByteString
render :: Timestamp -> ByteString
render =
  Text -> ByteString
Text.encodeUtf8
    (Text -> ByteString)
-> (Timestamp -> Text) -> Timestamp -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
Text.pack
    (String -> Text) -> (Timestamp -> String) -> Timestamp -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TimeLocale -> String -> UTCTime -> String
forall t. FormatTime t => TimeLocale -> String -> t -> String
Time.formatTime TimeLocale
Time.defaultTimeLocale String
format
    (UTCTime -> String)
-> (Timestamp -> UTCTime) -> Timestamp -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Timestamp -> UTCTime
unwrap