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

Advent.Types

Description

Data types used for the underlying API.

Since: 0.2.3.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

Instances details
FromJSON Day Source # 
Instance details

Defined in Advent.Types

FromJSONKey Day Source # 
Instance details

Defined in Advent.Types

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

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

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 #

Show Day Source # 
Instance details

Defined in Advent.Types

Methods

showsPrec :: Int -> Day -> ShowS #

show :: Day -> String #

showList :: [Day] -> ShowS #

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 #

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.2-IdxVEjTVN4P5hqyJVxgQ9S" '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.

Constructors

Part1 
Part2 

Instances

Instances details
FromJSON Part Source # 
Instance details

Defined in Advent.Types

FromJSONKey Part Source # 
Instance details

Defined in Advent.Types

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

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

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 #

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 #

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 #

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.2-IdxVEjTVN4P5hqyJVxgQ9S" '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

Instances details
Generic SubmitInfo Source # 
Instance details

Defined in Advent.Types

Associated Types

type Rep SubmitInfo :: Type -> Type #

Read SubmitInfo Source # 
Instance details

Defined in Advent.Types

Show SubmitInfo Source # 
Instance details

Defined in Advent.Types

Eq SubmitInfo Source # 
Instance details

Defined in Advent.Types

Ord SubmitInfo Source # 
Instance details

Defined in Advent.Types

ToForm SubmitInfo Source # 
Instance details

Defined in Advent.Types

Methods

toForm :: SubmitInfo -> Form #

type Rep SubmitInfo Source # 
Instance details

Defined in Advent.Types

