advent-of-code-api-0.1.0.0: Advent of Code REST API bindings

Copyright(c) Justin Le 2018
LicenseBSD3
Maintainerjustin@jle.im
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Advent

Contents

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.

Note that leaderboard API is not yet supported.

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 Finite 25, which represents a day of December up to and including Christmas Day (December 25th). You can convert an integer day (1 - 25) into a Finite 25 representing that day using mkDay or mkDay_.

Constructors

AoCPrompt :: Finite 25 -> AoC (Map Part Text)

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

AoCInput :: Finite 25 -> AoC Text

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

AoCSubmit :: Finite 25 -> 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.

Instances
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.

Note also that Challenge #25 typically only has a single part.

Constructors

Part1 
Part2 
Instances
Bounded Part Source # 
Instance details

Defined in Advent

Enum Part Source # 
Instance details

Defined in Advent

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

Methods

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

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

Ord Part Source # 
Instance details

Defined in Advent

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

Show Part Source # 
Instance details

Defined in Advent

Methods

showsPrec :: Int -> Part -> ShowS #

show :: Part -> String #

showList :: [Part] -> ShowS #

Generic Part Source # 
Instance details

Defined in Advent

Associated Types

type Rep Part :: Type -> Type #

Methods

from :: Part -> Rep Part x #

to :: Rep Part x -> Part #

type Rep Part Source # 
Instance details

Defined in Advent

type Rep Part = D1 (MetaData "Part" "Advent" "advent-of-code-api-0.1.0.0-inplace" False) (C1 (MetaCons "Part1" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Part2" 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

  • _aSessionKey :: String

    Session key

  • _aYear :: Integer

    Year of challenge

  • _aCache :: Maybe FilePath

    Cache directory. If Nothing is given, one will be allocated using getTemporaryDirectory.

  • _aForce :: Bool

    Fetch results even if cached. Still subject to throttling. Default is False.

  • _aThrottle :: Int

    Throttle delay, in milliseconds. Minimum is 1000000. Default is 3000000 (3 seconds).

  • _aCurlOpts :: [CurlOption]

    (Low-level usage) Extra CurlOption options to feed to the libcurl bindings. Meant for things like proxy options and custom SSL certificates. You should normally not have to add anything here, since the library manages cookies, request methods, etc. for you. Anything other than tweaking low-level network options (like the ones mentioned previously) will likely break everything. Default is [].

Instances
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

Incorrect submission. Check response text for hints (often, "too high" or "too low"), and also for the wait time required before the next submission.

SubWait

Submission was rejected because an incorrect submission was recently submitted. Check response text for wait time.

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

Could not parse server response.

Instances
Eq SubmitRes Source # 
Instance details

Defined in Advent

Ord SubmitRes Source # 
Instance details

Defined in Advent

Show SubmitRes Source # 
Instance details

Defined in Advent

Generic SubmitRes Source # 
Instance details

Defined in Advent

Associated Types

type Rep SubmitRes :: Type -> Type #

type Rep SubmitRes Source # 
Instance details

Defined in Advent

type Rep SubmitRes = D1 (MetaData "SubmitRes" "Advent" "advent-of-code-api-0.1.0.0-inplace" False) ((C1 (MetaCons "SubCorrect" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Integer))) :+: C1 (MetaCons "SubIncorrect" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "SubWait" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "SubInvalid" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SubUnknown" PrefixI False) (U1 :: Type -> Type))))

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.

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

AoCCurlError CurlCode String

A libcurl error, with response code and response body

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
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

Calendar

challengeReleaseTime Source #

Arguments

:: Integer

year

-> Finite 25

day

-> UTCTime 

Prompt release time

timeToRelease Source #

Arguments

:: Integer

year

-> Finite 25

day

-> IO NominalDiffTime 

Get time until release of a given challenge.

challengeReleased Source #

Arguments

:: Integer

year

-> Finite 25

day

-> IO Bool 

Check if a challenge has been released yet.

Utility

Day

mkDay :: Integer -> Maybe (Finite 25) Source #

Construct a Finite 25 (the type of 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 -> Finite 25 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 :: Finite 25 -> Integer Source #

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

aocDay :: AoC a -> Finite 25 Source #

Get the day associated with a given API command.

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.

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