circlehs-0.0.3: The CircleCI REST API for Haskell

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

Network.CircleCI.CheckoutKey

Contents

Description

API calls for work with Checkout Keys. CircleCI uses Checkout Keys to check out your GitHub project, submodules, and private dependencies.

For more info please see "Checkout SSH keys" section in your CircleCI project's Settings.

Synopsis

API calls

getCheckoutKeys Source

Arguments

:: ProjectPoint

Names of GitHub user/project.

-> CircleCIResponse [CheckoutKeyInfo]

List of checkout keys.

Shows list of checkout keys. Based on https://circleci.com/docs/api/#list-checkout-keys.

Usage example:

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE LambdaCase #-}

import Network.CircleCI

main :: IO ()
main = runCircleCI (getCheckoutKeys $ ProjectPoint "denisshevchenko" "circlehs")
                   (AccountAPIToken "e64c674195bbc0d0be3ef9679b6c6ba2whatever")
    >>= \case
        Left problem -> print problem
        Right keys   -> print keys

getCheckoutKey Source

Arguments

:: ProjectPoint

Names of GitHub user/project.

-> Fingerprint

Key fingerprint.

-> CircleCIResponse CheckoutKeyInfo

Checkout key info.

Shows single checkout key. Based on https://circleci.com/docs/api/#get-checkout-key.

Usage example:

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE LambdaCase #-}

import Network.CircleCI

main :: IO ()
main = runCircleCI (getCheckoutKey project fingerprint) apiToken
    >>= \case
        Left problem -> print problem
        Right key    -> print key
  where
    project     = ProjectPoint "denisshevchenko" "circlehs"
    fingerprint = Fingerprint "79:23:05:6a:6d:4c:3c:5c:0e:64:79:49:f0:e9:8d:a0"
    apiToken    = AccountAPIToken "e64c674195bbc0d0be3ef9679b6c6ba2whatever"

createCheckoutKey Source

Arguments

:: ProjectPoint

Names of GitHub user/project.

-> CircleCIResponse CheckoutKeyInfo

New checkout key info.

Creates checkout key. Based on https://circleci.com/docs/api/#new-checkout-key.

Usage example:

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE LambdaCase #-}

import Network.CircleCI

main :: IO ()
main = runCircleCI (createCheckoutKey $ ProjectPoint "denisshevchenko" "circlehs")
                   (AccountAPIToken "e64c674195bbc0d0be3ef9679b6c6ba2whatever")
    >>= \case
        Left problem -> print problem
        Right newKey -> print newKey

deleteCheckoutKey Source

Arguments

:: ProjectPoint

Names of GitHub user/project.

-> Fingerprint

Key fingerprint.

-> CircleCIResponse CheckoutKeyDeleted

Status of checkout key deletion.

Deletes single checkout key. Based on https://circleci.com/docs/api/#delete-checkout-key.

Usage example:

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE LambdaCase #-}

import Network.CircleCI

main :: IO ()
main = runCircleCI (deleteCheckoutKey project fingerprint) apiToken
    >>= \case
        Left problem    -> print problem
        Right isDeleted -> print isDeleted
  where
    project     = ProjectPoint "denisshevchenko" "circlehs"
    fingerprint = Fingerprint "79:23:05:6a:6d:4c:3c:5c:0e:64:79:49:f0:e9:8d:a0"
    apiToken    = AccountAPIToken "e64c674195bbc0d0be3ef9679b6c6ba2whatever"

Types for calls and responses

newtype Fingerprint Source

Checkout key fingerprint. For example, "79:23:05:6a:6d:4c:3c:5c:0e:64:79:49:f0:e9:8d:a0".

Constructors

Fingerprint Text 

data CheckoutKeyInfo Source

Info about checkout key.

Constructors

CheckoutKeyInfo 

Fields

publicKey :: Text

Public SSH key.

keyType :: CheckoutKeyType

Key type.

fingerprint :: Fingerprint

Key fingerprint.

preferred :: Bool

Preferred key or not.

issueDate :: UTCTime

Date when this key was issued.

data CheckoutKeyType Source

Type of checkout key.

Constructors

GitHubDeployKey

Repo-specific SSH key.

GitHubUserKey

User-specific SSH key.