type Rep SubmitInfo = D1 ('MetaData "SubmitInfo" "Advent.Types" "advent-of-code-api-0.2.8.2-IdxVEjTVN4P5hqyJVxgQ9S" '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

Instances details
Generic SubmitRes Source # 
Instance details

Defined in Advent.Types

Associated Types

type Rep SubmitRes :: Type -> Type #

Read SubmitRes Source # 
Instance details

Defined in Advent.Types

Show SubmitRes Source # 
Instance details

Defined in Advent.Types

Eq SubmitRes Source # 
Instance details

Defined in Advent.Types

Ord SubmitRes Source # 
Instance details

Defined in Advent.Types

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

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

Instances details
Generic PublicCode Source # 
Instance details

Defined in Advent.Types

Associated Types

type Rep PublicCode :: Type -> Type #

Read PublicCode Source # 
Instance details

Defined in Advent.Types

Show PublicCode Source # 
Instance details

Defined in Advent.Types

Eq PublicCode Source # 
Instance details

Defined in Advent.Types

Ord PublicCode Source # 
Instance details

Defined in Advent.Types

ToHttpApiData PublicCode Source # 
Instance details

Defined in Advent.Types

type Rep PublicCode Source # 
Instance details

Defined in Advent.Types

type Rep PublicCode = D1 ('MetaData "PublicCode" "Advent.Types" "advent-of-code-api-0.2.8.2-IdxVEjTVN4P5hqyJVxgQ9S" '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

Instances details
FromJSON Leaderboard Source # 
Instance details

Defined in Advent.Types

Generic Leaderboard Source # 
Instance details

Defined in Advent.Types

Associated Types

type Rep Leaderboard :: Type -> Type #

Show Leaderboard Source # 
Instance details

Defined in Advent.Types

Eq Leaderboard Source # 
Instance details

Defined in Advent.Types

Ord Leaderboard Source # 
Instance details

Defined in Advent.Types

type Rep Leaderboard Source # 
Instance details

Defined in Advent.Types

type Rep Leaderboard = D1 ('MetaData "Leaderboard" "Advent.Types" "advent-of-code-api-0.2.8.2-IdxVEjTVN4P5hqyJVxgQ9S" 'False) (C1 ('MetaCons "LB" 'PrefixI 'True) (S1 ('MetaSel ('Just "lbEvent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer) :*: (S1 ('MetaSel ('Just "lbOwnerId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "lbMembers") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Integer LeaderboardMember)))))

data LeaderboardMember Source #

Leaderboard position for a given member.

Constructors

LBM 

Fields

Instances

Instances details
FromJSON LeaderboardMember Source # 
Instance details

Defined in Advent.Types

Generic LeaderboardMember Source # 
Instance details

Defined in Advent.Types

Associated Types

type Rep LeaderboardMember :: Type -> Type #

Show LeaderboardMember Source # 
Instance details

Defined in Advent.Types

Eq LeaderboardMember Source # 
Instance details

Defined in Advent.Types

Ord LeaderboardMember Source # 
Instance details

Defined in Advent.Types

type Rep LeaderboardMember Source # 
Instance details

Defined in Advent.Types

newtype Rank Source #

Ranking between 1 to 100, for daily and global leaderboards

Note that getRank interanlly stores a number from 0 to 99, so be sure to add or subtract accordingly if you want to display or parse it.

Since: 0.2.3.0

Constructors

Rank 

Fields

Instances

Instances details
FromJSON Rank Source # 
Instance details

Defined in Advent.Types

FromJSONKey Rank Source # 
Instance details

Defined in Advent.Types

ToJSON Rank Source # 
Instance details

Defined in Advent.Types

ToJSONKey Rank Source # 
Instance details

Defined in Advent.Types

Generic Rank Source # 
Instance details

Defined in Advent.Types

Associated Types

type Rep Rank :: Type -> Type #

Methods

from :: Rank -> Rep Rank x #

to :: Rep Rank x -> Rank #

Show Rank Source # 
Instance details

Defined in Advent.Types

Methods

showsPrec :: Int -> Rank -> ShowS #

show :: Rank -> String #

showList :: [Rank] -> ShowS #

Eq Rank Source # 
Instance details

Defined in Advent.Types

Methods

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

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

Ord Rank Source # 
Instance details

Defined in Advent.Types

Methods

compare :: Rank -> Rank -> Ordering #

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

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

(>) :: Rank -> Rank -> Bool #

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

max :: Rank -> Rank -> Rank #

min :: Rank -> Rank -> Rank #

type Rep Rank Source # 
Instance details

Defined in Advent.Types

type Rep Rank = D1 ('MetaData "Rank" "Advent.Types" "advent-of-code-api-0.2.8.2-IdxVEjTVN4P5hqyJVxgQ9S" 'True) (C1 ('MetaCons "Rank" 'PrefixI 'True) (S1 ('MetaSel ('Just "getRank") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Finite 100))))

data DailyLeaderboard Source #

Daily leaderboard, containing Star 1 and Star 2 completions

Since: 0.2.3.0

Instances

Instances details
FromJSON DailyLeaderboard Source # 
Instance details

Defined in Advent.Types

ToJSON DailyLeaderboard Source # 
Instance details

Defined in Advent.Types

Generic DailyLeaderboard Source # 
Instance details

Defined in Advent.Types

Associated Types

type Rep DailyLeaderboard :: Type -> Type #

Show DailyLeaderboard Source # 
Instance details

Defined in Advent.Types

Eq DailyLeaderboard Source # 
Instance details

Defined in Advent.Types

Ord DailyLeaderboard Source # 
Instance details

Defined in Advent.Types

FromTags "div" DailyLeaderboard Source # 
Instance details

Defined in Advent.API

Methods

fromTags :: p "div" -> [Text] -> Maybe DailyLeaderboard Source #

type Rep DailyLeaderboard Source # 
Instance details

Defined in Advent.Types

type Rep DailyLeaderboard = D1 ('MetaData "DailyLeaderboard" "Advent.Types" "advent-of-code-api-0.2.8.2-IdxVEjTVN4P5hqyJVxgQ9S" 'False) (C1 ('MetaCons "DLB" 'PrefixI 'True) (S1 ('MetaSel ('Just "dlbStar1") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Rank DailyLeaderboardMember)) :*: S1 ('MetaSel ('Just "dlbStar2") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Rank DailyLeaderboardMember))))

data DailyLeaderboardMember Source #

Single daily leaderboard position

Since: 0.2.3.0

Constructors

DLBM 

Fields

Instances

Instances details
FromJSON DailyLeaderboardMember Source # 
Instance details

Defined in Advent.Types

ToJSON DailyLeaderboardMember Source # 
Instance details

Defined in Advent.Types

Generic DailyLeaderboardMember Source # 
Instance details

Defined in Advent.Types

Associated Types

type Rep DailyLeaderboardMember :: Type -> Type #

Show DailyLeaderboardMember Source # 
Instance details

Defined in Advent.Types

Eq DailyLeaderboardMember Source # 
Instance details

Defined in Advent.Types

Ord DailyLeaderboardMember Source # 
Instance details

Defined in Advent.Types

type Rep DailyLeaderboardMember Source # 
Instance details

Defined in Advent.Types

newtype GlobalLeaderboard Source #

Global leaderboard for the entire event

Under each Rank is an Integer for the score at that rank, as well as a non-empty list of all members who achieved that rank and score.

Since: 0.2.3.0

Instances

Instances details
FromJSON GlobalLeaderboard Source # 
Instance details

Defined in Advent.Types

ToJSON GlobalLeaderboard Source # 
Instance details

Defined in Advent.Types

Generic GlobalLeaderboard Source # 
Instance details

Defined in Advent.Types

Associated Types

type Rep GlobalLeaderboard :: Type -> Type #

Show GlobalLeaderboard Source # 
Instance details

Defined in Advent.Types

Eq GlobalLeaderboard Source # 
Instance details

Defined in Advent.Types

Ord GlobalLeaderboard Source # 
Instance details

Defined in Advent.Types

FromTags "div" GlobalLeaderboard Source # 
Instance details

Defined in Advent.API

Methods

fromTags :: p "div" -> [Text] -> Maybe GlobalLeaderboard Source #

type Rep GlobalLeaderboard Source # 
Instance details

Defined in Advent.Types

type Rep GlobalLeaderboard = D1 ('MetaData "GlobalLeaderboard" "Advent.Types" "advent-of-code-api-0.2.8.2-IdxVEjTVN4P5hqyJVxgQ9S" 'True) (C1 ('MetaCons "GLB" 'PrefixI 'True) (S1 ('MetaSel ('Just "glbMap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Rank (Integer, NonEmpty GlobalLeaderboardMember)))))

data GlobalLeaderboardMember Source #

Single global leaderboard position

Since: 0.2.3.0

Instances

Instances details
FromJSON GlobalLeaderboardMember Source # 
Instance details

Defined in Advent.Types

ToJSON GlobalLeaderboardMember Source # 
Instance details

Defined in Advent.Types

Generic GlobalLeaderboardMember Source # 
Instance details

Defined in Advent.Types

Associated Types

type Rep GlobalLeaderboardMember :: Type -> Type #

Show GlobalLeaderboardMember Source # 
Instance details

Defined in Advent.Types

Eq GlobalLeaderboardMember Source # 
Instance details

Defined in Advent.Types

Ord GlobalLeaderboardMember Source # 
Instance details

Defined in Advent.Types

type Rep GlobalLeaderboardMember Source # 
Instance details

Defined in Advent.Types

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
Generic NextDayTime Source # 
Instance details

Defined in Advent.Types

Associated Types

type Rep NextDayTime :: Type -> Type #

Show NextDayTime Source # 
Instance details

Defined in Advent.Types

Eq NextDayTime Source # 
Instance details

Defined in Advent.Types

Ord NextDayTime Source # 
Instance details

Defined in Advent.Types

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.2-IdxVEjTVN4P5hqyJVxgQ9S" '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))

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.

_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

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

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'

fullDailyBoard :: DailyLeaderboard -> Bool Source #

Check if a DailyLeaderboard is filled up or not.

Since: 0.2.4.0

dlbmCompleteTime :: Integer -> Day -> NominalDiffTime -> ZonedTime Source #

Turn a dlbmDecTime field into a ZonedTime for the actual completion of the puzzle, based on the year and day of event.

Since: 0.2.7.0

dlbmTime :: Day -> NominalDiffTime -> NominalDiffTime Source #

Turn a dlbmDecTime field into a NominalDiffTime representing the actual amount of time taken to complete the puzzle.

Since: 0.2.7.0

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.

Internal