advent-of-code-api-0.2.8.0: Advent of Code REST API bindings and servant API
Copyright(c) Justin Le 2019
LicenseBSD3
Maintainerjustin@jle.im
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Advent

Description

Haskell bindings for Advent of Code 2018 API. Caches and throttles requests automatically.

Specify your requests with AoC and AoCOpts, and run them with runAoC.

Examples:

-- Fetch prompts for day 5
runAoC myOpts $ AoCPrompt (mkDay_ 5)

-- Fetch input for day 8
runAoC myOpts $ AoCInput (mkDay_ 8)

-- Submit answer "hello" for Day 10, Part 1
runAoC myOpts $ AoCSubmit (mkDay_ 10) Part1 "hello"

Please use responsibly. All actions are by default rate limited to one per three seconds, but this can be adjusted to a hard-limited cap of one per second.

Synopsis

API

data AoC :: Type -> Type where Source #

An API command. An AoC a an AoC API request that returns results of type a.

A lot of these commands take Day, which represents a day of December up to and including Christmas Day (December 25th). You can convert an integer day (1 - 25) into a Day using mkDay or mkDay_.

Constructors

AoCPrompt :: Day -> AoC (Map Part Text)

Fetch prompts for a given day. Returns a Map of Parts and their associated promps, as HTML.

_Cacheing rules_: Is cached on a per-day basis. An empty session key is given, it will be happy with only having Part 1 cached. If a non-empty session key is given, it will trigger a cache invalidation on every request until both Part 1 and Part 2 are received.

AoCInput :: Day -> AoC Text

Fetch input, as plaintext. Returned verbatim. Be aware that input might contain trailing newlines.

Cacheing rules: Is cached forever, per day per session key.

AoCSubmit :: Day -> Part -> String -> AoC (Text, SubmitRes)

Submit a plaintext answer (the String) to a given day and part. Receive a server reponse (as HTML) and a response code SubmitRes.

WARNING: Answers are not length-limited. Answers are stripped of leading and trailing whitespace and run through encode before submitting.

Cacheing rules: Is never cached.

AoCLeaderboard :: Integer -> AoC Leaderboard

Fetch the leaderboard for a given leaderboard public code (owner member ID). Requires session key.

The public code can be found in the URL of the leaderboard:

https://adventofcode.com/2019/leaderboard/private/view/12345

(the 12345 above)

NOTE: This is the most expensive and taxing possible API call, and makes up the majority of bandwidth to the Advent of Code servers. As a courtesy to all who are participating in Advent of Code, please use this super respectfully, especially in December: if you set up automation for this, please do not use it more than once per day.

Cacheing rules: Is never cached, so please use responsibly (see note above).

Since: 0.2.0.0

AoCDailyLeaderboard :: Day -> AoC DailyLeaderboard

Fetch the daily leaderboard for a given day. Does not require a session key.

Leaderboard API calls tend to be expensive, so please be respectful when using this. If you automate this, please do not fetch any more often than necessary.

Cacheing rules: Will be cached if a full leaderboard is observed.

Since: 0.2.3.0

AoCGlobalLeaderboard :: AoC GlobalLeaderboard

Fetch the global leaderboard. Does not require a session key.

Leaderboard API calls tend to be expensive, so please be respectful when using this. If you automate this, please do not fetch any more often than necessary.

Cacheing rules: Will not cache if an event is ongoing, but will be cached if received after the event is over.

Since: 0.2.3.0

AoCNextDayTime :: AoC NextDayTime

From the calendar, fetch the next release's day and the number of seconds util its release, if there is any at all.

This does an actual request to the AoC servers, and is only accurate to the second; to infer this information (to the millisecond level) from the system clock, you should probably use timeToRelease and aocServerTime instead, which requires no network requests.

Since: 0.2.8.0

Instances

Instances details
Show (AoC a) Source # 
Instance details

Defined in Advent

Methods

showsPrec :: Int -> AoC a -> ShowS #

show :: AoC a -> String #

showList :: [AoC a] -> ShowS #

data Part Source #

A given part of a problem. All Advent of Code challenges are two-parts.

You can usually get Part1 (if it is already released) with a nonsense session key, but Part2 always requires a valid session key.

Constructors

Part1 
Part2 

Instances

Instances details
Bounded Part Source # 
Instance details

