dynamodb-simple-0.6.0.0: 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.

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 # 
DynamoEncodable Double Source # 
DynamoEncodable Int Source # 
DynamoEncodable Int16 Source # 
DynamoEncodable Int32 Source # 
DynamoEncodable Int64 Source # 
DynamoEncodable Integer Source # 
DynamoEncodable Word Source # 
DynamoEncodable ByteString Source # 
DynamoEncodable Scientific Source # 
DynamoEncodable Text Source # 
DynamoEncodable Value Source #

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

DynamoEncodable UUID Source # 
DynamoEncodable a => DynamoEncodable [a] Source #

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

DynamoEncodable a => DynamoEncodable (Maybe a) Source #

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

(Ord a, DynamoScalar v a) => DynamoEncodable (Set a) Source # 
(IsText t, DynamoEncodable a) => DynamoEncodable (HashMap t a) Source # 
DynamoEncodable a => DynamoEncodable (Tagged * v a) Source # 

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

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 # 
DynamoScalar S UUID Source # 
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.

DynamoScalar N Int Source # 
DynamoScalar N Int16 Source # 
DynamoScalar N Int32 Source # 
DynamoScalar N Int64 Source # 
DynamoScalar N Integer Source # 
DynamoScalar N Word Source # 
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.

DynamoScalar B ByteString Source # 
DynamoScalar v a => DynamoScalar v (Tagged * x a) Source #

Helper for tagged values

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.

Minimal complete definition

toText, fromText

Methods

toText :: a -> Text Source #

fromText :: Text -> a Source #

Instances

class IsNumber a Source #

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

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 #