aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/time/duration.lux
blob: 748cd039e56d55db9e020e4ab6b76dcca722d56a (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
(.module:
  [lux #*
   [control
    equivalence
    order
    codec
    [monoid (#+ Monoid)]
    ["p" parser]
    [monad (#+ do)]]
   [data
    [number ("int/" Codec<Text,Int> Number<Int>)]
    [text ("text/" Monoid<Text>)
     ["l" lexer]]
    ["e" error]]
   [type
    abstract]])

(abstract: #export Duration
  {#.doc "Durations have a resolution of milliseconds."}
  Int

  (def: #export from-millis
    (-> Int Duration)
    (|>> :abstraction))

  (def: #export to-millis
    (-> Duration Int)
    (|>> :representation))

  (do-template [<name> <op>]
    [(def: #export (<name> param subject)
       (-> Duration Duration Duration)
       (:abstraction (<op> (:representation param) (:representation subject))))]

    [merge i/+]
    [frame i/%]
    )

  (def: #export (scale scalar duration)
    (-> Int Duration Duration)
    (:abstraction (i/* scalar (:representation duration))))

  (def: #export (query param subject)
    (-> Duration Duration Int)
    (i// (:representation param) (:representation subject)))

  (structure: #export _ (Equivalence Duration)
    (def: (= param subject)
      (i/= (:representation param) (:representation subject))))

  (structure: #export _ (Order Duration)
    (def: eq Equivalence<Duration>)
    (do-template [<name> <op>]
      [(def: (<name> param subject)
         (<op> (:representation param) (:representation subject)))]

      [<  i/<]
      [<= i/<=]
      [>  i/>]
      [>= i/>=]
      ))

  (do-template [<name> <op>]
    [(def: #export (<name> duration)
       (-> Duration Bit)
       (<op> 0 (:representation duration)))]

    [positive? i/>]
    [negative? i/<]
    [neutral?  i/=])
  )

(def: #export empty Duration (from-millis 0))
(def: #export milli Duration (from-millis 1))
(def: #export second Duration (scale 1_000 milli))
(def: #export minute Duration (scale 60 second))
(def: #export hour Duration (scale 60 minute))
(def: #export day Duration (scale 24 hour))
(def: #export week Duration (scale 7 day))
(def: #export normal-year Duration (scale 365 day))
(def: #export leap-year Duration (merge day normal-year))

(structure: #export _ (Monoid Duration)
  (def: identity empty)
  (def: compose merge))

(def: (encode duration)
  (-> Duration Text)
  (if (:: Equivalence<Duration> = empty duration)
    "0ms"
    (let [signed? (negative? duration)
          [days time-left] [(query day duration) (frame day duration)]
          days (if signed?
                 (int/abs days)
                 days)
          time-left (if signed?
                      (scale -1 time-left)
                      time-left)
          [hours time-left] [(query hour time-left) (frame hour time-left)]
          [minutes time-left] [(query minute time-left) (frame minute time-left)]
          [seconds time-left] [(query second time-left) (frame second time-left)]
          millis (to-millis time-left)]
      ($_ text/compose
          (if signed? "-" "")
          (if (i/= 0 days) "" (text/compose (int/encode days) "D"))
          (if (i/= 0 hours) "" (text/compose (int/encode hours) "h"))
          (if (i/= 0 minutes) "" (text/compose (int/encode minutes) "m"))
          (if (i/= 0 seconds) "" (text/compose (int/encode seconds) "s"))
          (if (i/= 0 millis) "" (text/compose (int/encode millis) "ms"))
          ))))

(def: (lex-section suffix)
  (-> Text (l.Lexer Int))
  (|> (p.codec number.Codec<Text,Int> (l.many l.decimal))
      (p.before (p.seq (l.this suffix) (p.not l.alpha)))
      (p.default 0)))

(def: lex-duration
  (l.Lexer Duration)
  (do p.Monad<Parser>
    [signed? (l.this? "-")
     #let [sign (function (_ raw) (if signed? (i/* -1 raw) raw))]
     utc-day (lex-section "D")
     utc-hour (lex-section "h")
     utc-minute (lex-section "m")
     _ (p.assert "Invalid minute."
                 (and (i/>= 0 utc-minute)
                      (i/<= 59 utc-minute)))
     utc-second (lex-section "s")
     _ (p.assert "Invalid second."
                 (and (i/>= 0 utc-second)
                      (i/<= 59 utc-second)))
     utc-millis (lex-section "ms")
     _ (p.assert "Invalid milli-seconds."
                 (and (i/>= 0 utc-millis)
                      (i/<= 999 utc-millis)))]
    (wrap (|> empty
              (merge (scale (sign utc-day) day))
              (merge (scale (sign utc-hour) hour))
              (merge (scale (sign utc-minute) minute))
              (merge (scale (sign utc-second) second))
              (merge (scale (sign utc-millis) milli))))))

(def: (decode input)
  (-> Text (e.Error Duration))
  (l.run input lex-duration))

(structure: #export _
  {#.doc "For example: 15D21h14m51s827ms"}
  (Codec Text Duration)
  (def: encode encode)
  (def: decode decode))