polysemy-time: Polysemy Effect for Time

[ library, time ] [ Propose Tags ]
Versions [RSS] 0.1.0.0, 0.1.1.0, 0.1.2.0, 0.1.2.1, 0.1.2.2, 0.1.2.3, 0.1.2.4, 0.1.3.0, 0.1.3.1, 0.1.3.2, 0.1.4.0, 0.2.0.0, 0.2.0.1, 0.2.0.2, 0.2.0.3, 0.3.0.0, 0.4.0.0, 0.5.0.0, 0.5.1.0, 0.6.0.0, 0.6.0.1, 0.6.0.2
Change log changelog.md
Dependencies aeson (>=1.4 && <1.6), base (>=4 && <5), composition (>=1.0 && <1.1), containers, data-default (>=0.7 && <0.8), either, polysemy (>=1.3 && <1.6), relude (>=0.7 && <1.1), string-interpolate (>=0.2 && <0.4), template-haskell, text, time, torsor (>=0.1 && <0.2) [details]
License BSD-2-Clause-Patent
Copyright 2021 Torsten Schmits
Author Torsten Schmits
Maintainer tek@tryp.io
Category Time
Uploaded by tek at 2021-07-01T21:33:28Z
Distributions
Reverse Dependencies 12 direct, 17 indirect [details]
Downloads 2930 total (74 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs uploaded by user
Build status unknown [no reports yet]

Readme for polysemy-time-0.1.2.3

[back to package description]

About

This Haskell library provides a Polysemy effect for accessing the current time and date and an implementation for time and chronos.

Example

import Data.Time (UTCTime)
import Polysemy (Members, runM)
import Polysemy.Chronos (interpretTimeChronos)
import qualified Polysemy.Time as Time
import Polysemy.Time (MilliSeconds(MilliSeconds), Seconds(Seconds), Time, interpretTimeGhcAt, mkDatetime, year)

prog ::
  Ord t =>
  Member (Time t d) r =>
  Sem r ()
prog = do
  time1 <- Time.now
  Time.sleep (MilliSeconds 10)
  time2 <- Time.now
  print (time1 < time2)
  -- True

testTime :: UTCTime
testTime =
  mkDatetime 1845 12 31 23 59 59

main :: IO ()
main =
  runM do
    interpretTimeChronos prog
    interpretTimeGhcAt testTime do
      Time.sleep (Seconds 1)
      time <- Time.now
      print (year time)
      -- Years { unYear = 1846 }

Effect

The only effect contained in polysemy-time is:

data Time (time :: *) (date :: *) :: Effect where
  Now :: Time t d m t
  Today :: Time t d m d
  Sleep :: TimeUnit u => u -> Time t d m ()
  SetTime :: t -> Time t d m ()
  SetDate :: d -> Time t d m ()

Interpreters are provided for the time library bundled with GHC and chronos.

The type parameters correspond to the representations in the implementation, like Data.Time.UTCTime/Chronos.Time and Data.Time.Day/Chronos.Date.

SetTime and SetDate only have meaning when you're running in a testing context.

A special interpreter variant suffixed with At exists for both implementations, with which the current time is overridden to be relative to the supplied override fixed at the start of interpretation. This is useful for testing.

Utilities

A set of newtypes representing timespans are provided for convenience. Internally, the interpreters operate on NanoSeconds.

The class TimeUnit ties those types, and the types Chronos.Timespan and Data.Time.DiffTime, together to allow you to convert between them with the function convert:

>>> convert (picosecondsToDiffTime 50000000) :: MicroSeconds
MicroSeconds {unMicroSeconds = 50}

>>> convert (Days 5) :: Timespan
Timespan {getTimespan = 432000000000000}

The class Calendar allows you to construct UTCTime and Chronos.Datetime from integers with the function mkDatetime, as demonstrated in the first example.