aws-0.23: Amazon Web Services (AWS) for Haskell
CopyrightSoostone Inc Chris Allen
LicenseBSD3
MaintainerOzgun Ataman <ozgun.ataman@soostone.com>
Stabilityexperimental
Safe HaskellSafe-Inferred
LanguageHaskell2010

Aws.DynamoDb.Core

Description

Shared types and utilities for DyanmoDb functionality.

Synopsis

Configuration and Regions

data Region Source #

Constructors

Region 

Instances

Instances details
Read Region Source # 
Instance details

Defined in Aws.DynamoDb.Core

Show Region Source # 
Instance details

Defined in Aws.DynamoDb.Core

Eq Region Source # 
Instance details

Defined in Aws.DynamoDb.Core

Methods

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

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

ddbLocal :: Region Source #

DynamoDb local connection (for development)

data DdbConfiguration qt Source #

Constructors

DdbConfiguration 

Fields

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

Instances details
FromJSON DValue Source # 
Instance details

Defined in Aws.DynamoDb.Core

ToJSON DValue Source # 
Instance details

Defined in Aws.DynamoDb.Core

DynData DValue Source # 
Instance details

Defined in Aws.DynamoDb.Core

DynSize DValue Source # 
Instance details

Defined in Aws.DynamoDb.Core

Methods

dynSize :: DValue -> Int Source #

DynSize Item Source # 
Instance details

Defined in Aws.DynamoDb.Core

Methods

dynSize :: Item -> Int Source #

DynVal DValue Source # 
Instance details

Defined in Aws.DynamoDb.Core

Associated Types

type DynRep DValue Source #

FromDynItem Item Source # 
Instance details

Defined in Aws.DynamoDb.Core

ToDynItem Item Source # 
Instance details

Defined in Aws.DynamoDb.Core

Methods

toItem :: Item -> Item Source #

IsString DValue Source # 
Instance details

Defined in Aws.DynamoDb.Core

Methods

fromString :: String -> DValue #

Read DValue Source # 
Instance details

Defined in Aws.DynamoDb.Core

Show DValue Source # 
Instance details

Defined in Aws.DynamoDb.Core

Eq DValue Source # 
Instance details

Defined in Aws.DynamoDb.Core

Methods

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

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

Ord DValue Source # 
Instance details

Defined in Aws.DynamoDb.Core

ListResponse QueryResponse Item Source # 
Instance details

Defined in Aws.DynamoDb.Commands.Query

ListResponse ScanResponse Item Source # 
Instance details

Defined in Aws.DynamoDb.Commands.Scan

type DynRep DValue Source # 
Instance details

Defined in Aws.DynamoDb.Core

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

Instances details
DynVal DValue Source # 
Instance details

Defined in Aws.DynamoDb.Core

Associated Types

type DynRep DValue Source #

DynVal OldBool Source # 
Instance details

Defined in Aws.DynamoDb.Core

Associated Types

type DynRep OldBool Source #

DynVal Int16 Source # 
Instance details

Defined in Aws.DynamoDb.Core

Associated Types

type DynRep Int16 Source #

DynVal Int32 Source # 
Instance details

Defined in Aws.DynamoDb.Core

Associated Types

type DynRep Int32 Source #

DynVal Int64 Source # 
Instance details

Defined in Aws.DynamoDb.Core

Associated Types

type DynRep Int64 Source #

DynVal Int8 Source # 
Instance details

Defined in Aws.DynamoDb.Core

Associated Types

type DynRep Int8 Source #

DynVal Word16 Source # 
Instance details

Defined in Aws.DynamoDb.Core

Associated Types

type DynRep Word16 Source #

DynVal Word32 Source # 
Instance details

Defined in Aws.DynamoDb.Core

Associated Types

type DynRep Word32 Source #

DynVal Word64 Source # 
Instance details

Defined in Aws.DynamoDb.Core

Associated Types

type DynRep Word64 Source #

DynVal Word8 Source # 
Instance details

Defined in Aws.DynamoDb.Core

Associated Types

type DynRep Word8 Source #

DynVal ByteString Source # 
Instance details

Defined in Aws.DynamoDb.Core

Associated Types

type DynRep ByteString Source #

DynVal Text Source # 
Instance details

Defined in Aws.DynamoDb.Core

Associated Types

type DynRep Text Source #

DynVal Day Source #

Encoded as number of days

Instance details

Defined in Aws.DynamoDb.Core

Associated Types

type DynRep Day Source #

DynVal UTCTime Source #

Losslessly encoded via Integer picoseconds

Instance details

Defined in Aws.DynamoDb.Core

Associated Types

type DynRep UTCTime Source #

DynVal Integer Source # 
Instance details

Defined in Aws.DynamoDb.Core

Associated Types

type DynRep Integer Source #

DynVal Bool Source # 
Instance details

Defined in Aws.DynamoDb.Core

Associated Types

type DynRep Bool Source #

DynVal Double Source # 
Instance details

Defined in Aws.DynamoDb.Core

Associated Types

type DynRep Double Source #

