summaryrefslogtreecommitdiff
path: root/src/Utils
diff options
context:
space:
mode:
Diffstat (limited to 'src/Utils')
-rw-r--r--src/Utils/Monad.hs26
-rw-r--r--src/Utils/Time.hs43
2 files changed, 69 insertions, 0 deletions
diff --git a/src/Utils/Monad.hs b/src/Utils/Monad.hs
new file mode 100644
index 0000000..3c1ad17
--- /dev/null
+++ b/src/Utils/Monad.hs
@@ -0,0 +1,26 @@
+{-|
+Module : Utils.Monad
+Copyright : (c) UU, 2019
+License : MIT
+Maintainer : Tom Smeding
+Stability : experimental
+Portability : POSIX, macOS, Windows
+
+Some useful functions lifted to monadic actions.
+-}
+module Utils.Monad where
+
+
+-- | If the boolean resolves to True, returns the first argument, else the
+-- second.
+ifM :: Monad m => m Bool -> m a -> m a -> m a
+ifM b t e = b >>= \b' -> if b' then t else e
+
+-- | Runs the monadic action only if the boolean resolves to True.
+whenM :: Monad m => m Bool -> m () -> m ()
+whenM b t = ifM b t (return ())
+
+-- | whenJust m a = when (isJust m) (a (fromJust m)), but with less
+-- fromJust.
+whenJust :: Monad m => Maybe a -> (a -> m ()) -> m ()
+whenJust = flip (maybe (return ()))
diff --git a/src/Utils/Time.hs b/src/Utils/Time.hs
new file mode 100644
index 0000000..2139c53
--- /dev/null
+++ b/src/Utils/Time.hs
@@ -0,0 +1,43 @@
+{-|
+Module : Utils.Time
+Copyright : (c) UU, 2019
+License : MIT
+Maintainer : Tom Smeding
+Stability : experimental
+Portability : POSIX, macOS, Windows
+-}
+module Utils.Time where
+
+import Data.Time.Clock
+import Data.Time.Clock.System hiding (getSystemTime)
+import qualified Data.Time.Clock.System as Sys
+import Data.Time.Format
+
+
+-- | A timestamp in milliseconds.
+newtype TimeStamp = TimeStamp Int
+ deriving (Show, Read, Eq, Ord)
+
+-- | The number of milliseconds stored in the timestamp newtype.
+timestampMS :: TimeStamp -> Int
+timestampMS (TimeStamp n) = n
+
+-- | Offset the timestamp by the given number of milliseconds.
+plusMS :: TimeStamp -> Int -> TimeStamp
+plusMS (TimeStamp n) m = TimeStamp (n + m)
+
+-- | The number of milliseconds that the first timestamp is later than the
+-- second.
+subtractMS :: TimeStamp -> TimeStamp -> Int
+subtractMS (TimeStamp n) (TimeStamp m) = n - m
+
+-- | Return the current system time as a timestamp.
+getSystemTime :: IO TimeStamp
+getSystemTime = TimeStamp . systemToMS <$> Sys.getSystemTime
+ where
+ systemToMS tm = let MkSystemTime s ns = truncateSystemTimeLeapSecond tm
+ in fromIntegral s * 1000 + fromIntegral ns `div` 1000000
+
+-- | Show a UTCTime in ISO-8601 format.
+iso8601Show :: UTCTime -> String
+iso8601Show = formatTime defaultTimeLocale (iso8601DateFormat (Just "%H:%M:%S"))