@@ -19,6 +19,7 @@ module Data.Attoparsec.Time
19
19
, timeZone
20
20
, utcTime
21
21
, zonedTime
22
+ , year
22
23
, month
23
24
, quarter
24
25
) where
@@ -27,42 +28,53 @@ import Prelude.Compat
27
28
28
29
import Control.Applicative ((<|>) )
29
30
import Control.Monad (void , when )
30
- import Data.Attoparsec.Text (Parser , char , decimal , digit , option , anyChar , peekChar , peekChar' , takeWhile1 , satisfy )
31
+ import Data.Attoparsec.Text (Parser , char , digit , option , anyChar , peekChar , peekChar' , takeWhile1 , satisfy )
31
32
import Data.Attoparsec.Time.Internal (toPico )
32
33
import Data.Bits ((.&.) )
33
34
import Data.Char (isDigit , ord )
34
35
import Data.Fixed (Pico )
35
36
import Data.Int (Int64 )
36
37
import Data.Maybe (fromMaybe )
37
38
import Data.Time.Calendar (Day , fromGregorianValid )
39
+ import Data.Time.Calendar.Compat (Year )
38
40
import Data.Time.Calendar.Quarter.Compat (Quarter , QuarterOfYear (.. ), fromYearQuarter )
39
41
import Data.Time.Calendar.Month.Compat (Month , fromYearMonthValid )
40
42
import Data.Time.Clock (UTCTime (.. ))
41
43
import qualified Data.Text as T
42
44
import qualified Data.Time.LocalTime as Local
43
45
44
46
-- | Parse a date of the form @[+,-]YYYY-MM-DD@.
47
+ --
48
+ -- The year must contain at least 4 digits, to avoid the Y2K problem:
49
+ -- a two-digit year @YY@ may mean @YY@, @19YY@, or @20YY@, and we make it
50
+ -- an error to prevent the ambiguity.
51
+ -- Years from @0000@ to @0999@ must thus be zero-padded.
52
+ -- The year may have more than 4 digits.
45
53
day :: Parser Day
46
54
day = do
47
55
absOrNeg <- negate <$ char ' -' <|> id <$ char ' +' <|> pure id
48
- y <- (decimal <* char ' -' ) <|> fail " date must be of form [+,-]YYYY-MM-DD"
56
+ y <- (year <* char ' -' ) <|> fail " date must be of form [+,-]YYYY-MM-DD"
49
57
m <- (twoDigits <* char ' -' ) <|> fail " date must be of form [+,-]YYYY-MM-DD"
50
58
d <- twoDigits <|> fail " date must be of form [+,-]YYYY-MM-DD"
51
59
maybe (fail " invalid date" ) return (fromGregorianValid (absOrNeg y) m d)
52
60
53
61
-- | Parse a month of the form @[+,-]YYYY-MM@.
62
+ --
63
+ -- See also 'day' for details about the year format.
54
64
month :: Parser Month
55
65
month = do
56
66
absOrNeg <- negate <$ char ' -' <|> id <$ char ' +' <|> pure id
57
- y <- (decimal <* char ' -' ) <|> fail " month must be of form [+,-]YYYY-MM"
67
+ y <- (year <* char ' -' ) <|> fail " month must be of form [+,-]YYYY-MM"
58
68
m <- twoDigits <|> fail " month must be of form [+,-]YYYY-MM"
59
69
maybe (fail " invalid month" ) return (fromYearMonthValid (absOrNeg y) m)
60
70
61
71
-- | Parse a quarter of the form @[+,-]YYYY-QN@.
72
+ --
73
+ -- See also 'day' for details about the year format.
62
74
quarter :: Parser Quarter
63
75
quarter = do
64
76
absOrNeg <- negate <$ char ' -' <|> id <$ char ' +' <|> pure id
65
- y <- (decimal <* char ' -' ) <|> fail " month must be of form [+,-]YYYY-MM"
77
+ y <- (year <* char ' -' ) <|> fail " month must be of form [+,-]YYYY-MM"
66
78
_ <- char ' q' <|> char ' Q'
67
79
q <- parseQ
68
80
return $! fromYearQuarter (absOrNeg y) q
@@ -72,6 +84,19 @@ quarter = do
72
84
<|> Q3 <$ char ' 3'
73
85
<|> Q4 <$ char ' 4'
74
86
87
+ -- | Parse a year @YYYY@, with at least 4 digits. Does not include any sign.
88
+ --
89
+ -- Note: 'Year' is a type synonym for 'Integer'.
90
+ --
91
+ -- @since 1.1.0.0
92
+ year :: Parser Year
93
+ year = do
94
+ ds <- takeWhile1 isDigit
95
+ if T. length ds < 4 then
96
+ fail " expected year with at least 4 digits"
97
+ else
98
+ pure (txtToInteger ds)
99
+
75
100
-- | Parse a two-digit integer (e.g. day of month, hour).
76
101
twoDigits :: Parser Int
77
102
twoDigits = do
@@ -172,3 +197,53 @@ zonedTime = Local.ZonedTime <$> localTime <*> (fromMaybe utc <$> timeZone)
172
197
173
198
utc :: Local. TimeZone
174
199
utc = Local. TimeZone 0 False " "
200
+
201
+ ------------------ Copy-pasted and adapted from base ------------------------
202
+
203
+ txtToInteger :: T. Text -> Integer
204
+ txtToInteger bs
205
+ | l > 40 = valInteger 10 l [ fromIntegral (ord w - 48 ) | w <- T. unpack bs ]
206
+ | otherwise = txtToIntegerSimple bs
207
+ where
208
+ l = T. length bs
209
+
210
+ txtToIntegerSimple :: T. Text -> Integer
211
+ txtToIntegerSimple = T. foldl' step 0 where
212
+ step a b = a * 10 + fromIntegral (ord b - 48 ) -- 48 = '0'
213
+
214
+ -- A sub-quadratic algorithm for Integer. Pairs of adjacent radix b
215
+ -- digits are combined into a single radix b^2 digit. This process is
216
+ -- repeated until we are left with a single digit. This algorithm
217
+ -- performs well only on large inputs, so we use the simple algorithm
218
+ -- for smaller inputs.
219
+ valInteger :: Integer -> Int -> [Integer ] -> Integer
220
+ valInteger = go
221
+ where
222
+ go :: Integer -> Int -> [Integer ] -> Integer
223
+ go _ _ [] = 0
224
+ go _ _ [d] = d
225
+ go b l ds
226
+ | l > 40 = b' `seq` go b' l' (combine b ds')
227
+ | otherwise = valSimple b ds
228
+ where
229
+ -- ensure that we have an even number of digits
230
+ -- before we call combine:
231
+ ds' = if even l then ds else 0 : ds
232
+ b' = b * b
233
+ l' = (l + 1 ) `quot` 2
234
+
235
+ combine b (d1 : d2 : ds) = d `seq` (d : combine b ds)
236
+ where
237
+ d = d1 * b + d2
238
+ combine _ [] = []
239
+ combine _ [_] = errorWithoutStackTrace " this should not happen"
240
+
241
+ -- The following algorithm is only linear for types whose Num operations
242
+ -- are in constant time.
243
+ valSimple :: Integer -> [Integer ] -> Integer
244
+ valSimple base = go 0
245
+ where
246
+ go r [] = r
247
+ go r (d : ds) = r' `seq` go r' ds
248
+ where
249
+ r' = r * base + fromIntegral d
0 commit comments