aws-0.11: Amazon Web Services (AWS) for Haskell

CopyrightSoostone Inc, Chris Allen
LicenseBSD3
MaintainerOzgun Ataman <ozgun.ataman@soostone.com>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Aws.DynamoDb.Core

Contents

Description

Shared types and utilities for DyanmoDb functionality.

Synopsis

Configuration and Regions

data Region Source

Constructors

Region 

ddbLocal :: Region Source

DynamoDb local connection (for development)

data DdbConfiguration qt Source

Constructors

DdbConfiguration 

Fields

ddbcRegion :: Region

The regional endpoint. Ex: ddbUsEast

ddbcProtocol :: Protocol

HTTP or HTTPS

ddbcPort :: Maybe Int

Port override (mostly for local dev connection)

DynamoDB values

data DValue Source

Value types natively recognized by DynamoDb. We pretty much exactly reflect the AWS API onto Haskell types.

Constructors

DNum Scientific 
DString Text 
DBinary ByteString

Binary data will automatically be base64 marshalled.

DNumSet (Set Scientific) 
DStringSet (Set Text) 
DBinSet (Set ByteString)

Binary data will automatically be base64 marshalled.

Converting to/from DValue

class DynData (DynRep a) => DynVal a where Source

Class of Haskell types that can be represented as DynamoDb values.

This is the conversion layer; instantiate this class for your own types and then use the toValue and fromValue combinators to convert in application code.

Each Haskell type instantiated with this class will map to a DynamoDb-supported type that most naturally represents it.

Associated Types

type DynRep a Source

Which of the DynData instances does this data type directly map to?

Methods

toRep :: a -> DynRep a Source

Convert to representation

fromRep :: DynRep a -> Maybe a Source

Convert from representation

Instances

DynVal Bool

Encoded as 0 and 1.

DynVal Double 
DynVal Int 
DynVal Int8 
DynVal Int16 
DynVal Int32 
DynVal Int64 
DynVal Integer 
DynVal Word8 
DynVal Word16 
DynVal Word32 
DynVal Word64 
DynVal ByteString 
DynVal Text 
DynVal UTCTime

Losslessly encoded via Integer picoseconds

DynVal Day

Encoded as number of days

DynVal DValue 
(DynData (DynRep [a]), DynVal a) => DynVal [a]

Any singular DynVal can be upgraded to a list.

(DynData (DynRep (Set a)), DynVal a, Ord a) => DynVal (Set a)

Any singular DynVal can be upgraded to a Set.

Serialize a => DynVal (Bin a) 

toValue :: DynVal a => a -> DValue Source

Encode a Haskell value.

fromValue :: DynVal a => DValue -> Maybe a Source

Decode a Haskell value.

newtype Bin a Source

Type wrapper for binary data to be written to DynamoDB. Wrap any Serialize instance in there and DynVal will know how to automatically handle conversions in binary form.

Constructors

Bin 

Fields

getBin :: a
 

Instances

Enum a => Enum (Bin a) 
Eq a => Eq (Bin a) 
Ord a => Ord (Bin a) 
Read a => Read (Bin a) 
Show a => Show (Bin a) 
Serialize a => DynVal (Bin a) 
Typeable (* -> *) Bin 
type DynRep (Bin a) = DynBinary 

Defining new DynVal instances

class Ord a => DynData a where Source

An internally used closed typeclass for values that have direct DynamoDb representations. Based on AWS API, this is basically numbers, strings and binary blobs.

This is here so that any DynVal haskell value can automatically be lifted to a list or a Set without any instance code duplication.

Do not try to create your own instances.

newtype DynBinary Source

Binary values stored in DynamoDb. Only used in defining new DynVal instances.

Constructors

DynBinary 

newtype DynNumber Source

Numeric values stored in DynamoDb. Only used in defining new DynVal instances.

Constructors

DynNumber 

newtype DynString Source

String values stored in DynamoDb. Only used in defining new DynVal instances.

Constructors

DynString 

Fields

unDynString :: Text
 

Working with key/value pairs

parseAttributeJson :: Value -> Parser [Attribute] Source

Parse a JSON object that contains attributes

attributeJson :: Attribute -> Pair Source

Convert into JSON pair

attributesJson :: [Attribute] -> Value Source

Convert into JSON object for AWS.

attrTuple :: Attribute -> (Text, DValue) Source

Convert attribute to a tuple representation

attr :: DynVal a => Text -> a -> Attribute Source

Convenience function for constructing key-value pairs

