confcrypt-0.1.0.3

Copyright(c) 2018 Chris Coffey
(c) 2018 CollegeVine
LicenseMIT
MaintainerChris Coffey
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

ConfCrypt.Types

Contents

Description

Core types and some small helper functions used to construct ConfCrypt.

Synopsis

Core types

type ConfCryptM m ctx = ReaderT (ConfCryptFile, ctx) (WriterT [Text] (ExceptT ConfCryptError (ResourceT m))) Source #

The core transformer stack for ConfCrypt. The most important parts are the ReaderT and ResourceT, as the WriterT and ExceptT can both be replaced with explicit return types.

Errors

data ConfCryptError Source #

The possible errors produced during a confcrypt operation.

Instances
Eq ConfCryptError Source # 
Instance details

Defined in ConfCrypt.Types

Ord ConfCryptError Source # 
Instance details

Defined in ConfCrypt.Types

Show ConfCryptError Source # 
Instance details

Defined in ConfCrypt.Types

Generic ConfCryptError Source # 
Instance details

Defined in ConfCrypt.Types

Associated Types

type Rep ConfCryptError :: Type -> Type #

Monad m => Command NewConfCrypt (ConfCryptM m ()) Source # 
Instance details

Defined in ConfCrypt.Commands

Methods

evaluate :: NewConfCrypt -> ConfCryptM m () () Source #

(Monad m, MonadDecrypt (ConfCryptM m key) key) => Command ValidateConfCrypt (ConfCryptM m key) Source # 
Instance details

Defined in ConfCrypt.Commands

Monad m => Command DeleteConfCrypt (ConfCryptM m ()) Source # 
Instance details

Defined in ConfCrypt.Commands

(Monad m, MonadRandom m, MonadEncrypt (ConfCryptM m key) key) => Command EditConfCrypt (ConfCryptM m key) Source # 
Instance details

Defined in ConfCrypt.Commands

Methods

evaluate :: EditConfCrypt -> ConfCryptM m key () Source #

(Monad m, MonadRandom m, MonadEncrypt (ConfCryptM m key) key) => Command AddConfCrypt (ConfCryptM m key) Source # 
Instance details

Defined in ConfCrypt.Commands

Methods

evaluate :: AddConfCrypt -> ConfCryptM m key () Source #

(Monad m, MonadDecrypt (ConfCryptM m key) key) => Command GetConfCrypt (ConfCryptM m key) Source # 
Instance details

Defined in ConfCrypt.Commands

Methods

evaluate :: GetConfCrypt -> ConfCryptM m key () Source #

(Monad m, MonadDecrypt (ConfCryptM m key) key) => Command ReadConfCrypt (ConfCryptM m key) Source # 
Instance details

Defined in ConfCrypt.Commands

Methods

evaluate :: ReadConfCrypt -> ConfCryptM m key () Source #

MonadRandom m => MonadRandom (ConfCryptM m k) Source # 
Instance details

Defined in ConfCrypt.Encryption

Methods

getRandomBytes :: ByteArray byteArray => Int -> ConfCryptM m k byteArray #

MonadEncrypt (ConfCryptM IO (RemoteKey AWSCtx)) (RemoteKey AWSCtx) Source # 
Instance details

Defined in ConfCrypt.Encryption

MonadDecrypt (ConfCryptM IO (RemoteKey AWSCtx)) (RemoteKey AWSCtx) Source # 
Instance details

Defined in ConfCrypt.Encryption

type Rep ConfCryptError Source # 
Instance details

Defined in ConfCrypt.Types

