hask-irc/hask-irc-core/Network/IRC/Util.hs

84 lines
2.6 KiB
Haskell
Raw Normal View History

2014-05-25 14:51:33 +05:30
{-# LANGUAGE FlexibleContexts #-}
module Network.IRC.Util where
import qualified Data.Text.Lazy as LzT
import qualified Data.Text.Format as TF
import ClassyPrelude
2014-05-25 14:51:33 +05:30
import Control.Arrow (Arrow)
import Control.Concurrent.Lifted (Chan)
2014-05-25 14:51:33 +05:30
import Control.Monad.Base (MonadBase)
2014-05-23 02:45:45 +05:30
import Data.Text (strip)
import Data.Time (diffUTCTime)
oneSec :: Int
oneSec = 1000000
type Latch = MVar ()
latchIt :: Latch -> IO ()
latchIt latch = putMVar latch ()
awaitLatch :: Latch -> IO ()
awaitLatch latch = void $ takeMVar latch
type Channel a = (Chan a, Latch)
2014-05-22 20:59:02 +05:30
mapKeys :: IsMap map => map -> [ContainerKey map]
mapKeys = map fst . mapToList
mapValues :: IsMap map => map -> [MapValue map]
mapValues = map snd . mapToList
2014-05-23 02:45:45 +05:30
whenJust :: Monad m => Maybe t -> (t -> m ()) -> m ()
whenJust m f = maybe (return ()) f m
clean :: Text -> Text
clean = toLower . strip
2014-05-23 12:21:38 +05:30
io :: MonadIO m => IO a -> m a
io = liftIO
2014-05-25 14:51:33 +05:30
both :: Arrow cat => cat b d -> cat (b, b) (d, d)
both f = first f . second f
atomicModIORef :: MonadBase IO f => IORef t -> (t -> t) -> f ()
atomicModIORef ref f = void . atomicModifyIORef' ref $ \v -> (f v, v)
-- | Display a time span as one time relative to another.
relativeTime :: UTCTime -> UTCTime -> Text
relativeTime t1 t2 =
maybe "unknown" (LzT.toStrict . format) $ find (\(s,_,_) -> abs period >= s) ranges
where
minute = 60; hour = minute * 60; day = hour * 24;
week = day * 7; month = day * 30; year = month * 12
format range =
(if period > 0 then "in " else "")
++ case range of
(_, str, 0) -> pack str
(_, str, base) -> TF.format (fromString str) $ TF.Only (abs $ round (period / base) :: Integer)
2014-06-01 06:48:24 +05:30
++ (if period <= 0 then " ago" else "")
period = t1 `diffUTCTime` t2
ranges = [(year*2, "{} years", year)
,(year, "a year", 0)
,(month*2, "{} months", month)
,(month, "a month", 0)
,(week*2, "{} weeks", week)
,(week, "a week", 0)
,(day*2, "{} days", day)
,(day, "a day", 0)
,(hour*4, "{} hours", hour)
,(hour*3, "a few hours", 0)
,(hour*2, "{} hours", hour)
,(hour, "an hour", 0)
,(minute*31, "{} minutes", minute)
,(minute*30, "half an hour", 0)
,(minute*2, "{} minutes", minute)
,(minute, "a minute", 0)
,(0, "{} seconds", 1)
]