attrAs :: DynVal a => Proxy a -> Text -> a -> Attribute Source

attr with type witness to help with cases where you're manually supplying values in code.

> item [ attrAs text "name" "john" ]

text :: Proxy Text Source

Type witness for Text. See attrAs.

int :: Proxy Integer Source

Type witness for Integer. See attrAs.

double :: Proxy Double Source

Type witness for Double. See attrAs.

data PrimaryKey Source

Primary keys consist of either just a Hash key (mandatory) or a hash key and a range key (optional).

Constructors

PrimaryKey 

hk :: Text -> DValue -> PrimaryKey Source

Construct a hash-only primary key.

>>> hk "user-id" "ABCD"
>>> hk "user-id" (mkVal 23)

hrk Source

Arguments

:: Text

Hash key name

-> DValue

Hash key value

-> Text

Range key name

-> DValue

Range key value

-> PrimaryKey 

Construct a hash-and-range primary key.

Working with objects (attribute collections)

type Item = Map Text DValue Source

A DynamoDb object is simply a key-value dictionary.

item :: [Attribute] -> Item Source

Pack a list of attributes into an Item.

attributes :: Map Text DValue -> [Attribute] Source

Unpack an Item into a list of attributes.

class ToDynItem a where Source

Types convertible to DynamoDb Item collections.

Use attr and attrAs combinators to conveniently define instances.

Methods

toItem :: a -> Item Source

Instances

class FromDynItem a where Source

Types parseable from DynamoDb Item collections.

User getAttr family of functions to applicatively or monadically parse into your custom types.

Methods

parseItem :: Item -> Parser a Source

Instances

fromItem :: FromDynItem a => Item -> Either String a Source

Parse an Item into target type using the FromDynItem instance.

newtype Parser a Source

A continuation-based parser type.

Constructors

Parser 

Fields

runParser :: forall f r. Failure f r -> Success a f r -> f r
 

getAttr Source

Arguments

:: forall a . (Typeable a, DynVal a) 
=> Text

Attribute name

-> Item

Item from DynamoDb

-> Parser a 

Convenience combinator for parsing fields from an Item returned by DynamoDb.

getAttr' Source

Arguments

:: forall a . (Typeable a, DynVal a) 
=> Text

Attribute name

-> Item

Item from DynamoDb

-> Parser (Maybe a) 

Parse attribute if it's present in the Item. Fail if attribute is present but conversion fails.

Common types used by operations

data Conditions Source

Conditions used by mutation operations (PutItem, UpdateItem, etc.). The default def instance is empty (no condition).

conditionsJson :: Text -> Conditions -> [Pair] Source

JSON encoding of conditions parameter in various contexts.

data Condition Source

A condition used by mutation operations (PutItem, UpdateItem, etc.).

Constructors

Condition 

Fields

condAttr :: Text

Attribute to use as the basis for this conditional

condOp :: CondOp

Operation on the selected attribute

data CondMerge Source

How to merge multiple conditions.

Constructors

CondAnd 
CondOr 

data UpdateReturn Source

What to return from the current update operation

Constructors

URNone

Return nothing

URAllOld

Return old values

URUpdatedOld

Return old values with a newer replacement

URAllNew

Return new values

URUpdatedNew

Return new values that were replacements

data QuerySelect Source

What to return from a Query or Scan query.

Constructors

SelectSpecific [Text]

Only return selected attributes

SelectCount

Return counts instead of attributes

SelectProjected

Return index-projected attributes

SelectAll

Default. Return everything.

Size estimation

class DynSize a where Source

A class to help predict DynamoDb size of values, attributes and entire items. The result is given in number of bytes.

Methods

dynSize :: a -> Int Source

nullAttr :: Attribute -> Bool Source

Will an attribute be considered empty by DynamoDb?

A PutItem (or similar) with empty attributes will be rejection with a ValidationException.

Responses & Errors

data DdbResponse Source

Response metadata that is present in every DynamoDB response.

Constructors

DdbResponse 

shouldRetry :: DdbErrCode -> Bool Source

Whether the action should be retried based on the received error.

data DdbError Source

Potential errors raised by DynamoDB

Constructors

DdbError 

Fields

ddbStatusCode :: Int

200 if successful, 400 for client errors and 500 for server-side errors.

ddbErrCode :: DdbErrCode
 
ddbErrMsg :: Text
 

Internal Helpers

data AmazonError Source

Constructors

AmazonError 

Fields

aeType :: Text
 
aeMessage :: Maybe Text