Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Condition a where
- newtype Conditions a = Conditions {
- getConditions :: [Condition a]
- data Columns where
- type family Flatten (cols :: k) :: [(Symbol, Type)] where ...
- type Tuple f cols = FlatTuple f (Flatten cols)
- data FlatTuple :: (Type -> Type) -> [(Symbol, Type)] -> Type where
- pattern (:~) :: a -> FlatTuple Identity cols -> FlatTuple Identity ('(sym, a) ': cols)
- empty :: FlatTuple f '[]
- class Field f (sym :: Symbol) a (cols :: [(Symbol, Type)]) | cols sym -> a where
- class Wrapper f a where
- wrap :: a -> f a
- field :: forall cols sym f a. (Field f sym a (Flatten cols), Wrapper f a) => a -> Tuple f cols
- ffield :: forall cols sym f a. Field f sym a (Flatten cols) => f a -> Tuple f cols
- class MergeSplitTuple keyCols cols where
- mergeTuple :: (FlatTuple f keyCols, FlatTuple f cols) -> Tuple f (WithUniqueKey keyCols cols)
- splitTuple :: Tuple f (WithUniqueKey keyCols cols) -> (FlatTuple f keyCols, FlatTuple f cols)
- type family AllColumns (cs :: Type -> Constraint) (cols :: [(Symbol, Type)]) :: Constraint where ...
- toList :: forall cs cols f b. AllColumns cs cols => (forall a. cs a => String -> f a -> b) -> FlatTuple f cols -> [b]
- class GetKeyAndConditions keyCols cols where
- getKeyAndConditions :: Tuple Conditions (WithUniqueKey keyCols cols) -> Maybe (FlatTuple Identity keyCols, FlatTuple Conditions cols)
- matches :: FlatTuple Identity cols -> FlatTuple Conditions cols -> Bool
- matchesCond :: a -> Condition a -> Bool
- data Update a where
- update :: FlatTuple Update cols -> FlatTuple Identity cols -> FlatTuple Identity cols
Documentation
data Condition a where Source #
Equal :: Eq a => a -> Condition a | |
NotEqual :: Eq a => a -> Condition a | |
LowerThan :: Ord a => a -> Condition a | |
LowerThanOrEqual :: Ord a => a -> Condition a | |
GreaterThan :: Ord a => a -> Condition a | |
GreaterThanOrEqual :: Ord a => a -> Condition a |
newtype Conditions a Source #
Conditions | |
|
Instances
Eq a => Wrapper Conditions a Source # | |
Defined in Database.CQRS.TabularData.Internal wrap :: a -> Conditions a Source # | |
Eq (Conditions a) Source # | |
Defined in Database.CQRS.TabularData.Internal (==) :: Conditions a -> Conditions a -> Bool # (/=) :: Conditions a -> Conditions a -> Bool # | |
Show a => Show (Conditions a) Source # | |
Defined in Database.CQRS.TabularData.Internal showsPrec :: Int -> Conditions a -> ShowS # show :: Conditions a -> String # showList :: [Conditions a] -> ShowS # | |
Semigroup (Conditions a) Source # | |
Defined in Database.CQRS.TabularData.Internal (<>) :: Conditions a -> Conditions a -> Conditions a # sconcat :: NonEmpty (Conditions a) -> Conditions a # stimes :: Integral b => b -> Conditions a -> Conditions a # | |
Monoid (Conditions a) Source # | |
Defined in Database.CQRS.TabularData.Internal mempty :: Conditions a # mappend :: Conditions a -> Conditions a -> Conditions a # mconcat :: [Conditions a] -> Conditions a # |
Kind of types that describe columns of a table.
This is not intended as a type. It's promoted to a kind.
Use Flat
for simple tables and WithUniqueKey
if you want to be able to
do upserts and/or store tuples in memory with a hash map instead of a list.
type family Flatten (cols :: k) :: [(Symbol, Type)] where ... Source #
Flatten (WithUniqueKey (col ': keyCols) cols) = col ': Flatten (WithUniqueKey keyCols cols) | |
Flatten (WithUniqueKey '[] cols) = cols | |
Flatten (Flat cols) = cols |
type Tuple f cols = FlatTuple f (Flatten cols) Source #
A named tuple representing a row in the table.
data FlatTuple :: (Type -> Type) -> [(Symbol, Type)] -> Type where Source #
Instances
(Eq (f a), Eq (FlatTuple f cols)) => Eq (FlatTuple f ((,) sym a ': cols)) Source # | |
Eq (FlatTuple f ([] :: [(Symbol, Type)])) Source # | |
(Ord (f a), Ord (FlatTuple f cols)) => Ord (FlatTuple f ((,) sym a ': cols)) Source # | |
Defined in Database.CQRS.TabularData.Internal compare :: FlatTuple f ((sym, a) ': cols) -> FlatTuple f ((sym, a) ': cols) -> Ordering # (<) :: FlatTuple f ((sym, a) ': cols) -> FlatTuple f ((sym, a) ': cols) -> Bool # (<=) :: FlatTuple f ((sym, a) ': cols) -> FlatTuple f ((sym, a) ': cols) -> Bool # (>) :: FlatTuple f ((sym, a) ': cols) -> FlatTuple f ((sym, a) ': cols) -> Bool # (>=) :: FlatTuple f ((sym, a) ': cols) -> FlatTuple f ((sym, a) ': cols) -> Bool # max :: FlatTuple f ((sym, a) ': cols) -> FlatTuple f ((sym, a) ': cols) -> FlatTuple f ((sym, a) ': cols) # min :: FlatTuple f ((sym, a) ': cols) -> FlatTuple f ((sym, a) ': cols) -> FlatTuple f ((sym, a) ': cols) # | |
Ord (FlatTuple f ([] :: [(Symbol, Type)])) Source # | |
Defined in Database.CQRS.TabularData.Internal compare :: FlatTuple f [] -> FlatTuple f [] -> Ordering # (<) :: FlatTuple f [] -> FlatTuple f [] -> Bool # (<=) :: FlatTuple f [] -> FlatTuple f [] -> Bool # (>) :: FlatTuple f [] -> FlatTuple f [] -> Bool # (>=) :: FlatTuple f [] -> FlatTuple f [] -> Bool # | |
(AllColumns Show cols, forall a. Show a => Show (f a)) => Show (FlatTuple f cols) Source # | |
(Semigroup (f a), Semigroup (FlatTuple f cols)) => Semigroup (FlatTuple f ((,) sym a ': cols)) Source # | |
Defined in Database.CQRS.TabularData.Internal | |
Semigroup (FlatTuple f ([] :: [(Symbol, Type)])) Source # | |
(Monoid (f a), Monoid (FlatTuple f xs)) => Monoid (FlatTuple f ((,) sym a ': xs)) Source # | |
Monoid (FlatTuple f ([] :: [(Symbol, Type)])) Source # | |
(Hashable (f a), Hashable (FlatTuple f cols)) => Hashable (FlatTuple f ((,) sym a ': cols)) Source # | |
Defined in Database.CQRS.TabularData.Internal | |
Hashable (FlatTuple f ([] :: [(Symbol, Type)])) Source # | |
Defined in Database.CQRS.TabularData.Internal |
pattern (:~) :: a -> FlatTuple Identity cols -> FlatTuple Identity ('(sym, a) ': cols) infixr 5 Source #
class Field f (sym :: Symbol) a (cols :: [(Symbol, Type)]) | cols sym -> a where Source #
class Wrapper f a where Source #
Instances
Wrapper Update a Source # | |
Defined in Database.CQRS.TabularData.Internal | |
Eq a => Wrapper Conditions a Source # | |
Defined in Database.CQRS.TabularData.Internal wrap :: a -> Conditions a Source # |
field :: forall cols sym f a. (Field f sym a (Flatten cols), Wrapper f a) => a -> Tuple f cols Source #
Create a tuple with the given field set to the given value wrapped into
f
. In practice, f
is Conditions
or Update
.
It is meant to be used together with TypeApplications
, e.g.
field
"field_name" value
@
ffield :: forall cols sym f a. Field f sym a (Flatten cols) => f a -> Tuple f cols Source #
Create a tuple with the given field set to the given "wrapped" value.
It is more flexible than field
but less convenient to use if the goal is to
simply wrap the value inside the Applicative
. In particular, it can be used
with Conditions
such as
ffield
"email" (equal "someoneexample.com")
class MergeSplitTuple keyCols cols where Source #
mergeTuple :: (FlatTuple f keyCols, FlatTuple f cols) -> Tuple f (WithUniqueKey keyCols cols) Source #
splitTuple :: Tuple f (WithUniqueKey keyCols cols) -> (FlatTuple f keyCols, FlatTuple f cols) Source #
Instances
MergeSplitTuple ([] :: [(Symbol, Type)]) cols Source # | |
Defined in Database.CQRS.TabularData.Internal mergeTuple :: (FlatTuple f [], FlatTuple f cols) -> Tuple f (WithUniqueKey [] cols) Source # splitTuple :: Tuple f (WithUniqueKey [] cols) -> (FlatTuple f [], FlatTuple f cols) Source # | |
MergeSplitTuple keyCols cols => MergeSplitTuple (a ': keyCols) cols Source # | |
Defined in Database.CQRS.TabularData.Internal mergeTuple :: (FlatTuple f (a ': keyCols), FlatTuple f cols) -> Tuple f (WithUniqueKey (a ': keyCols) cols) Source # splitTuple :: Tuple f (WithUniqueKey (a ': keyCols) cols) -> (FlatTuple f (a ': keyCols), FlatTuple f cols) Source # |
type family AllColumns (cs :: Type -> Constraint) (cols :: [(Symbol, Type)]) :: Constraint where ... Source #
AllColumns _ '[] = () | |
AllColumns cs ('(sym, a) ': cols) = (cs a, KnownSymbol sym, AllColumns cs cols) |
toList :: forall cs cols f b. AllColumns cs cols => (forall a. cs a => String -> f a -> b) -> FlatTuple f cols -> [b] Source #
Transform a tuple into a list of pairs given a function to transform the field values.
cs
is some constraint that the values need to satisfy. For example,
toList
Show (name value -> (name, maybe NULL show (getLast value)))
:: Tuple Last cols -> [(String, String)]
@
class GetKeyAndConditions keyCols cols where Source #
Used to optimise operations on the in-memory storage. When we want to
update or delete rows based on some conditions that would match one row
matching its key, it's more efficient to use alter
instead of traversing
the hash map.
getKeyAndConditions :: Tuple Conditions (WithUniqueKey keyCols cols) -> Maybe (FlatTuple Identity keyCols, FlatTuple Conditions cols) Source #
Instances
GetKeyAndConditions ([] :: [(Symbol, Type)]) cols Source # | |
Defined in Database.CQRS.TabularData.Internal getKeyAndConditions :: Tuple Conditions (WithUniqueKey [] cols) -> Maybe (FlatTuple Identity [], FlatTuple Conditions cols) Source # | |
GetKeyAndConditions keyCols cols => GetKeyAndConditions ((,) sym a ': keyCols) cols Source # | |
Defined in Database.CQRS.TabularData.Internal getKeyAndConditions :: Tuple Conditions (WithUniqueKey ((sym, a) ': keyCols) cols) -> Maybe (FlatTuple Identity ((sym, a) ': keyCols), FlatTuple Conditions cols) Source # |
matchesCond :: a -> Condition a -> Bool Source #