credentials-0.0.1.1: Secure Credentials Storage and Distribution

Copyright(c) 2015-2016 Brendan Hay
LicenseMozilla Public License, v. 2.0.
MaintainerBrendan Hay <brendan.g.hay@gmail.com>
Stabilityprovisional
Portabilitynon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell2010

Credentials

Contents

Description

This module provides a common interface for operating on your shared credentials.

Synopsis

Usage

To use the library, make sure you have met the following prerequisites:

  • You have a master key in KMS. You can create this under Identity and Access Management > Encryption Keys, in the AWS developer console.
  • Your AWS access credentials are available where amazonka can find them. This will be automatic if you are running on an EC2 host, otherwise the ~/.aws/credentials file, as AWS_ACCESS_KEY_ID and AWS_SECRET_ACCESS_KEY environment variables need to be configured.

Since all of the credentials operations are constrained by a MonadAWS context, running them is identical to that of amazonka, which you will also need to add to your build-depends section of your project's cabal file.

{-# LANGUAGE OverloadedStrings #-}

import Credentials
import Control.Lens
import Data.ByteString (ByteString)
import Network.AWS
import System.IO

example :: IO (ByteString, Revision)
example = do
    -- A new 'Logger' to replace the default noop logger is created,
    -- which will print AWS debug information and errors to stdout.
    lgr <- newLogger Debug stdout

    -- A new amazonka 'Env' is created, which auto-discovers the
    -- underlying host credentials.
    env <- newEnv Frankfurt Discover

    let table = "dynamo-table-name"
        key   = "kms-key-alias"
        name  = "credential-name"

    -- We now run the 'AWS' computation with the overriden logger,
    -- performing the sequence of credentials operations.
    runResourceT . runAWS (env & envLogger .~ lgr) $ do
        -- Firstly, we create the DynamoDB table.
        -- This is an idempotent operation but since it makes remote API calls,
        -- it's recommended you only run this once via the CLI.
        Credentials.setup table

        -- Then we insert a credential\'s value, for a given name.
        -- Encryption is handled transparently and the resulting revision
        -- is returned.
        _ <- Credentials.insert key mempty name "a-super-secret-value" table

        -- Selecting the credential by name, and specifying 'Nothing' for the
        -- revision results in the latest credential revision being returned.
        Credentials.select mempty name Nothing table

Operations

insert Source #

Arguments

:: (MonadMask m, MonadAWS m, Typeable m) 
=> KeyId

The KMS master key ARN or alias.

-> Context

The KMS encryption context.

-> Name

The credential name.

-> ByteString

The unencrypted plaintext.

-> DynamoTable

The DynamoDB table.

-> m Revision 

Encrypt and insert a new credential revision with the specified name.

The newly inserted revision is returned.

select Source #

Arguments

:: MonadAWS m 
=> Context

The KMS encryption context that was used during insertion.

-> Name

The credential name.

-> Maybe Revision

A revision. If Nothing, the latest will be selected.

-> DynamoTable

The DynamoDB table.

-> m (ByteString, Revision) 

Select an existing credential, optionally specifying the revision.

The decrypted plaintext and selected revision are returned.

delete Source #

Arguments

:: MonadAWS m 
=> Name

The credential name.

-> Revision

The revision to delete.

-> DynamoTable

The DynamoDB table.

-> m () 

Delete the specific credential revision.

truncate Source #

Arguments

:: MonadAWS m 
=> Name

The credential name.

-> DynamoTable

The DynamoDB table.

-> m () 

Truncate all of a credential's revisions, so that only the latest revision remains.

revisions Source #

Arguments

:: MonadAWS m 
=> DynamoTable

The DynamoDB table.

-> Source m (Name, NonEmpty Revision) 

Scan the entire credential database, grouping pages of results into unique credential names and their corresponding revisions.

setup Source #

Arguments

:: MonadAWS m 
=> DynamoTable

The DynamoDB table.

-> m Setup 

Create the credentials database table.

The returned idempotency flag can be used to notify configuration management tools such as ansible whether about system state.

teardown :: MonadAWS m => DynamoTable -> m () Source #

Delete the credentials database table and all data.

Note: Unless you have DynamoDB backups running, this is a completely irrevocable action.

KMS

newtype KeyId Source #

The KMS master key identifier.

Constructors

KeyId Text 

defaultKeyId :: KeyId Source #

The default KMS master key alias.

Value: alias/credentials

DynamoDB

defaultTable :: DynamoTable Source #

The default DynamoDB table used to store credentials.

Value: credentials

Errors

data CredentialError Source #

Constructors

MasterKeyMissing KeyId (Maybe Text)

The specified master key id doesn't exist.

IntegrityFailure Name ByteString ByteString

The computed HMAC doesn't matched the stored HMAC.

EncryptFailure Context Name Text

Failure occured during local encryption.

DecryptFailure Context Name Text

Failure occured during local decryption.

StorageMissing Text

Storage doesn't exist, or has gone on holiday.

StorageFailure Text

Some storage pre-condition wasn't met. For example: DynamoDB column size exceeded.

FieldMissing Text [Text]

Missing field from the storage engine.

FieldInvalid Text String

Unable to parse field from the storage engine.

SecretMissing Name (Maybe Revision) Text

Secret with the specified name cannot found.

OptimisticLockFailure Name Revision Text

Attempting to insert a revision that already exists.

class AsCredentialError a where Source #

Instances

AsCredentialError SomeException Source # 
AsCredentialError CredentialError Source # 

Types

newtype Context Source #

A KMS encryption context.

See: KMS Encryption Context documentation for more information.

Constructors

Context 

data Setup Source #

Denotes idempotency of an action. That is, whether an action resulted in any setup being performed.

Constructors

Created 
Exists 

Instances