Defined in Advent.Types

Enum Part Source # 
Instance details

Defined in Advent.Types

Methods

succ :: Part -> Part #

pred :: Part -> Part #

toEnum :: Int -> Part #

fromEnum :: Part -> Int #

enumFrom :: Part -> [Part] #

enumFromThen :: Part -> Part -> [Part] #

enumFromTo :: Part -> Part -> [Part] #

enumFromThenTo :: Part -> Part -> Part -> [Part] #

Eq Part Source # 
Instance details

Defined in Advent.Types

Methods

(==) :: Part -> Part -> Bool #

(/=) :: Part -> Part -> Bool #

Ord Part Source # 
Instance details

Defined in Advent.Types

Methods

compare :: Part -> Part -> Ordering #

(<) :: Part -> Part -> Bool #

(<=) :: Part -> Part -> Bool #

(>) :: Part -> Part -> Bool #

(>=) :: Part -> Part -> Bool #

max :: Part -> Part -> Part #

min :: Part -> Part -> Part #

Read Part Source # 
Instance details

Defined in Advent.Types

Show Part Source # 
Instance details

Defined in Advent.Types

Methods

showsPrec :: Int -> Part -> ShowS #

show :: Part -> String #

showList :: [Part] -> ShowS #

Generic Part Source # 
Instance details

Defined in Advent.Types

Associated Types

type Rep Part :: Type -> Type #

Methods

from :: Part -> Rep Part x #

to :: Rep Part x -> Part #

ToJSON Part Source #

Since: 0.2.4.2

Instance details

Defined in Advent.Types

ToJSONKey Part Source #

Since: 0.2.4.2

Instance details

Defined in Advent.Types

FromJSON Part Source # 
Instance details

Defined in Advent.Types

FromJSONKey Part Source # 
Instance details

Defined in Advent.Types

ToHttpApiData Part Source # 
Instance details

Defined in Advent.Types

type Rep Part Source # 
Instance details

Defined in Advent.Types

