| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Database.DynamoDB.Types
Description
Synopsis
- data DynamoException = DynamoException Text
- class DynamoEncodable a where- dEncode :: a -> Maybe AttributeValue
- dDecode :: Maybe AttributeValue -> Maybe a
- dDecodeEither :: Maybe AttributeValue -> Either Text a
- dIsMissing :: a -> Bool
 
- class ScalarAuto v => DynamoScalar (v :: ScalarAttributeType) a | a -> v where- scalarEncode :: a -> ScalarValue v
- scalarDecode :: ScalarValue v -> Maybe a
 
- data ScalarValue (v :: ScalarAttributeType) where- ScS :: !Text -> ScalarValue S
- ScN :: !Scientific -> ScalarValue N
- ScB :: !ByteString -> ScalarValue B
 
- class (Eq a, Hashable a) => IsText a where
- class IsNumber a
- data RangeOper a where- 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
 
- dType :: forall a v. DynamoScalar v a => Proxy a -> ScalarAttributeType
- dScalarEncode :: DynamoScalar v a => a -> AttributeValue
Exceptions
data DynamoException Source #
Exceptions thrown by some dynamodb-simple actions.
Constructors
| DynamoException Text | 
Instances
| Show DynamoException Source # | |
| Defined in Database.DynamoDB.Types Methods showsPrec :: Int -> DynamoException -> ShowS # show :: DynamoException -> String # showList :: [DynamoException] -> ShowS # | |
| Exception DynamoException Source # | |
| Defined in Database.DynamoDB.Types Methods toException :: DynamoException -> SomeException # | |
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
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
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.
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 #
dScalarEncode :: DynamoScalar v a => a -> AttributeValue Source #