aws-0.18: 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

ddbLocal :: Region Source #

DynamoDb local connection (for development)

DynamoDB values

data DValue Source #

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

Constructors

DNull 
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.

DBool Bool 
DBoolSet (Set Bool)

Composite data

DList (Vector DValue) 
DMap (Map Text DValue) 

Instances

Eq DValue Source # 

Methods

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

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

Ord DValue Source # 
Read DValue Source # 
Show DValue Source # 
IsString DValue Source # 

Methods

fromString :: String -> DValue #

FromJSON DValue Source # 
ToJSON DValue Source # 
FromDynItem Item Source # 
ToDynItem Item Source # 

Methods

toItem :: Item -> Item Source #

DynSize Item Source # 

Methods

dynSize :: Item -> Int Source #

DynSize DValue Source # 

Methods

dynSize :: DValue -> Int Source #

DynVal DValue Source # 

Associated Types

type DynRep DValue :: * Source #

DynData DValue Source # 
ListResponse QueryResponse Item Source # 
ListResponse ScanResponse Item Source # 
type DynRep DValue Source # 

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.

Minimal complete definition

toRep, fromRep

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 Source # 

Associated Types

type DynRep Bool :: * Source #

DynVal Double Source # 

Associated Types

type DynRep Double :: * Source #

DynVal Int Source # 

Associated Types

type DynRep Int :: * Source #

DynVal Int8 Source # 

Associated Types

type DynRep Int8 :: * Source #

DynVal Int16 Source # 

Associated Types

type DynRep Int16 :: * Source #

DynVal Int32 Source # 

Associated Types

type DynRep Int32 :: * Source #

DynVal Int64 Source # 

Associated Types

type DynRep Int64 :: * Source #

DynVal Integer Source # 
DynVal Word8 Source # 

Associated Types

type DynRep Word8 :: * Source #

DynVal Word16 Source # 

Associated Types

type DynRep Word16 :: * Source #

DynVal Word32 Source # 

Associated Types

type DynRep Word32 :: * Source #

DynVal Word64 Source # 

Associated Types

type DynRep Word64 :: * Source #

DynVal ByteString Source # 
DynVal Text Source # 

Associated Types

type DynRep Text :: * Source #

DynVal UTCTime Source #

Losslessly encoded via Integer picoseconds

DynVal Day Source #

Encoded as number of days

Associated Types

type DynRep Day :: * Source #

DynVal DValue Source # 

Associated Types

type DynRep DValue :: * Source #

DynVal OldBool Source # 
(DynData (DynRep [a]), DynVal a) => DynVal [a] Source #

Any singular DynVal can be upgraded to a list.

Associated Types

type DynRep [a] :: * Source #

Methods

toRep :: [a] -> DynRep [a] Source #

fromRep :: DynRep [a] -> Maybe [a] Source #

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

Any singular DynVal can be upgraded to a Set.

Associated Types

type DynRep (Set a) :: * Source #

Methods

toRep :: Set a -> DynRep (Set a) Source #

fromRep :: DynRep (Set a) -> Maybe (Set a) Source #

Serialize a => DynVal (Bin a) Source # 

Associated Types

type DynRep (Bin a) :: * Source #

Methods

toRep :: Bin a -> DynRep (Bin a) Source #

fromRep :: DynRep (Bin a) -> Maybe (Bin a) Source #

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

Instances

Enum a => Enum (Bin a) Source # 

Methods

succ :: Bin a -> Bin a #

pred :: Bin a -> Bin a #

toEnum :: Int -> Bin a #

fromEnum :: Bin a -> Int #

enumFrom :: Bin a -> [Bin a] #

enumFromThen :: Bin a -> Bin a -> [Bin a] #

enumFromTo :: Bin a -> Bin a -> [Bin a] #

enumFromThenTo :: Bin a -> Bin a -> Bin a -> [Bin a] #

Eq a => Eq (Bin a) Source # 

Methods

(==) :: Bin a -> Bin a -> Bool #

(/=) :: Bin a -> Bin a -> Bool #

Ord a => Ord (Bin a) Source # 

Methods

compare :: Bin a -> Bin a -> Ordering #

(<) :: Bin a -> Bin a -> Bool #

(<=) :: Bin a -> Bin a -> Bool #

(>) :: Bin a -> Bin a -> Bool #

(>=) :: Bin a -> Bin a -> Bool #

max :: Bin a -> Bin a -> Bin a #

min :: Bin a -> Bin a -> Bin a #

Read a => Read (Bin a) Source # 
Show a => Show (Bin a) Source # 

Methods

showsPrec :: Int -> Bin a -> ShowS #

show :: Bin a -> String #

showList :: [Bin a] -> ShowS #

Serialize a => DynVal (Bin a) Source # 

Associated Types

type DynRep (Bin a) :: * Source #

Methods

toRep :: Bin a -> DynRep (Bin a) Source #

fromRep :: DynRep (Bin a) -> Maybe (Bin a) Source #

type DynRep (Bin a) Source # 
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.

Minimal complete definition

fromData, toData

Methods

fromData :: a -> DValue Source #

toData :: DValue -> Maybe a Source #

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.

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.

Minimal complete definition

toItem

Methods

toItem :: a -> Item Source #

Instances

ToDynItem Item Source # 

Methods

toItem :: Item -> Item Source #

DynVal a => ToDynItem [(Text, a)] Source # 

Methods

toItem :: [(Text, a)] -> Item Source #

DynVal a => ToDynItem (Map Text a) Source # 

Methods

toItem :: Map Text a -> Item Source #

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.

Minimal complete definition

parseItem

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
     

Instances

Monad Parser Source # 

Methods

(>>=) :: Parser a -> (a -> Parser b) -> Parser b #

(>>) :: Parser a -> Parser b -> Parser b #

return :: a -> Parser a #

fail :: String -> Parser a #

Functor Parser Source # 

Methods

fmap :: (a -> b) -> Parser a -> Parser b #

(<$) :: a -> Parser b -> Parser a #

Applicative Parser Source # 

Methods

pure :: a -> Parser a #

(<*>) :: Parser (a -> b) -> Parser a -> Parser b #

(*>) :: Parser a -> Parser b -> Parser b #

(<*) :: Parser a -> Parser b -> Parser a #

Alternative Parser Source # 

Methods

empty :: Parser a #

(<|>) :: Parser a -> Parser a -> Parser a #

some :: Parser a -> Parser [a] #

many :: Parser a -> Parser [a] #

MonadPlus Parser Source # 

Methods

mzero :: Parser a #

mplus :: Parser a -> Parser a -> Parser a #

Monoid (Parser a) Source # 

Methods

mempty :: Parser a #

mappend :: Parser a -> Parser a -> Parser a #

mconcat :: [Parser a] -> Parser a #

getAttr Source #

Arguments

:: (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

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

parseAttr Source #

Arguments

:: FromDynItem a 
=> Text

Attribute name

-> Item

Item from DynamoDb

-> Parser a 

Combinator for parsing an attribute into a FromDynItem.

Common types used by operations

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

data ReturnItemCollectionMetrics Source #

Constructors

RICMSize 
RICMNone 

Instances

Eq ReturnItemCollectionMetrics Source # 
Ord ReturnItemCollectionMetrics Source # 
Read ReturnItemCollectionMetrics Source # 
Show ReturnItemCollectionMetrics Source # 
ToJSON ReturnItemCollectionMetrics Source # 
Default ReturnItemCollectionMetrics Source # 

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.

Minimal complete definition

dynSize

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 rejected 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

Internal Helpers