circlehs-0.0.2: The CircleCI REST API for Haskell

Copyright(c) Denis Shevchenko, 2016
LicenseMIT
Maintainerme@dshevchenko.biz
Stabilityalpha
Safe HaskellNone
LanguageHaskell2010

Network.CircleCI.User

Contents

Description

API calls for work with User info.

Synopsis

API call

getUserInfo Source

Arguments

:: 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 Network.CircleCI

main :: IO ()
main = runCircleCI getUserInfo
                   (AccountAPIToken "e64c674195bbc0d0be3efa2whatever")
    >>= \case
        Left problem -> print problem
        Right info   -> print info

Types for calls and response

data UserInfo Source

Info about user.

Constructors

UserInfo 

Fields

inBetaProgram :: Bool

Does user in the CircleCI Beta Program?

fullName :: Text

User's full name.

allEmails :: [Text]

All email addresses in user's account.

defaultEmail :: Text

Default email for notifications.

basicEmailPreference :: EmailNotification

User email notifications.

gitHubAvatarUrl :: Text

GitHub avatar URL.

gitHubId :: Integer

GitHub ID.

gitHubLogin :: Text

User's GitHub login.

gitHubOAuthScopes :: [GitHubOAuth]

GitHub OAuth scopes.

accountCreatedAt :: UTCTime

Date when CircleCI-account was created.

trialEndDate :: UTCTime

Trial period end date.

plan :: Plan

User's plan pricing.

parallelism :: Int

Parallelism for tests.

containtersNumber :: Int

Number of user's build containers.

projects :: [ProjectShortInfo]

User's projects, short info.

analyticsId :: AnalyticsId

Analytics ID.

pusherId :: Text

Pusher ID.

herokuAPIKey :: Maybe Text

Heroku API key.

data ProjectShortInfo Source

Short info about the project.

Constructors

ProjectShortInfo 

Fields

gitHubURL :: Text

Project's GitHUb URL.

onDashboard :: Bool

Does this project on CircleCI Dashboard?

emailNotification :: EmailNotification

Email notifications for this project.

data Plan Source

CircleCI plan. For more info please see https://circleci.com/pricing/.

Constructors

Hobbyist 
Plan Text 

Instances

data GitHubOAuth Source

GitHub OAuth mode.

Constructors

UserEmailOAuth 
RepoOAuth 

type AnalyticsId = Text Source

User's analytics id. For example, "6fc20e13-008e-4dc9-b158-ababd33a099d".