{-# LANGUAGE QuantifiedConstraints #-}
{-# LANGUAGE TypeFamilyDependencies #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Database.CQRS.TabularData
( TabularDataAction(..)
, Condition(..)
, Conditions(..)
, equal
, notEqual
, lowerThan
, lowerThanOrEqual
, greaterThan
, greaterThanOrEqual
, Update(..)
, set
, plus
, minus
, Columns(..)
, Tuple
, Flatten
, FlatTuple(..)
, pattern (:~)
, empty
, Table
, field
, ffield
, MergeSplitTuple(..)
, applyTabularDataAction
, GetKeyAndConditions
, AllColumns
, toList
) where
import Control.Monad (foldM)
import Data.Hashable (Hashable(..))
import Data.Kind (Type)
import Data.List (foldl')
import qualified Control.Monad.Except as Exc
import qualified Control.Monad.Identity as Id
import qualified Control.Monad.State.Strict as St
import qualified Data.HashMap.Strict as HM
import Database.CQRS.TabularData.Internal
import qualified Database.CQRS as CQRS
equal :: Eq a => a -> Conditions a
equal = Conditions . pure . Equal
notEqual :: Eq a => a -> Conditions a
notEqual = Conditions . pure . NotEqual
lowerThan :: Ord a => a -> Conditions a
lowerThan = Conditions . pure . LowerThan
lowerThanOrEqual :: Ord a => a -> Conditions a
lowerThanOrEqual = Conditions . pure . LowerThanOrEqual
greaterThan :: Ord a => a -> Conditions a
greaterThan = Conditions . pure . GreaterThan
greaterThanOrEqual :: Ord a => a -> Conditions a
greaterThanOrEqual = Conditions . pure . GreaterThanOrEqual
set :: a -> Update a
set = Set
plus :: Num a => a -> Update a
plus = Plus
minus :: Num a => a -> Update a
minus = Minus
data TabularDataAction (cols :: Columns) where
Insert :: Tuple Id.Identity cols -> TabularDataAction cols
Update :: Tuple Update cols -> Tuple Conditions cols -> TabularDataAction cols
Upsert
:: Tuple Id.Identity ('WithUniqueKey keyCols cols)
-> TabularDataAction ('WithUniqueKey keyCols cols)
Delete :: Tuple Conditions cols -> TabularDataAction cols
deriving instance
AllColumns Show (Flatten cols) => Show (TabularDataAction cols)
type family Table (cols :: Columns) :: Type where
Table ('WithUniqueKey keyCols cols) =
HM.HashMap (FlatTuple Id.Identity keyCols) (FlatTuple Id.Identity cols)
Table ('Flat cols) = [FlatTuple Id.Identity cols]
class ApplyTabularDataAction f (cols :: Columns) where
applyTabularDataAction
:: Table cols -> TabularDataAction cols -> f (Table cols)
instance Applicative f => ApplyTabularDataAction f ('Flat cols) where
applyTabularDataAction tbl = pure . \case
Insert tuple -> tuple : tbl
Update updates conditions ->
map (\tuple ->
if tuple `matches` conditions
then update updates tuple
else tuple) tbl
Delete conditions -> filter (`matches` conditions) tbl
instance
( AllColumns Show keyCols
, Exc.MonadError CQRS.Error m
, GetKeyAndConditions keyCols cols
, Hashable (FlatTuple Id.Identity keyCols)
, Ord (FlatTuple Id.Identity keyCols)
, MergeSplitTuple keyCols cols
)
=> ApplyTabularDataAction m ('WithUniqueKey keyCols cols) where
applyTabularDataAction tbl = \case
Insert tuple -> do
let (keyTuple, otherTuple) = splitTuple tuple
op = \case
Nothing -> pure $ Just otherTuple
Just _ -> Exc.throwError . CQRS.ProjectionError $
"duplicate key on insert: " ++ show keyTuple
HM.alterF op keyTuple tbl
Update updates conditions ->
case getKeyAndConditions conditions of
Just (keyTuple, otherConditions) ->
case HM.lookup keyTuple tbl of
Nothing -> pure tbl
Just otherTuple
| otherTuple `matches` otherConditions -> do
let (keyTuple', otherTuple') =
splitTuple . update updates . mergeTuple
$ (keyTuple, otherTuple)
if keyTuple == keyTuple'
then pure $ HM.insert keyTuple otherTuple' tbl
else
case HM.lookup keyTuple' tbl of
Nothing ->
pure . HM.delete keyTuple
. HM.insert keyTuple' otherTuple' $ tbl
Just _ ->
Exc.throwError . CQRS.ProjectionError $
"duplicate key on update: " ++ show keyTuple'
| otherwise -> pure tbl
Nothing -> do
let step keyTuple otherTuple = do
let merged = mergeTuple (keyTuple, otherTuple)
if merged `matches` conditions
then do
let (keyTuple', otherTuple') =
splitTuple $ update updates merged
if keyTuple == keyTuple'
then pure $ Just otherTuple'
else do
St.modify' $ \(tbd, tbi) ->
(keyTuple : tbd, (keyTuple', otherTuple') : tbi)
pure $ Just otherTuple
else pure $ Just otherTuple
(toBeDeleted, toBeInserted) =
St.execState (HM.traverseWithKey step tbl) ([], [])
tbl' = foldl' (flip HM.delete) tbl toBeDeleted
foldM
(\t (keyTuple, otherTuple) ->
case HM.lookup keyTuple t of
Just _ -> Exc.throwError . CQRS.ProjectionError $
"duplicate key on update: " ++ show keyTuple
Nothing -> pure . HM.insert keyTuple otherTuple $ t
)
tbl' toBeInserted
Upsert tuple -> do
let (keyTuple, otherTuple) = splitTuple tuple
pure $ HM.insert keyTuple otherTuple tbl
Delete conditions ->
case getKeyAndConditions conditions of
Just (keyTuple, otherConditions) -> do
let op = \case
Nothing -> Nothing
Just otherTuple
| otherTuple `matches` otherConditions -> Nothing
| otherwise -> Just otherTuple
pure . HM.alter op keyTuple $ tbl
Nothing -> do
let op keyTuple otherTuple
| mergeTuple (keyTuple, otherTuple) `matches` conditions =
Nothing
| otherwise = Just otherTuple
pure . HM.mapMaybeWithKey op $ tbl