advent-of-code-api-0.2.0.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.API

Contents

Description

Raw Servant API for Advent of Code. Can be useful for building mock servers, generating documentation and other servanty things, or low-level raw requests.

If you use this to make requests directly, please use responsibly: do not make automated requests more than once per day and throttle all manual requestes. See notes in Advent.

Since: 0.2.0.0

Synopsis

Types

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
Bounded Day Source # 
Instance details

Defined in Advent.API

Methods

minBound :: Day #

maxBound :: Day #

Enum Day Source # 
Instance details

Defined in Advent.API

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

Methods

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

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

Ord Day Source # 
Instance details

Defined in Advent.API

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

Methods

showsPrec :: Int -> Day -> ShowS #

show :: Day -> String #

showList :: [Day] -> ShowS #

Generic Day Source # 
Instance details

Defined in Advent.API

Associated Types

type Rep Day :: Type -> Type #

Methods

from :: Day -> Rep Day x #

to :: Rep Day x -> Day #

FromJSON Day Source # 
Instance details

Defined in Advent.API

FromJSONKey Day Source # 
Instance details

Defined in Advent.API

ToHttpApiData Day Source # 
Instance details

Defined in Advent.API

type Rep Day Source # 
Instance details

Defined in Advent.API

type Rep Day = D1 (MetaData "Day" "Advent.API" "advent-of-code-api-0.2.0.0-9psdOTjm1cbBBNumE09bCX" True) (C1 (MetaCons "Day" PrefixI True) (S1 (MetaSel (Just "dayFinite") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Finite 25))))

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

Enum Part Source # 
Instance details

Defined in Advent.API

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

Methods

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

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

Ord Part Source # 
Instance details

Defined in Advent.API

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

Show Part Source # 
Instance details

Defined in Advent.API

Methods

showsPrec :: Int -> Part -> ShowS #

show :: Part -> String #

showList :: [Part] -> ShowS #

Generic Part Source # 
Instance details

Defined in Advent.API

Associated Types

type Rep Part :: Type -> Type #

Methods

from :: Part -> Rep Part x #

to :: Rep Part x -> Part #

FromJSON Part Source # 
Instance details

Defined in Advent.API

FromJSONKey Part Source # 
Instance details

Defined in Advent.API

ToHttpApiData Part Source # 
Instance details

Defined in Advent.API

type Rep Part Source # 
Instance details

Defined in Advent.API

