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

Safe HaskellNone
LanguageHaskell2010

Database.DynamoDB.TH

Contents

Description

Template Haskell macros to automatically derive instances, create column datatypes and create migrations functions.

Synopsis

Derive instances for table and indexes

Use mkTableDefs to derive everything about a table and its indexes. After running the function, you will end up with lots of instances, data types for columns (P_TId, P_TBase, P_TDescr) and smart constructors for column (tId', tBase', tDescr', etc.) and one function (migrate) that creates table and updates the indexes.

The migration function has a signature:

 MonadAWS m => HashMap T.Text ProvisionedThroughput -> Maybe StreamViewType -> m0 ()

ProvisionedThroughput hashmap keys are DynamoDB table or index names.

  • Table by default equals name of the type.
  • Attribute names in an index table must be the same as attribute names in the main table (translateField tableFieldName == translateField indexFieldName).
  • Attribute name is a field name from a first underscore (tId). This should make it compatibile with lens.
  • Column name is an attribute name with appended tick: tId'
  • Predefined proxies starting with "t" for tables and "i" for indexes (e.g. tTest, iTestIndex).
  • Polymorphic lens to access fields in both tables and indexes.
  • For indexes with the same dataset as the base table, the conversion function (e.g. toTest) gets created for easy conversion between index and base type.
  • Auxiliary datatype for column is P_ followed by capitalized attribute name (P_TId).
data Test = Test {
    _tId :: Int
  , _tBase :: T.Text
  , _tDescr :: T.Text
  , _tDate :: T.Text
  , _tDict :: HashMap T.Text Inner
} deriving (Show, GHC.Generic)

data TestIndex = TestIndex {
  , i_tDate :: T.Text
  , i_tDescr :: T.Text
} deriving (Show, GHC.Generic)
mkTableDefs "migrate" (tableConfig (''Test, WithRange) [(''TestIndex, NoRange)] [])

Derive instances for nested records

Use deriveCollection for records that are nested. Use deriveEncodable for records that are nested in one table and serve as its own table at the same time.

@ data Book = Book { author :: T.Text , title :: T.Text } deriving (Show)

Sparse indexes

Define sparse index by defining the attribute as Maybe in the main table and directly in the index table.

data Table {
   hashKey :: UUID
 , published :: Maybe UTCTime
 , ...
}
data PublishedIndex {
    published :: UTCTime
 ,  hashKey :: UUID
 ,  ...
}
mkTableDefs "migrate" (tableConfig (''Table, NoRange) [(''PublishedIndex, NoRange)] [])

Main table definition

mkTableDefs Source #

Arguments

:: String

Name of the migration function

-> TableConfig 
-> Q [Dec] 

Create instances, datatypes for table, fields and instances.

Example of what gets created:

data Test { _first :: Text, _second :: Text, _third :: Int }
data TestIndex { u_third :: Int, i_second :: T.Text}

mkTableDefs (tableConfig "" (''Test, WithRange) [(''TestIndex, NoRange)] [])

deriveGenericOnly ''Test
instance DynamoCollection Test WithRange IsTable
...
instance DynamoTable Test WithRange
   tableName _ = "Test"

deriveGenericOnly ''TestIndex
instance DynamoCollection TestIndex NoRange IsIndex
...
instance DynamoIndex TestIndex Test NoRange IsIndex
   indexName _ = "TestIndex"

data P_First
instance ColumnInfo P_First where
    columnName _ = "first"
instance InCollection P_First Test 'NestedPath -- For every attribute
instance InCollection P_Second TestIndex 'FullPath -- For every non-primary attribute
first' :: Column Text TypColumn P_First
first' = Column
-- Polymorphic lenses
class Test_lens_first a b | a -> b where
   first :: Functor f => (a -> f b) -> a -> f b
instance Test_lens_first TestIndex Text where
   first = ...

data TableConfig Source #

Configuration of TH macro for creating table instances

Constructors

TableConfig 

Fields

tableConfig Source #

Arguments

:: String

Prefix for table and index names; dynamodb doesn't have namespaces, this is to remedy the problem.

-> (Name, RangeType)

Table type name, primary key type

-> [(Name, RangeType)]

Global secondary index records, index key type

-> [Name]

Local secondary index records

-> TableConfig 

Simple table configuration

defaultTranslate :: String -> String Source #

Translates haskell field names to database attribute names. Strips everything up to first '_'.

Nested structures

deriveCollection :: Name -> (String -> String) -> Q [Dec] Source #

Derive DynamoEncodable and prepare column instances for nested structures.

deriveEncodable :: Name -> (String -> String) -> Q [Dec] Source #

Derive just the DynamoEncodable instance for structures that were already derived using mkTableDefs and you want to use them as nested structures as well.

Creates:

instance DynamoEncodable Type where
  dEncode val = Just (attributeValue & avM .~ gdEncodeG [fieldnames] val)
  dDecode (Just attr) = gdDecodeG [fieldnames] (attr ^. avM)
  dDecode Nothing = Nothing
instance InCollection column_type P_Column1 'NestedPath
instance InCollection column_type P_Column2 'NestedPath
...

Data types

data RangeType Source #

Data collection type - with hash key or with hash+sort key

Constructors

NoRange 
WithRange