Copyright | (c) Denis Shevchenko, 2016 |
---|---|
License | MIT |
Maintainer | me@dshevchenko.biz |
Stability | alpha |
Safe Haskell | None |
Language | Haskell2010 |
API calls for work with User info.
- getUserInfo :: CircleCIResponse UserInfo
- data UserInfo = UserInfo {
- inBetaProgram :: Bool
- fullName :: Text
- allEmails :: [Text]
- defaultEmail :: Text
- basicEmailPreference :: EmailNotification
- gitHubAvatarUrl :: Text
- gitHubId :: Integer
- gitHubLogin :: Text
- gitHubOAuthScopes :: [GitHubOAuth]
- accountCreatedAt :: UTCTime
- trialEndDate :: UTCTime
- plan :: Plan
- parallelism :: Int
- containtersNumber :: Int
- projects :: [ProjectShortInfo]
- analyticsId :: AnalyticsId
- pusherId :: Text
- herokuAPIKey :: Maybe Text
- data ProjectShortInfo = ProjectShortInfo {}
- data EmailNotification
- data Plan
- data GitHubOAuth
- type AnalyticsId = Text
- module CircleCI.Common.Types
- module CircleCI.Common.Run
API call
:: CircleCIResponse UserInfo | Info about the signed in user. |
Show info about user. Based on https://circleci.com/docs/api/#user.
Usage example:
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE LambdaCase #-} import CircleCI main :: IO () main = runCircleCI getUserInfo (AccountAPIToken "e64c674195bbc0d0be3efa2whatever") >>= \case Left problem -> print problem Right info -> print info
Types for calls and response
Info about user.
UserInfo | |
|
data ProjectShortInfo Source
Short info about the project.
ProjectShortInfo | |
|
data EmailNotification Source
Email notification preference.
CircleCI plan. For more info please see https://circleci.com/pricing/.
type AnalyticsId = Text Source
User's analytics id. For example, "6fc20e13-008e-4dc9-b158-ababd33a099d"
.
module CircleCI.Common.Types
module CircleCI.Common.Run