type Rep ConfCryptError = D1 (MetaData "ConfCryptError" "ConfCrypt.Types" "confcrypt-0.1.0.3-HTKSTr1TBe1BmQ6kc05Zmi" False) (((C1 (MetaCons "ParserError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) :+: C1 (MetaCons "NonRSAKey" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "KeyUnpackingError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) :+: (C1 (MetaCons "DecryptionError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) :+: C1 (MetaCons "AWSDecryptionError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))))) :+: ((C1 (MetaCons "AWSEncryptionError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) :+: (C1 (MetaCons "EncryptionError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Error)) :+: C1 (MetaCons "MissingLine" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))) :+: (C1 (MetaCons "UnknownParameter" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) :+: (C1 (MetaCons "WrongFileAction" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) :+: C1 (MetaCons "CleanupError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))))))

Runtime Environment

data ConfCryptFile Source #

As indicated in the Readme, a ConfCrypt file

Instances
Show ConfCryptFile Source # 
Instance details

Defined in ConfCrypt.Types

Generic ConfCryptFile Source # 
Instance details

Defined in ConfCrypt.Types

Associated Types

type Rep ConfCryptFile :: Type -> Type #

NFData ConfCryptFile Source # 
Instance details

Defined in ConfCrypt.Types

Methods

rnf :: ConfCryptFile -> () #

Monad m => Command NewConfCrypt (ConfCryptM m ()) Source # 
Instance details

Defined in ConfCrypt.Commands

Methods

evaluate :: NewConfCrypt -> ConfCryptM m () () Source #

(Monad m, MonadDecrypt (ConfCryptM m key) key) => Command ValidateConfCrypt (ConfCryptM m key) Source # 
Instance details

Defined in ConfCrypt.Commands

Monad m => Command DeleteConfCrypt (ConfCryptM m ()) Source # 
Instance details

Defined in ConfCrypt.Commands

(Monad m, MonadRandom m, MonadEncrypt (ConfCryptM m key) key) => Command EditConfCrypt (ConfCryptM m key) Source # 
Instance details

Defined in ConfCrypt.Commands

Methods

evaluate :: EditConfCrypt -> ConfCryptM m key () Source #

(Monad m, MonadRandom m, MonadEncrypt (ConfCryptM m key) key) => Command AddConfCrypt (ConfCryptM m key) Source # 
Instance details

Defined in ConfCrypt.Commands

Methods

evaluate :: AddConfCrypt -> ConfCryptM m key () Source #

(Monad m, MonadDecrypt (ConfCryptM m key) key) => Command GetConfCrypt (ConfCryptM m key) Source # 
Instance details

Defined in ConfCrypt.Commands

Methods

evaluate :: GetConfCrypt -> ConfCryptM m key () Source #

(Monad m, MonadDecrypt (ConfCryptM m key) key) => Command ReadConfCrypt (ConfCryptM m key) Source # 
Instance details

Defined in ConfCrypt.Commands

Methods

evaluate :: ReadConfCrypt -> ConfCryptM m key () Source #

HasEnv (ConfCryptFile, AWSCtx) Source # 
Instance details

Defined in ConfCrypt.Providers.AWS

MonadRandom m => MonadRandom (ConfCryptM m k) Source # 
Instance details

Defined in ConfCrypt.Encryption

Methods

getRandomBytes :: ByteArray byteArray => Int -> ConfCryptM m k byteArray #

MonadEncrypt (ConfCryptM IO (RemoteKey AWSCtx)) (RemoteKey AWSCtx) Source # 
Instance details

Defined in ConfCrypt.Encryption

MonadDecrypt (ConfCryptM IO (RemoteKey AWSCtx)) (RemoteKey AWSCtx) Source # 
Instance details

Defined in ConfCrypt.Encryption

type Rep ConfCryptFile Source # 
Instance details

Defined in ConfCrypt.Types

type Rep ConfCryptFile = D1 (MetaData "ConfCryptFile" "ConfCrypt.Types" "confcrypt-0.1.0.3-HTKSTr1TBe1BmQ6kc05Zmi" False) (C1 (MetaCons "ConfCryptFile" PrefixI True) (S1 (MetaSel (Just "fileName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: (S1 (MetaSel (Just "fileContents") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map ConfCryptElement LineNumber)) :*: S1 (MetaSel (Just "parameters") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Parameter]))))

data Parameter Source #

A parameter consists of both a ParamLine and Schema line from the confcr

Instances
Eq Parameter Source # 
Instance details

Defined in ConfCrypt.Types

Ord Parameter Source # 
Instance details

Defined in ConfCrypt.Types

Show Parameter Source # 
Instance details

Defined in ConfCrypt.Types

Generic Parameter Source # 
Instance details

Defined in ConfCrypt.Types

Associated Types

type Rep Parameter :: Type -> Type #

NFData Parameter Source # 
Instance details

Defined in ConfCrypt.Types

Methods

rnf :: Parameter -> () #

type Rep Parameter Source # 
Instance details

Defined in ConfCrypt.Types

type Rep Parameter = D1 (MetaData "Parameter" "ConfCrypt.Types" "confcrypt-0.1.0.3-HTKSTr1TBe1BmQ6kc05Zmi" False) (C1 (MetaCons "Parameter" PrefixI True) (S1 (MetaSel (Just "paramName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: (S1 (MetaSel (Just "paramValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "paramType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SchemaType)))))

File Format

data ConfCryptElement Source #

The syntax used to describe a confcrypt file. A line in a confcrypt file may be one of Schema, ParamLine, or comment. The grammar itself is described in the readme and Parser.

Instances
Eq ConfCryptElement Source #

this implementation means that there can only be a single parameter or schema with the same name. Attempting to add multiple with the same name is undefined behavior and will result in missing data.

Instance details

Defined in ConfCrypt.Types

Ord ConfCryptElement Source #

In order to

Instance details

Defined in ConfCrypt.Types

Show ConfCryptElement Source # 
Instance details

Defined in ConfCrypt.Types

Generic ConfCryptElement Source # 
Instance details

Defined in ConfCrypt.Types

Associated Types

type Rep ConfCryptElement :: Type -> Type #

NFData ConfCryptElement Source # 
Instance details

Defined in ConfCrypt.Types

Methods

rnf :: ConfCryptElement -> () #

type Rep ConfCryptElement Source # 
Instance details

Defined in ConfCrypt.Types

newtype LineNumber Source #

Self explanitory

Constructors

LineNumber Int 
Instances
Eq LineNumber Source # 
Instance details

Defined in ConfCrypt.Types

Ord LineNumber Source # 
Instance details

Defined in ConfCrypt.Types

Show LineNumber Source # 
Instance details

Defined in ConfCrypt.Types

Generic LineNumber Source # 
Instance details

Defined in ConfCrypt.Types

Associated Types

type Rep LineNumber :: Type -> Type #

NFData LineNumber Source # 
Instance details

Defined in ConfCrypt.Types

Methods

rnf :: LineNumber -> () #

type Rep LineNumber Source # 
Instance details

Defined in ConfCrypt.Types

type Rep LineNumber = D1 (MetaData "LineNumber" "ConfCrypt.Types" "confcrypt-0.1.0.3-HTKSTr1TBe1BmQ6kc05Zmi" True) (C1 (MetaCons "LineNumber" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

data SchemaType Source #

Indicates which types a

Constructors

CString

Maps to String

CInt

Maps to Int

CBoolean

Maps to Bool

Instances
Eq SchemaType Source # 
Instance details

Defined in ConfCrypt.Types

Ord SchemaType Source # 
Instance details

Defined in ConfCrypt.Types

Read SchemaType Source # 
Instance details

Defined in ConfCrypt.Types

Show SchemaType Source # 
Instance details

Defined in ConfCrypt.Types

Generic SchemaType Source # 
Instance details

Defined in ConfCrypt.Types

Associated Types

type Rep SchemaType :: Type -> Type #

NFData SchemaType Source # 
Instance details

Defined in ConfCrypt.Types

Methods

rnf :: SchemaType -> () #

type Rep SchemaType Source # 
Instance details

Defined in ConfCrypt.Types

type Rep SchemaType = D1 (MetaData "SchemaType" "ConfCrypt.Types" "confcrypt-0.1.0.3-HTKSTr1TBe1BmQ6kc05Zmi" False) (C1 (MetaCons "CString" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "CInt" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CBoolean" PrefixI False) (U1 :: Type -> Type)))

data ParamLine Source #

A parsed parameter line from a confcrypt file

Constructors

ParamLine 

Fields

Instances
Eq ParamLine Source # 
Instance details

Defined in ConfCrypt.Types

Ord ParamLine Source # 
Instance details

Defined in ConfCrypt.Types

Show ParamLine Source # 
Instance details

Defined in ConfCrypt.Types

Generic ParamLine Source # 
Instance details

Defined in ConfCrypt.Types

Associated Types

type Rep ParamLine :: Type -> Type #

NFData ParamLine Source # 
Instance details

Defined in ConfCrypt.Types

Methods

rnf :: ParamLine -> () #

type Rep ParamLine Source # 
Instance details

Defined in ConfCrypt.Types

type Rep ParamLine = D1 (MetaData "ParamLine" "ConfCrypt.Types" "confcrypt-0.1.0.3-HTKSTr1TBe1BmQ6kc05Zmi" False) (C1 (MetaCons "ParamLine" PrefixI True) (S1 (MetaSel (Just "pName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "pValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data Schema Source #

A parsed schema line from a confcrypt file

Constructors

Schema 

Fields

Instances
Eq Schema Source # 
Instance details

Defined in ConfCrypt.Types

Methods

(==) :: Schema -> Schema -> Bool #

(/=) :: Schema -> Schema -> Bool #

Ord Schema Source # 
Instance details

Defined in ConfCrypt.Types

Show Schema Source # 
Instance details

Defined in ConfCrypt.Types

Generic Schema Source # 
Instance details

Defined in ConfCrypt.Types

Associated Types

type Rep Schema :: Type -> Type #

Methods

from :: Schema -> Rep Schema x #

to :: Rep Schema x -> Schema #

NFData Schema Source # 
Instance details

Defined in ConfCrypt.Types

Methods

rnf :: Schema -> () #

type Rep Schema Source # 
Instance details

Defined in ConfCrypt.Types

type Rep Schema = D1 (MetaData "Schema" "ConfCrypt.Types" "confcrypt-0.1.0.3-HTKSTr1TBe1BmQ6kc05Zmi" False) (C1 (MetaCons "Schema" PrefixI True) (S1 (MetaSel (Just "sName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "sType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SchemaType)))

Key constraints

class LocalKey key Source #

This constraint provides a type-level check that the wrapped key type is local to the current machine. For use with things like RSA keys.

Instances
LocalKey PublicKey Source # 
Instance details

Defined in ConfCrypt.Encryption

LocalKey PrivateKey Source # 
Instance details

Defined in ConfCrypt.Encryption

class KMSKey key Source #

This constraint provides a type-level check that the wrapped key type exists off-system inside an externally provided Key Management System (KMS). For use with AWS KMS or Azure KMS.

Instances
KMSKey AWSCtx Source # 
Instance details

Defined in ConfCrypt.Encryption

Helpers

unWrapSchema :: ConfCryptElement -> Maybe Schema Source #

Attempts to unwrap a line from a confcrypt file into a Schema

isParameter :: ConfCryptElement -> Bool Source #

Checks whether the provided line from a confcrypt file is a Parameter

typeToOutputString :: SchemaType -> Text Source #

A special purpose Show function for convert

parameterToLines :: Parameter -> (ParamLine, Maybe Schema) Source #

Convert a parameter into a ParameterLine and SchemaLine if possible.

Orphan instances

Ord Error Source # 
Instance details

Methods

compare :: Error -> Error -> Ordering #

(<) :: Error -> Error -> Bool #

(<=) :: Error -> Error -> Bool #

(>) :: Error -> Error -> Bool #

(>=) :: Error -> Error -> Bool #

max :: Error -> Error -> Error #

min :: Error -> Error -> Error #