-- | Provides typeclasses for clocks and randomizer environments
module System.Chatty.Misc where

import Data.Time.Clock
import Data.Time.Calendar
import System.Random

-- | Typeclass for all monads that know the time
class (Functor m,Monad m) => MonadClock m where
  -- | Get UTC Time
  mutctime :: m UTCTime
  -- | Get timestamp, guaranteed to grow
  mgetstamp :: m NominalDiffTime
  mgetstamp = fmap (diffUTCTime (UTCTime (fromGregorian 1970 1 1) (secondsToDiffTime 0))) mutctime

instance MonadClock IO where
  mutctime = getCurrentTime

-- | Typeclass for all monads that may provide random numbers
class Monad m => MonadRandom m where
  -- | Get a single random number
  mrandom :: Random r => m r
  -- | Get a single random number in the given range
  mrandomR :: Random r => (r,r) -> m r

instance MonadRandom IO where
  mrandom = randomIO
  mrandomR rs = randomRIO rs