9
9
{-# LANGUAGE RecordWildCards #-}
10
10
{-# LANGUAGE StandaloneDeriving #-}
11
11
{-# LANGUAGE TupleSections #-}
12
+
{-# LANGUAGE TypeApplications #-}
12
13
{-# LANGUAGE TypeInType #-}
13
14
{-# LANGUAGE ViewPatterns #-}
14
15
@@ -139,12 +140,20 @@ getAoCThrottleLimit = getLimit aocThrottler
139
140
data AoC :: Type -> Type where
140
141
-- | Fetch prompts for a given day. Returns a 'Map' of 'Part's and
141
142
-- their associated promps, as HTML.
143
+
--
144
+
-- _Cacheing rules_: Is cached on a per-day basis. An empty session
145
+
-- key is given, it will be happy with only having Part 1 cached. If
146
+
-- a non-empty session key is given, it will trigger a cache
147
+
-- invalidation on every request until both Part 1 and Part 2 are
148
+
-- received.
142
149
AoCPrompt
143
150
:: Day
144
151
-> AoC (Map Part Text)
145
152
146
153
-- | Fetch input, as plaintext. Returned verbatim. Be aware that
147
154
-- input might contain trailing newlines.
155
+
--
156
+
-- /Cacheing rules/: Is cached forever, per day per session key.
148
157
AoCInput :: Day -> AoC Text
149
158
150
159
-- | Submit a plaintext answer (the 'String') to a given day and part.
@@ -153,6 +162,8 @@ data AoC :: Type -> Type where
153
162
-- __WARNING__: Answers are not length-limited. Answers are stripped
154
163
-- of leading and trailing whitespace and run through 'URI.encode'
155
164
-- before submitting.
165
+
--
166
+
-- /Cacheing rules/: Is never cached.
156
167
AoCSubmit
157
168
:: Day
158
169
-> Part
@@ -175,6 +186,9 @@ data AoC :: Type -> Type where
175
186
-- you set up automation for this, please do not use it more than once
176
187
-- per day.
177
188
--
189
+
-- /Cacheing rules/: Is never cached, so please use responsibly (see
190
+
-- note above).
191
+
--
178
192
-- @since 0.2.0.0
179
193
AoCLeaderboard
180
194
:: Integer
@@ -187,7 +201,7 @@ data AoC :: Type -> Type where
187
201
-- when using this. If you automate this, please do not fetch any more
188
202
-- often than necessary.
189
203
--
190
-
-- Calls to this will be cached if a full leaderboard is observed.
204
+
-- /Cacheing rules/: Will be cached if a full leaderboard is observed.
191
205
--
192
206
-- @since 0.2.3.0
193
207
AoCDailyLeaderboard
@@ -201,7 +215,8 @@ data AoC :: Type -> Type where
201
215
-- when using this. If you automate this, please do not fetch any more
202
216
-- often than necessary.
203
217
--
204
-
-- Calls to this will be cached if fetched after each event ends.
218
+
-- /Cacheing rules/: Will not cache if an event is ongoing, but will be
219
+
-- cached if received after the event is over.
205
220
--
206
221
-- @since 0.2.3.0
207
222
AoCGlobalLeaderboard
@@ -345,7 +360,10 @@ runAoC AoCOpts{..} a = do
345
360
Just fp -> cacheing (cacheDir </> fp) $
346
361
if _aForce
347
362
then noCache
348
-
else saverLoader (not eventOver) a
363
+
else saverLoader
364
+
(not (null _aSessionKey))
365
+
(not eventOver)
366
+
a
349
367
350
368
cacher . runExceptT $ do
351
369
forM_ (aocDay a) $ \d -> do
@@ -390,10 +408,11 @@ aocClientEnv s = do
390
408
391
409
392
410
saverLoader
393
-
:: Bool -- ^ is the event ongoing (True) or over (False)?
411
+
:: Bool -- ^ is there a non-empty session token?
412
+
-> Bool -- ^ is the event ongoing (True) or over (False)?
394
413
-> AoC a
395
414
-> SaverLoader (Either AoCError a)
396
-
saverLoader evt = \case
415
+
saverLoader validToken evt = \case
397
416
AoCPrompt{} -> SL { _slSave = either (const Nothing) (Just . encodeMap)
398
417
, _slLoad = \str ->
399
418
let mp = decodeMap str
@@ -412,15 +431,20 @@ saverLoader evt = \case
412
431
guard $ fullDailyBoard r
413
432
pure $ Right r
414
433
}
415
-
AoCGlobalLeaderboard{}
416
-
| evt -> noCache
417
-
| otherwise -> SL
418
-
{ _slSave = either (const Nothing) (Just . TL.toStrict . TL.decodeUtf8 . A.encode)
419
-
, _slLoad = fmap Right . A.decode . TL.encodeUtf8 . TL.fromStrict
420
-
}
434
+
AoCGlobalLeaderboard{} -> SL
435
+
{ _slSave = either
436
+
(const Nothing)
437
+
(Just . TL.toStrict . TL.decodeUtf8 . A.encode @(Bool, GlobalLeaderboard) . (evt,))
438
+
, _slLoad = \str -> do
439
+
(evt', lb) <- A.decode @(Bool, GlobalLeaderboard) . TL.encodeUtf8 . TL.fromStrict $ str
440
+
guard $ not evt' -- only load cache if evt' is false: it was saved in a non-evt time
441
+
pure $ Right lb
442
+
}
421
443
where
422
444
expectedParts :: Set Part
423
-
expectedParts = S.fromDistinctAscList [Part1 ..]
445
+
expectedParts
446
+
| validToken = S.singleton Part1
447
+
| otherwise = S.fromDistinctAscList [Part1 ..]
424
448
sep = ">>>>>>>>>"
425
449
encodeMap mp = T.intercalate "\n" . concat $
426
450
[ maybeToList $ M.lookup Part1 mp
RetroSearch is an open source project built by @garambo | Open a GitHub Issue
Search and Browse the WWW like it's 1997 | Search results from DuckDuckGo
HTML:
3.2
| Encoding:
UTF-8
| Version:
0.7.4