DynVal Int Source # 
Instance details

Defined in Aws.DynamoDb.Core

Associated Types

type DynRep Int Source #

Serialize a => DynVal (Bin a) Source # 
Instance details

Defined in Aws.DynamoDb.Core

Associated Types

type DynRep (Bin a) Source #

Methods

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

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

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

Any singular DynVal can be upgraded to a Set.

Instance details

Defined in Aws.DynamoDb.Core

Associated Types

type DynRep (Set a) Source #

Methods

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

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

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

Any singular DynVal can be upgraded to a list.

Instance details

Defined in Aws.DynamoDb.Core

Associated Types

type DynRep [a] Source #

Methods

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

fromRep :: DynRep [a] -> Maybe [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

Instances details
Serialize a => DynVal (Bin a) Source # 
Instance details

Defined in Aws.DynamoDb.Core

Associated Types

type DynRep (Bin a) Source #

Methods

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

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

Enum a => Enum (Bin a) Source # 
Instance details

Defined in Aws.DynamoDb.Core

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

Read a => Read (Bin a) Source # 
Instance details

Defined in Aws.DynamoDb.Core

Show a => Show (Bin a) Source # 
Instance details

Defined in Aws.DynamoDb.Core

Methods

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

show :: Bin a -> String #

showList :: [Bin a] -> ShowS #

Eq a => Eq (Bin a) Source # 
Instance details

Defined in Aws.DynamoDb.Core

Methods

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

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

Ord a => Ord (Bin a) Source # 
Instance details

Defined in Aws.DynamoDb.Core

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 #

type DynRep (Bin a) Source # 
Instance details

Defined in Aws.DynamoDb.Core

type DynRep (Bin a) = DynBinary

newtype OldBool Source #

Constructors

OldBool Bool 

Instances

Instances details
DynVal OldBool Source # 
Instance details

Defined in Aws.DynamoDb.Core

Associated Types

type DynRep OldBool Source #

type DynRep OldBool Source # 
Instance details

Defined in Aws.DynamoDb.Core

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.

Methods

fromData :: a -> DValue Source #

toData :: DValue -> Maybe a Source #

Instances

Instances details
DynData DValue Source # 
Instance details

Defined in Aws.DynamoDb.Core

DynData DynBinary Source # 
Instance details

Defined in Aws.DynamoDb.Core

DynData DynBool Source # 
Instance details

Defined in Aws.DynamoDb.Core

DynData DynNumber Source # 
Instance details

Defined in Aws.DynamoDb.Core

DynData DynString Source # 
Instance details

Defined in Aws.DynamoDb.Core

DynData (Set DynBinary) Source # 
Instance details

Defined in Aws.DynamoDb.Core

DynData (Set DynBool) Source # 
Instance details

Defined in Aws.DynamoDb.Core

DynData (Set DynNumber) Source # 
Instance details

Defined in Aws.DynamoDb.Core

DynData (Set DynString) Source # 
Instance details

Defined in Aws.DynamoDb.Core

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

newtype DynBool Source #

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

Constructors

DynBool 

Fields

Instances

Instances details
DynData DynBool Source # 
Instance details

Defined in Aws.DynamoDb.Core

Read DynBool Source # 
Instance details

Defined in Aws.DynamoDb.Core

Show DynBool Source # 
Instance details

Defined in Aws.DynamoDb.Core

Eq DynBool Source # 
Instance details

Defined in Aws.DynamoDb.Core

Methods

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

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

Ord DynBool Source # 
Instance details

Defined in Aws.DynamoDb.Core

DynData (Set DynBool) Source # 
Instance details

Defined in Aws.DynamoDb.Core

Working with key/value pairs

data Attribute Source #

A key-value pair

Constructors

Attribute 

Fields

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

Instances details
ToDynItem Item Source # 
Instance details

Defined in Aws.DynamoDb.Core

Methods

toItem :: Item -> Item Source #

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

Defined in Aws.DynamoDb.Core

Methods

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

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

Defined in Aws.DynamoDb.Core

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.

Methods

parseItem :: Item -> Parser a Source #

Instances

Instances details
FromDynItem Item Source # 
Instance details

Defined in Aws.DynamoDb.Core

(Typeable a, DynVal a) => FromDynItem [(Text, a)] Source # 
Instance details

Defined in Aws.DynamoDb.Core

Methods

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

(Typeable a, DynVal a) => FromDynItem (Map Text a) Source # 
Instance details

Defined in Aws.DynamoDb.Core

Methods

parseItem :: Item -> Parser (Map Text a) Source #

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

Instances details
MonadFail Parser Source # 
Instance details

Defined in Aws.DynamoDb.Core

Methods

fail :: String -> Parser a #

Alternative Parser Source # 
Instance details

Defined in Aws.DynamoDb.Core

Methods

empty :: Parser a #

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

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

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

Applicative Parser Source # 
Instance details

Defined in Aws.DynamoDb.Core

Methods

pure :: a -> Parser a #

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

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

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

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

Functor Parser Source # 
Instance details

Defined in Aws.DynamoDb.Core

Methods

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

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

Monad Parser Source # 
Instance details

Defined in Aws.DynamoDb.Core

Methods

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

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

return :: a -> Parser a #

MonadPlus Parser Source # 
Instance details

Defined in Aws.DynamoDb.Core

Methods

mzero :: Parser a #

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

Monoid (Parser a) Source # 
Instance details

Defined in Aws.DynamoDb.Core

Methods

mempty :: Parser a #

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

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

Semigroup (Parser a) Source # 
Instance details

Defined in Aws.DynamoDb.Core

Methods

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

sconcat :: NonEmpty (Parser a) -> Parser a #

stimes :: Integral b => b -> Parser a -> Parser a #

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

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

data CondOp Source #

Conditional operation to perform on a field.

Instances

Instances details
ToJSON CondOp Source # 
Instance details

Defined in Aws.DynamoDb.Core

Read CondOp Source # 
Instance details

Defined in Aws.DynamoDb.Core

Show CondOp Source # 
Instance details

Defined in Aws.DynamoDb.Core

Eq CondOp Source # 
Instance details

Defined in Aws.DynamoDb.Core

Methods

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

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

Ord CondOp Source # 
Instance details

Defined in Aws.DynamoDb.Core

data CondMerge Source #

How to merge multiple conditions.

Constructors

CondAnd 
CondOr 

data ConsumedCapacity Source #

The standard response metrics on capacity consumption.

data ReturnConsumption Source #

Constructors

RCIndexes 
RCTotal 
RCNone 

Instances

Instances details
ToJSON ReturnConsumption Source # 
Instance details

Defined in Aws.DynamoDb.Core

Read ReturnConsumption Source # 
Instance details

Defined in Aws.DynamoDb.Core

Show ReturnConsumption Source # 
Instance details

Defined in Aws.DynamoDb.Core

Default ReturnConsumption Source # 
Instance details

Defined in Aws.DynamoDb.Core

Eq ReturnConsumption Source # 
Instance details

Defined in Aws.DynamoDb.Core

Ord ReturnConsumption Source # 
Instance details

Defined in Aws.DynamoDb.Core

data ItemCollectionMetrics Source #

Constructors

ItemCollectionMetrics 

Fields

Instances

Instances details
FromJSON ItemCollectionMetrics Source # 
Instance details

Defined in Aws.DynamoDb.Core

Read ItemCollectionMetrics Source # 
Instance details

Defined in Aws.DynamoDb.Core

Show ItemCollectionMetrics Source # 
Instance details

Defined in Aws.DynamoDb.Core

Eq ItemCollectionMetrics Source # 
Instance details

Defined in Aws.DynamoDb.Core

Ord ItemCollectionMetrics Source # 
Instance details

Defined in Aws.DynamoDb.Core

data ReturnItemCollectionMetrics Source #

Constructors

RICMSize 
RICMNone 

Instances

Instances details
ToJSON ReturnItemCollectionMetrics Source # 
Instance details

Defined in Aws.DynamoDb.Core

Read ReturnItemCollectionMetrics Source # 
Instance details

Defined in Aws.DynamoDb.Core

Show ReturnItemCollectionMetrics Source # 
Instance details

Defined in Aws.DynamoDb.Core

Default ReturnItemCollectionMetrics Source # 
Instance details

Defined in Aws.DynamoDb.Core

Eq ReturnItemCollectionMetrics Source # 
Instance details

Defined in Aws.DynamoDb.Core

Ord ReturnItemCollectionMetrics Source # 
Instance details

Defined in Aws.DynamoDb.Core

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 #

Instances

Instances details
DynSize AttributeUpdate Source # 
Instance details

Defined in Aws.DynamoDb.Commands.UpdateItem

DynSize Attribute Source # 
Instance details

Defined in Aws.DynamoDb.Core

DynSize DValue Source # 
Instance details

Defined in Aws.DynamoDb.Core

Methods

dynSize :: DValue -> Int Source #

DynSize Item Source # 
Instance details

Defined in Aws.DynamoDb.Core

Methods

dynSize :: Item -> Int Source #

DynSize a => DynSize (Maybe a) Source # 
Instance details

Defined in Aws.DynamoDb.Core

Methods

dynSize :: Maybe a -> Int Source #

DynSize a => DynSize [a] Source # 
Instance details

Defined in Aws.DynamoDb.Core

Methods

dynSize :: [a] -> Int Source #

(DynSize a, DynSize b) => DynSize (Either a b) Source # 
Instance details

Defined in Aws.DynamoDb.Core

Methods

dynSize :: Either a b -> 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

Instances

Instances details
Exception DdbError Source # 
Instance details

Defined in Aws.DynamoDb.Core

Show DdbError Source # 
Instance details

Defined in Aws.DynamoDb.Core

Eq DdbError Source # 
Instance details

Defined in Aws.DynamoDb.Core

Internal Helpers

data AmazonError Source #

Constructors

AmazonError 

Fields

Instances

Instances details
FromJSON AmazonError Source # 
Instance details

Defined in Aws.DynamoDb.Core