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

LicenseBSD-style
Maintainerpalkovsky.ondrej@gmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Database.DynamoDB

Contents

Description

Type-safe library for accessing DynamoDB database.

Synopsis

Introduction

This library is operated in the following way:

  • Create instances for your custom types using Database.DynamoDB.Types
  • Create ordinary datatypes with records
  • Use functions from Database.DynamoDB.TH to derive appropriate instances
  • Optionally call generated migration function to automatically create tables and indices
  • Call functions from this module to access the database

The library does its best to ensure that only correct DynamoDB operations are allowed. There are some limitations of DynamoDB regarding access to empty values, but the library takes care of this reasonably well.

Example of use

You may need to set AWS_ACCESS_KEY_ID and AWS_SECRET_ACCESS_KEY environment variables.

data Test = Test {
    category :: T.Text
  , messageid :: T.Text
  , subject :: T.Text
} deriving (Show)
mkTableDefs "migrate" (tableConfig (''Test, WithRange) [] [])

This code creates appropriate instances for the table and the columns. It creates global variables colCategory, colMessageid and colSubject that can be used in filtering conditions or update queries.

main = do
   lgr <- newLogger Info stdout
   env <- newEnv NorthVirginia Discover
   -- Override, use DynamoDD on localhost
   let dynamo = setEndpoint False "localhost" 8000 dynamoDB
   let newenv = env & configure dynamo
                    & set envLogger lgr
   runResourceT $ runAWS newenv $ do
       -- Create tables and indexes
       migrate mempty Nothing
       -- Save data to database
       putItem (Test "news" "1-2-3-4" "New subject")
       -- Fetch data given primary key
       item <- getItem Eventually (tTest, ("news", "1-2-3-4"))
       liftIO $ print item       -- (item :: Maybe Test)
       -- Scan data using filter condition, return 10 results
       items <- scanCond tTest (subject' ==. "New subejct") 10
       print items         -- (items :: [Test])

See examples and test directories for more detail examples.

Proxies

In order to avoid ambiguity errors, most API calls need a Proxy argument to find out on which table or index to operate. These proxies are automatically generated as a name of type prepended with "t" for tables and "i" for indexes.

A proxy for table Test will have name tTest, for index TestIndex the name will be iTestIndex.

Lens support

If the field names in the table record start with an underscore, the lens get automatically generated for accessing the fields. The lens are polymorphic, you can use them to access the fields of both main table and all the indexes.

data Test = Test {
    _messageid :: T.Text
  , _category :: T.Text
  , _subject :: T.Text
} deriving (Show)
data TestIndex = TestIndex {
    _category :: T.Text
  , _messageid :: T.Text
}
mkTableDefs "migrate" (tableConfig (''Test, WithRange) [(''TestIndex, NoRange)] [])

doWithTest :: Test -> ...
doWithTest item = (item ^. category) ...

doWithItemIdx :: TestIndex -> ..
getCategoryIdx item = (item ^. category) ...

Data types

data Consistency Source #

Parameter for queries involving read consistency settings.

Constructors

Eventually 
Strongly 

data Direction Source #

Query direction

Constructors

Forward 
Backward 

data Column typ coltype col Source #

Representation of a column for filter queries

  • typ - datatype of column (Int, Text..)
  • coltype - TypColumn or TypSize (result of size(column))
  • col - instance of ColumnInfo, uniquely identify a column

Attribute path combinators

(<.>) :: InCollection col2 (UnMaybe typ) NestedPath => Column typ TypColumn col1 -> Column typ2 TypColumn col2 -> Column typ2 TypColumn col1 infixl 7 Source #

Combine attributes from nested structures.

address' <.> street'

(<!>) :: Column [typ] TypColumn col -> Int -> Column typ TypColumn col infixl 8 Source #

Access an index in a nested list.

users' <!> 0 <.> name'

(<!:>) :: IsText key => Column (HashMap key typ) TypColumn col -> key -> Column typ TypColumn col infixl 8 Source #

Access a key in a nested hashmap.

phones' <!:> "mobile" <.> number'

Fetching items

getItem :: forall m a r range hash rest. (MonadAWS m, DynamoTable a r, HasPrimaryKey a r IsTable, Code a ~ '[hash ': (range ': rest)]) => Consistency -> (Proxy a, PrimaryKey (Code a) r) -> m (Maybe a) Source #

Read item from the database; primary key is either a hash key or (hash,range) tuple depending on the table.

getItemBatch :: forall m a r range hash rest. (MonadAWS m, DynamoTable a r, HasPrimaryKey a r IsTable, Code a ~ '[hash ': (range ': rest)]) => Consistency -> [PrimaryKey (Code a) r] -> m [a] Source #

Get batch of items.

Query options

data QueryOpts a hash range Source #

Options for a generic query.

queryOpts :: hash -> QueryOpts a hash range Source #

Default settings for query options.

qConsistentRead :: forall a hash range. Lens' (QueryOpts a hash range) Consistency Source #

qStartKey :: forall a hash range. Lens' (QueryOpts a hash range) (Maybe (hash, range)) Source #

qDirection :: forall a hash range. Lens' (QueryOpts a hash range) Direction Source #

qFilterCondition :: forall a hash range a. Lens (QueryOpts a hash range) (QueryOpts a hash range) (Maybe (FilterCondition a)) (Maybe (FilterCondition a)) Source #

qHashKey :: forall a hash range. Lens' (QueryOpts a hash range) hash Source #

qRangeCondition :: forall a hash range. Lens' (QueryOpts a hash range) (Maybe (RangeOper range)) Source #

qLimit :: forall a hash range. Lens' (QueryOpts a hash range) (Maybe Natural) Source #

Performing query

query Source #

Arguments

:: (TableQuery a t, DynamoCollection a WithRange t, MonadAWS m, Code a ~ '[hash ': (range ': rest)], DynamoScalar v1 hash, DynamoScalar v2 range) 
=> Proxy a 
-> QueryOpts a hash range 
-> Int

Maximum number of items to fetch

-> m ([a], Maybe (PrimaryKey (Code a) WithRange)) 

Fetch exactly the required count of items even when it means more calls to dynamodb. Return last evaluted key if end of data was not reached. Use qStartKey to continue reading the query.

querySimple Source #

Arguments

:: (TableQuery a t, MonadAWS m, Code a ~ '[hash ': (range ': rest)], DynamoScalar v1 hash, DynamoScalar v2 range) 
=> Proxy a

Proxy type of a table to query

-> hash

Hash key

-> Maybe (RangeOper range)

Range condition

-> Direction

Scan direction

-> Int

Maximum number of items to fetch

-> m [a] 

Perform a simple, eventually consistent, query.

Simple to use function to query limited amount of data from database.

queryCond Source #

Arguments

:: (TableQuery a t, MonadAWS m, Code a ~ '[hash ': (range ': rest)], DynamoScalar v1 hash, DynamoScalar v2 range) 
=> Proxy a 
-> hash

Hash key

-> Maybe (RangeOper range)

Range condition

-> FilterCondition a 
-> Direction

Scan direction

-> Int

Maximum number of items to fetch

-> m [a] 

Query with condition

querySource :: forall a t m v1 v2 hash range rest. (TableQuery a t, MonadAWS m, Code a ~ '[hash ': (range ': rest)], DynamoScalar v1 hash, DynamoScalar v2 range) => Proxy a -> QueryOpts a hash range -> Source m a Source #

Generic query function. You can query table or indexes that have a range key defined. The filter condition cannot access the hash and range keys.

Scan options

data ScanOpts a r Source #

Record for defining scan command. Use lenses to set the content.

sParallel: (Segment number, Total segments)

sLimit :: forall a r. Lens' (ScanOpts a r) (Maybe Natural) Source #

sParallel :: forall a r. Lens' (ScanOpts a r) (Maybe (Natural, Natural)) Source #

sStartKey :: forall a r r. Lens (ScanOpts a r) (ScanOpts a r) (Maybe (PrimaryKey (Code a) r)) (Maybe (PrimaryKey (Code a) r)) Source #

Performing scan

scan Source #

Arguments

:: (MonadAWS m, Code a ~ '[hash ': (range ': rest)], TableScan a r t, HasPrimaryKey a r t) 
=> Proxy a 
-> ScanOpts a r

Scan settings

-> Int

Required result count

-> m ([a], Maybe (PrimaryKey (Code a) r))

list of results, lastEvalutedKey or Nothing if end of data reached

Function to call bounded scans. Tries to return exactly requested number of items.

Use sStartKey to continue the scan.

scanSource :: (MonadAWS m, TableScan a r t, HasPrimaryKey a r t, Code a ~ '[hash ': (range ': xss)]) => Proxy a -> ScanOpts a r -> Source m a Source #

Conduit source for running a scan.

scanCond :: forall a m hash range rest r t. (MonadAWS m, HasPrimaryKey a r t, Code a ~ '[hash ': (range ': rest)], TableScan a r t) => Proxy a -> FilterCondition a -> Int -> m [a] Source #

Scan table using a given filter condition.

scanCond (colAddress <!:> "Home" <.> colCity ==. "London") 10

Data entry

putItem :: (MonadAWS m, DynamoTable a r) => a -> m () Source #

Write item into the database; overwrite any previously existing item with the same primary key.

putItemBatch :: forall m a r. (MonadAWS m, DynamoTable a r) => [a] -> m () Source #

Batch write into the database.

The batch is divided to 25-item chunks, each is sent and retried separately. If a batch fails on dynamodb exception, it is raised.

Note: On exception, the information about which items were saved is unavailable

insertItem :: forall a r m. (MonadAWS m, DynamoTable a r) => a -> m () Source #

Write item into the database only if it doesn't already exist.

Data modification

updateItemByKey :: forall a m r hash range rest. (MonadAWS m, HasPrimaryKey a r IsTable, DynamoTable a r, Code a ~ '[hash ': (range ': rest)]) => (Proxy a, PrimaryKey (Code a) r) -> Action a -> m a Source #

updateItemByKey_ :: forall a m r hash range rest. (MonadAWS m, HasPrimaryKey a r IsTable, DynamoTable a r, Code a ~ '[hash ': (range ': rest)]) => (Proxy a, PrimaryKey (Code a) r) -> Action a -> m () Source #

Update item in a table

updateItem (Proxy :: Proxy Test) (12, "2") [colCount +=. 100]

updateItemCond_ :: forall a m r hash range rest. (MonadAWS m, DynamoTable a r, HasPrimaryKey a r IsTable, Code a ~ '[hash ': (range ': rest)]) => (Proxy a, PrimaryKey (Code a) r) -> Action a -> FilterCondition a -> m () Source #

Update item in a table while specifying a condition

Deleting data

deleteItemByKey :: forall m a r hash range rest. (MonadAWS m, HasPrimaryKey a r IsTable, DynamoTable a r, Code a ~ '[hash ': (range ': rest)]) => (Proxy a, PrimaryKey (Code a) r) -> m () Source #

Delete item from the database by specifying the primary key.

deleteItemCondByKey :: forall m a r hash range rest. (MonadAWS m, HasPrimaryKey a r IsTable, DynamoTable a r, Code a ~ '[hash ': (range ': rest)]) => (Proxy a, PrimaryKey (Code a) r) -> FilterCondition a -> m () Source #

Delete item from the database by specifying the primary key and a condition. Throws AWS exception if the condition does not succeed.

deleteItemBatchByKey :: forall m a r range hash rest. (MonadAWS m, HasPrimaryKey a r IsTable, DynamoTable a r, Code a ~ '[hash ': (range ': rest)]) => Proxy a -> [PrimaryKey (Code a) r] -> m () Source #

Batch version of deleteItemByKey.

Note: Because the requests are chunked, the information about which items were deleted in case of exception is unavailable.

Delete table

deleteTable :: (MonadAWS m, DynamoTable a r) => Proxy a -> m () Source #

Delete table from DynamoDB.

Utility functions

tableKey :: forall a parent key. ContainsTableKey a parent key => a -> (Proxy parent, key) Source #

Extract primary key from a record in a form that can be directly used by other functions.

You can use this on both main table or on index tables if they contain the primary key from the main table. Table key is always projected to indexes anyway, so just define it in every index.