type Rep Part = D1 (MetaData "Part" "Advent.API" "advent-of-code-api-0.2.0.0-9psdOTjm1cbBBNumE09bCX" False) (C1 (MetaCons "Part1" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Part2" PrefixI False) (U1 :: Type -> Type))

data SubmitInfo Source #

Info required to submit an answer for a part.

Constructors

SubmitInfo 

Fields

Instances
Eq SubmitInfo Source # 
Instance details

Defined in Advent.API

Ord SubmitInfo Source # 
Instance details

Defined in Advent.API

Read SubmitInfo Source # 
Instance details

Defined in Advent.API

Show SubmitInfo Source # 
Instance details

Defined in Advent.API

Generic SubmitInfo Source # 
Instance details

Defined in Advent.API

Associated Types

type Rep SubmitInfo :: Type -> Type #

ToForm SubmitInfo Source # 
Instance details

Defined in Advent.API

Methods

toForm :: SubmitInfo -> Form #

type Rep SubmitInfo Source # 
Instance details

Defined in Advent.API

type Rep SubmitInfo = D1 (MetaData "SubmitInfo" "Advent.API" "advent-of-code-api-0.2.0.0-9psdOTjm1cbBBNumE09bCX" False) (C1 (MetaCons "SubmitInfo" PrefixI True) (S1 (MetaSel (Just "siLevel") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Part) :*: S1 (MetaSel (Just "siAnswer") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))

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
Eq SubmitRes Source # 
Instance details

Defined in Advent.API

Ord SubmitRes Source # 
Instance details

Defined in Advent.API

Read SubmitRes Source # 
Instance details

Defined in Advent.API

Show SubmitRes Source # 
Instance details

Defined in Advent.API

Generic SubmitRes Source # 
Instance details

Defined in Advent.API

Associated Types

type Rep SubmitRes :: Type -> Type #

FromArticles SubmitRes Source # 
Instance details

Defined in Advent.API

type Rep SubmitRes Source # 
Instance details

Defined in Advent.API

newtype PublicCode Source #

Member ID of public leaderboard (the first part of the registration code, before the hyphen). It can be found as the number in the URL:

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

(the 12345 above)

Constructors

PublicCode 
Instances
Eq PublicCode Source # 
Instance details

Defined in Advent.API

Ord PublicCode Source # 
Instance details

Defined in Advent.API

Read PublicCode Source # 
Instance details

Defined in Advent.API

Show PublicCode Source # 
Instance details

Defined in Advent.API

Generic PublicCode Source # 
Instance details

Defined in Advent.API

Associated Types

type Rep PublicCode :: Type -> Type #

ToHttpApiData PublicCode Source # 
Instance details

Defined in Advent.API

type Rep PublicCode Source # 
Instance details

Defined in Advent.API

type Rep PublicCode = D1 (MetaData "PublicCode" "Advent.API" "advent-of-code-api-0.2.0.0-9psdOTjm1cbBBNumE09bCX" True) (C1 (MetaCons "PublicCode" PrefixI True) (S1 (MetaSel (Just "getPublicCode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer)))

data Leaderboard Source #

Leaderboard type, representing private leaderboard information.

Constructors

LB 

Fields

Instances
Eq Leaderboard Source # 
Instance details

Defined in Advent.API

Ord Leaderboard Source # 
Instance details

Defined in Advent.API

Show Leaderboard Source # 
Instance details

Defined in Advent.API

Generic Leaderboard Source # 
Instance details

Defined in Advent.API

Associated Types

type Rep Leaderboard :: Type -> Type #

FromJSON Leaderboard Source # 
Instance details

Defined in Advent.API

type Rep Leaderboard Source # 
Instance details

Defined in Advent.API

data LeaderboardMember Source #

Leaderboard position for a given member.

Constructors

LBM 

Fields

Instances
Eq LeaderboardMember Source # 
Instance details

Defined in Advent.API

Ord LeaderboardMember Source # 
Instance details

Defined in Advent.API

Show LeaderboardMember Source # 
Instance details

Defined in Advent.API

Generic LeaderboardMember Source # 
Instance details

Defined in Advent.API

Associated Types

type Rep LeaderboardMember :: Type -> Type #

FromJSON LeaderboardMember Source # 
Instance details

Defined in Advent.API

type Rep LeaderboardMember Source # 
Instance details

Defined in Advent.API

Servant API

type AdventAPI = Capture "year" Integer :> (("day" :> (Capture "day" Day :> (Get '[Articles] (Map Part Text) :<|> (("input" :> Get '[RawText] Text) :<|> ("answer" :> (ReqBody '[FormUrlEncoded] SubmitInfo :> Post '[Articles] (Text :<|> SubmitRes))))))) :<|> ("leaderboard" :> ("private" :> ("view" :> (Capture "code" PublicCode :> Get '[JSON] Leaderboard))))) Source #

REST API of Advent of Code.

Note that most of these requests assume a "session=" cookie.

adventAPI :: Proxy AdventAPI Source #

Proxy used for servant functions.

adventAPIPuzzleClient :: Integer -> Day -> ClientM (Map Part Text) :<|> (ClientM Text :<|> (SubmitInfo -> ClientM (Text :<|> SubmitRes))) Source #

A subset of adventAPIClient for only puzzle-related API routes, not leaderboard ones.

Util

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.

partInt :: Part -> Int Source #

Convert a Part to an Int.

partChar :: Part -> Char Source #

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

Internal

processHTML :: Text -> [Text] Source #

Process an HTML webpage into a list of all contents in articles

data Articles Source #

Interpret repsonse as a list of HTML Text in article tags.

class FromArticles a where Source #

Class for interpreting a list of Text in article tags to some desired output.

Methods

fromArticles :: [Text] -> a Source #

Instances
FromArticles Text Source # 
Instance details

Defined in Advent.API

Methods

fromArticles :: [Text] -> Text Source #

FromArticles SubmitRes Source # 
Instance details

Defined in Advent.API

FromArticles [Text] Source # 
Instance details

Defined in Advent.API

Methods

fromArticles :: [Text] -> [Text] Source #

(Ord a, Enum a, Bounded a) => FromArticles (Map a Text) Source # 
Instance details

Defined in Advent.API

Methods

fromArticles :: [Text] -> Map a Text Source #

(FromArticles a, FromArticles b) => FromArticles (a :<|> b) Source # 
Instance details

Defined in Advent.API

Methods

fromArticles :: [Text] -> a :<|> b Source #