| Copyright | (c) Justin Le 2019 |
|---|---|
| License | BSD3 |
| Maintainer | justin@jle.im |
| Stability | experimental |
| Portability | non-portable |
| Safe Haskell | None |
| Language | Haskell2010 |
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
- newtype Day = Day {}
- data Part
- data SubmitInfo = SubmitInfo {}
- data SubmitRes
- = SubCorrect (Maybe Integer)
- | SubIncorrect Int (Maybe String)
- | SubWait Int
- | SubInvalid
- | SubUnknown String
- showSubmitRes :: SubmitRes -> String
- newtype PublicCode = PublicCode {}
- data Leaderboard = LB {}
- data LeaderboardMember = LBM {
- lbmGlobalScore :: Integer
- lbmName :: Maybe Text
- lbmLocalScore :: Integer
- lbmId :: Integer
- lbmLastStarTS :: Maybe UTCTime
- lbmStars :: Int
- lbmCompletion :: Map Day (Map Part UTCTime)
- 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)))))
- adventAPI :: Proxy AdventAPI
- adventAPIClient :: Integer -> (Day -> ClientM (Map Part Text) :<|> (ClientM Text :<|> (SubmitInfo -> ClientM (Text :<|> SubmitRes)))) :<|> (PublicCode -> ClientM Leaderboard)
- adventAPIPuzzleClient :: Integer -> Day -> ClientM (Map Part Text) :<|> (ClientM Text :<|> (SubmitInfo -> ClientM (Text :<|> SubmitRes)))
- mkDay :: Integer -> Maybe Day
- mkDay_ :: Integer -> Day
- dayInt :: Day -> Integer
- partInt :: Part -> Int
- partChar :: Part -> Char
- processHTML :: Text -> [Text]
- parseSubmitRes :: Text -> SubmitRes
- data Articles
- class FromArticles a where
- fromArticles :: [Text] -> a
- data RawText
Types
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.
Instances
| Bounded Day Source # | |
| Enum Day Source # | |
| Eq Day Source # | |
| Ord Day Source # | |
| Show Day Source # | |
| Generic Day Source # | |
| FromJSON Day Source # | |
| FromJSONKey Day Source # | |
Defined in Advent.API | |
| ToHttpApiData Day Source # | |
Defined in Advent.API Methods toUrlPiece :: Day -> Text # toEncodedUrlPiece :: Day -> Builder # toHeader :: Day -> ByteString # toQueryParam :: Day -> Text # | |
| type Rep Day Source # | |
Defined in Advent.API | |
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.
Instances
| Bounded Part Source # | |
| Enum Part Source # | |
| Eq Part Source # | |
| Ord Part Source # | |
| Read Part Source # | |
| Show Part Source # | |
| Generic Part Source # | |
| FromJSON Part Source # | |
| FromJSONKey Part Source # | |
Defined in Advent.API | |
| ToHttpApiData Part Source # | |
Defined in Advent.API Methods toUrlPiece :: Part -> Text # toEncodedUrlPiece :: Part -> Builder # toHeader :: Part -> ByteString # toQueryParam :: Part -> Text # | |
| type Rep Part Source # | |
data SubmitInfo Source #
Info required to submit an answer for a part.
Constructors
| SubmitInfo | |
Instances
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 |
| 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
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 | |
Fields | |
Instances
data Leaderboard Source #
Leaderboard type, representing private leaderboard information.
Constructors
| LB | |
Instances
data LeaderboardMember Source #
Leaderboard position for a given member.
Constructors
| LBM | |
Fields
| |
Instances
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.
adventAPIClient :: Integer -> (Day -> ClientM (Map Part Text) :<|> (ClientM Text :<|> (SubmitInfo -> ClientM (Text :<|> SubmitRes)))) :<|> (PublicCode -> ClientM Leaderboard) Source #
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
Internal
processHTML :: Text -> [Text] Source #
Process an HTML webpage into a list of all contents in articles
Instances
| Accept Articles Source # | |
Defined in Advent.API | |
| FromArticles a => MimeUnrender Articles a Source # | |
Defined in Advent.API Methods mimeUnrender :: Proxy Articles -> ByteString -> Either String a # mimeUnrenderWithType :: Proxy Articles -> MediaType -> ByteString -> Either String a # | |
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 # | |
Defined in Advent.API Methods fromArticles :: [Text] -> Text Source # | |
| FromArticles SubmitRes Source # | |
Defined in Advent.API Methods fromArticles :: [Text] -> SubmitRes Source # | |
| FromArticles [Text] Source # | |
Defined in Advent.API Methods fromArticles :: [Text] -> [Text] Source # | |
| (Ord a, Enum a, Bounded a) => FromArticles (Map a Text) Source # | |
Defined in Advent.API | |
| (FromArticles a, FromArticles b) => FromArticles (a :<|> b) Source # | |
Defined in Advent.API Methods fromArticles :: [Text] -> a :<|> b Source # | |
Raw "text/plain" MIME type
Instances
| Accept RawText Source # | |
Defined in Advent.API | |
| MimeUnrender RawText Text Source # | |
Defined in Advent.API Methods mimeUnrender :: Proxy RawText -> ByteString -> Either String Text # mimeUnrenderWithType :: Proxy RawText -> MediaType -> ByteString -> Either String Text # | |