dynamodb-simple-0.6.0.2: Typesafe library for working with DynamoDB database

Safe HaskellNone
LanguageHaskell2010

Database.DynamoDB.Types

Contents

Description

 
Synopsis

Exceptions

Marshalling

class DynamoEncodable a where Source #

Typeclass showing that this datatype can be saved to DynamoDB.

Minimal complete definition

Nothing

Methods

dEncode :: a -> Maybe AttributeValue Source #

Encode data. Return Nothing if attribute should be omitted.

dEncode :: (Show a, Read a) => a -> Maybe AttributeValue Source #

Encode data. Return Nothing if attribute should be omitted.

dDecode :: Maybe AttributeValue -> Maybe a Source #

Decode data. Return Nothing on parsing error, gets Nothing on input if the attribute was missing in the database.

dDecode :: (Show a, Read a) => Maybe AttributeValue -> Maybe a Source #

Decode data. Return Nothing on parsing error, gets Nothing on input if the attribute was missing in the database.

dDecodeEither :: Maybe AttributeValue -> Either Text a Source #

Decode data. Return (Left err) on parsing error, gets Nothing on input if the attribute was missing in the database. The default instance uses dDecode, define this just for better errors

dIsMissing :: a -> Bool Source #

Aid for searching for empty list and hashmap; these can be represented both by empty list and by missing value, if this returns true, enhance search. Also used by joins to weed out empty foreign keys

Instances
DynamoEncodable Bool Source # 
Instance details

Defined in Database.DynamoDB.Types

DynamoEncodable Double Source # 
Instance details

Defined in Database.DynamoDB.Types

DynamoEncodable Int Source # 
Instance details

Defined in Database.DynamoDB.Types

DynamoEncodable Int16 Source # 
Instance details

Defined in Database.DynamoDB.Types

DynamoEncodable Int32 Source # 
Instance details

Defined in Database.DynamoDB.Types

DynamoEncodable Int64 Source # 
Instance details

Defined in Database.DynamoDB.Types

DynamoEncodable Integer Source # 
Instance details

Defined in Database.DynamoDB.Types

DynamoEncodable Word Source # 
Instance details

Defined in Database.DynamoDB.Types

DynamoEncodable ByteString Source # 
Instance details

Defined in Database.DynamoDB.Types

DynamoEncodable Scientific Source # 
Instance details

Defined in Database.DynamoDB.Types

DynamoEncodable Text Source # 
Instance details

Defined in Database.DynamoDB.Types

DynamoEncodable Value Source #

Partial encoding/decoding Aeson values. Empty strings get converted to NULL.

Instance details

Defined in Database.DynamoDB.Types

DynamoEncodable UUID Source # 
Instance details

Defined in Database.DynamoDB.Types

DynamoEncodable a => DynamoEncodable [a] Source #

DynamoDB cannot represent empty items; [Maybe a] will lose Nothings.

Instance details

Defined in Database.DynamoDB.Types

DynamoEncodable a => DynamoEncodable (Maybe a) Source #

Maybe (Maybe a) will not work well; it will join the value in the database.

Instance details

Defined in Database.DynamoDB.Types

(Ord a, DynamoScalar v a) => DynamoEncodable (Set a) Source # 
Instance details

Defined in Database.DynamoDB.Types

(IsText t, DynamoEncodable a) => DynamoEncodable (HashMap t a) Source # 
Instance details

Defined in Database.DynamoDB.Types

DynamoEncodable a => DynamoEncodable (Tagged v a) Source # 
Instance details

Defined in Database.DynamoDB.Types

class ScalarAuto v => DynamoScalar (v :: ScalarAttributeType) a | a -> v where Source #

Typeclass signifying that this is a scalar attribute and can be used as a hash/sort key.

instance DynamoScalar Network.AWS.DynamoDB.Types.S T.Text where
   scalarEncode = ScS
   scalarDecode (ScS txt) = Just txt

Minimal complete definition

Nothing

Methods

scalarEncode :: a -> ScalarValue v Source #

Scalars must have total encoding function

scalarEncode :: (Show a, Read a, v ~ S) => a -> ScalarValue v Source #

Scalars must have total encoding function

scalarDecode :: ScalarValue v -> Maybe a Source #

scalarDecode :: (Show a, Read a, v ~ S) => ScalarValue v -> Maybe a Source #

Instances
DynamoScalar S Text Source # 
Instance details

Defined in Database.DynamoDB.Types

DynamoScalar S UUID Source # 
Instance details

Defined in Database.DynamoDB.Types

DynamoScalar N Double Source #

Don't use Double as a part of primary key in a table. It is included here for convenience to be used as a range key in indexes.

Instance details

Defined in Database.DynamoDB.Types

DynamoScalar N Int Source # 
Instance details

Defined in Database.DynamoDB.Types

DynamoScalar N Int16 Source # 
Instance details

Defined in Database.DynamoDB.Types

DynamoScalar N Int32 Source # 
Instance details

Defined in Database.DynamoDB.Types

DynamoScalar N Int64 Source # 
Instance details

Defined in Database.DynamoDB.Types

DynamoScalar N Integer Source # 
Instance details

Defined in Database.DynamoDB.Types

DynamoScalar N Word Source # 
Instance details

Defined in Database.DynamoDB.Types

DynamoScalar N Scientific Source #

Double as a primary key isn't generally a good thing as equality on double is sometimes a little dodgy. Use scientific instead.

Instance details

Defined in Database.DynamoDB.Types

DynamoScalar B ByteString Source # 
Instance details

Defined in Database.DynamoDB.Types

DynamoScalar v a => DynamoScalar v (Tagged x a) Source #

Helper for tagged values

Instance details

Defined in Database.DynamoDB.Types

data ScalarValue (v :: ScalarAttributeType) where Source #

Datatype for encoding scalar values

Constructors

ScS :: !Text -> ScalarValue S 
ScN :: !Scientific -> ScalarValue N 
ScB :: !ByteString -> ScalarValue B 

class (Eq a, Hashable a) => IsText a where Source #

Class to limit certain operations to text-like only in queries. Members of this class can be keys to HashMap.

Methods

toText :: a -> Text Source #

fromText :: Text -> a Source #

Instances
IsText Text Source # 
Instance details

Defined in Database.DynamoDB.Types

(Hashable (Tagged t a), IsText a) => IsText (Tagged t a) Source # 
Instance details

Defined in Database.DynamoDB.Types

Methods

toText :: Tagged t a -> Text Source #

fromText :: Text -> Tagged t a Source #

class IsNumber a Source #

Class to limit +=. and -=. for updates.

Instances
IsNumber Double Source # 
Instance details

Defined in Database.DynamoDB.Types

IsNumber Int Source # 
Instance details

Defined in Database.DynamoDB.Types

IsNumber Integer Source # 
Instance details

Defined in Database.DynamoDB.Types

IsNumber a => IsNumber (Tagged t a) Source # 
Instance details

Defined in Database.DynamoDB.Types

Query datatype

data RangeOper a where Source #

Operation on range key for query.

Constructors

RangeEquals :: a -> RangeOper a 
RangeLessThan :: a -> RangeOper a 
RangeLessThanE :: a -> RangeOper a 
RangeGreaterThan :: a -> RangeOper a 
RangeGreaterThanE :: a -> RangeOper a 
RangeBetween :: a -> a -> RangeOper a 
RangeBeginsWith :: IsText a => a -> RangeOper a 

Utility functions

dType :: forall a v. DynamoScalar v a => Proxy a -> ScalarAttributeType Source #