type Rep Part = D1 ('MetaData "Part" "Advent.Types" "advent-of-code-api-0.2.8.0-inplace" 'False) (C1 ('MetaCons "Part1" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Part2" 'PrefixI 'False) (U1 :: Type -> Type))

newtype Day Source #

Describes the day: a number between 1 and 25 inclusive.

Represented by a Finite ranging from 0 to 24 inclusive; you should probably make one using the smart constructor mkDay.

Constructors

Day 

Fields

Instances

Instances details
Bounded Day Source # 
Instance details

Defined in Advent.Types

Methods

minBound :: Day #

maxBound :: Day #

Enum Day Source # 
Instance details

Defined in Advent.Types

Methods

succ :: Day -> Day #

pred :: Day -> Day #

toEnum :: Int -> Day #

fromEnum :: Day -> Int #

enumFrom :: Day -> [Day] #

enumFromThen :: Day -> Day -> [Day] #

enumFromTo :: Day -> Day -> [Day] #

enumFromThenTo :: Day -> Day -> Day -> [Day] #

Eq Day Source # 
Instance details

Defined in Advent.Types

Methods

(==) :: Day -> Day -> Bool #

(/=) :: Day -> Day -> Bool #

Ord Day Source # 
Instance details

Defined in Advent.Types

Methods

compare :: Day -> Day -> Ordering #

(<) :: Day -> Day -> Bool #

(<=) :: Day -> Day -> Bool #

(>) :: Day -> Day -> Bool #

(>=) :: Day -> Day -> Bool #

max :: Day -> Day -> Day #

min :: Day -> Day -> Day #

Show Day Source # 
Instance details

Defined in Advent.Types

Methods

showsPrec :: Int -> Day -> ShowS #

show :: Day -> String #

showList :: [Day] -> ShowS #

Generic Day Source # 
Instance details

Defined in Advent.Types

Associated Types

type Rep Day :: Type -> Type #

Methods

from :: Day -> Rep Day x #

to :: Rep Day x -> Day #

ToJSON Day Source #

Since: 0.2.4.2

Instance details

Defined in Advent.Types

ToJSONKey Day Source #

Since: 0.2.4.2

Instance details

Defined in Advent.Types

FromJSON Day Source # 
Instance details

Defined in Advent.Types

FromJSONKey Day Source # 
Instance details

Defined in Advent.Types

ToHttpApiData Day Source # 
Instance details

Defined in Advent.Types

type Rep Day Source # 
Instance details

Defined in Advent.Types

type Rep Day = D1 ('MetaData "Day" "Advent.Types" "advent-of-code-api-0.2.8.0-inplace" 'True) (C1 ('MetaCons "Day" 'PrefixI 'True) (S1 ('MetaSel ('Just "dayFinite") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Finite 25))))

data NextDayTime Source #

The next day for a challenge in a given year, and also the number of seconds until the challenge is released.

Since: 0.2.8.0

Instances

Instances details
Eq NextDayTime Source # 
Instance details

Defined in Advent.Types

Ord NextDayTime Source # 
Instance details

Defined in Advent.Types

Show NextDayTime Source # 
Instance details

Defined in Advent.Types

Generic NextDayTime Source # 
Instance details

Defined in Advent.Types

Associated Types

type Rep NextDayTime :: Type -> Type #

FromTags "script" NextDayTime Source # 
Instance details

Defined in Advent.API

Methods

fromTags :: p "script" -> [Text] -> Maybe NextDayTime Source #

type Rep NextDayTime Source # 
Instance details

Defined in Advent.Types

type Rep NextDayTime = D1 ('MetaData "NextDayTime" "Advent.Types" "advent-of-code-api-0.2.8.0-inplace" 'False) (C1 ('MetaCons "NextDayTime" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Day) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: C1 ('MetaCons "NoNextDayTime" 'PrefixI 'False) (U1 :: Type -> Type))

data AoCOpts Source #

Setings for running an API request.

Session keys are required for all commands, but if you enter a bogus key you should be able to get at least Part 1 from AoCPrompt.

The session key can be found by logging in on a web client and checking the cookies. You can usually check these with in-browser developer tools.

Throttling is hard-limited to a minimum of 1 second between calls. Please be respectful and do not try to bypass this.

Constructors

AoCOpts 

Fields

Instances

Instances details
Show AoCOpts Source # 
Instance details

Defined in Advent

Generic AoCOpts Source # 
Instance details

Defined in Advent

Associated Types

type Rep AoCOpts :: Type -> Type #

Methods

from :: AoCOpts -> Rep AoCOpts x #

to :: Rep AoCOpts x -> AoCOpts #

type Rep AoCOpts Source # 
Instance details

Defined in Advent

data SubmitRes Source #

The result of a submission.

Constructors

SubCorrect (Maybe Integer)

Correct submission, including global rank (if reported, which usually happens if rank is under 1000)

SubIncorrect Int (Maybe String)

Incorrect submission. Contains the number of seconds you must wait before trying again. The Maybe contains possible hints given by the server (usually "too low" or "too high").

SubWait Int

Submission was rejected because an incorrect submission was recently submitted. Contains the number of seconds you must wait before trying again.

SubInvalid

Submission was rejected because it was sent to an invalid question or part. Usually happens if you submit to a part you have already answered or have not yet unlocked.

SubUnknown String

Could not parse server response. Contains parse error.

Instances

Instances details
Eq SubmitRes Source # 
Instance details

Defined in Advent.Types

Ord SubmitRes Source # 
Instance details

Defined in Advent.Types

Read SubmitRes Source # 
Instance details

Defined in Advent.Types

Show SubmitRes Source # 
Instance details

Defined in Advent.Types

Generic SubmitRes Source # 
Instance details

Defined in Advent.Types

Associated Types

type Rep SubmitRes :: Type -> Type #

FromTags "article" SubmitRes Source # 
Instance details

Defined in Advent.API

Methods

fromTags :: p "article" -> [Text] -> Maybe SubmitRes Source #

type Rep SubmitRes Source # 
Instance details

Defined in Advent.Types

runAoC :: AoCOpts -> AoC a -> IO (Either AoCError a) Source #

Run an AoC command with a given AoCOpts to produce the result or a list of (lines of) errors.

WARNING: Answers are not length-limited. Answers are stripped of leading and trailing whitespace and run through encode before submitting.

runAoC_ :: AoCOpts -> AoC a -> IO a Source #

A version of runAoC that throws an IO exception (of type AoCError) upon failure, instead of an Either.

Since: 0.2.5.0

defaultAoCOpts :: Integer -> String -> AoCOpts Source #

Sensible defaults for AoCOpts for a given year and session key.

Use system temporary directory as cache, and throttle requests to one request per three seconds.

data AoCError Source #

A possible (syncronous, logical, pure) error returnable from runAoC. Does not cover any asynchronous or IO errors.

Constructors

AoCClientError ClientError

An error in the http request itself

Note that if you are building this with servant-client-core <= 0.16, this will contain ServantError instead of ClientError, which was the previous name of ths type.

AoCReleaseError NominalDiffTime

Tried to interact with a challenge that has not yet been released. Contains the amount of time until release.

AoCThrottleError

The throttler limit is full. Either make less requests, or adjust it with setAoCThrottleLimit.

Instances

Instances details
Show AoCError Source # 
Instance details

Defined in Advent

Generic AoCError Source # 
Instance details

Defined in Advent

Associated Types

type Rep AoCError :: Type -> Type #

Methods

from :: AoCError -> Rep AoCError x #

to :: Rep AoCError x -> AoCError #

Exception AoCError Source # 
Instance details

Defined in Advent

type Rep AoCError Source # 
Instance details

Defined in Advent

type Rep AoCError = D1 ('MetaData "AoCError" "Advent" "advent-of-code-api-0.2.8.0-inplace" 'False) (C1 ('MetaCons "AoCClientError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ClientError)) :+: (C1 ('MetaCons "AoCReleaseError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NominalDiffTime)) :+: C1 ('MetaCons "AoCThrottleError" 'PrefixI 'False) (U1 :: Type -> Type)))

Calendar

challengeReleaseTime Source #

Arguments

:: Integer

year

-> Day

day

-> ZonedTime 

Prompt release time.

Changed from UTCTime to ZonedTime in v0.2.7.0. To use as a UTCTime, use zonedTimeToUTC.

timeToRelease Source #

Arguments

:: Integer

year

-> Day

day

-> IO NominalDiffTime 

Get time until release of a given challenge.

challengeReleased Source #

Arguments

:: Integer

year

-> Day

day

-> IO Bool 

Check if a challenge has been released yet.

Utility

Day

mkDay :: Integer -> Maybe Day Source #

Construct a Day from a day integer (1 - 25). If input is out of range, Nothing is returned. See mkDay_ for an unsafe version useful for literals.

Inverse of dayInt.

mkDay_ :: Integer -> Day Source #

Construct a Finite 25 (the type of a Day) from a day integer (1 - 25). Is undefined if input is out of range. Can be useful for compile-time literals, like mkDay_ 4

Inverse of dayInt.

dayInt :: Day -> Integer Source #

Convert a Finite 25 day into a day integer (1 - 25). Inverse of mkDay.

pattern DayInt :: Day -> Integer Source #

Pattern synonym allowing you to match on an Integer as if it were a Day:

case myInt of
  DayInt d -> ...
  _        -> ...

Will fail if the integer is out of bounds (outside of 1-25)

Since: 0.2.4.0

_DayInt :: (Choice p, Applicative f) => p Day (f Day) -> p Integer (f Integer) Source #

This is a Prism' Integer Day , to treat an Integer as if it were a Day.

Since: 0.2.4.0

aocDay :: AoC a -> Maybe Day Source #

Get the day associated with a given API command, if there is one.

aocServerTime :: IO LocalTime Source #

Utility to get the current time on AoC servers. Basically just gets the current time in Eastern Standard Time. This is only as accurate as your machine's actual time --- it doesn't actually do anything networked.

Since: 0.2.6.0

Part

partChar :: Part -> Char Source #

A character associated with a given part. Part1 is associated with 'a', and Part2 is associated with 'b'

partInt :: Part -> Int Source #

Convert a Part to an Int.

Leaderboard

fullDailyBoard :: DailyLeaderboard -> Bool Source #

Check if a DailyLeaderboard is filled up or not.

Since: 0.2.4.0

Throttler

setAoCThrottleLimit :: Int -> IO () Source #

Set the internal throttler maximum queue capacity. Default is 100.

getAoCThrottleLimit :: IO Int Source #

Get the internal throttler maximum queue capacity.

Internal

aocReq :: Integer -> AoC a -> ClientM a Source #

ClientM request for a given AoC API call.

aocBase :: BaseUrl Source #

HTTPS base of Advent of Code API.