Safe Haskell | None |
---|---|
Language | Haskell98 |
Synopsis
- class (Monoid (QueryResult a), Semigroup (QueryResult a)) => Query a where
- type QueryResult a :: *
- data QueryMorphism q q' = QueryMorphism {
- _queryMorphism_mapQuery :: q -> q'
- _queryMorphism_mapQueryResult :: QueryResult q' -> QueryResult q
- newtype SelectedCount = SelectedCount {}
- combineSelectedCounts :: SelectedCount -> SelectedCount -> Maybe SelectedCount
- class (Group q, Additive q, Query q) => MonadQuery t q m | m -> q t where
- tellQueryDyn :: (Reflex t, MonadQuery t q m) => Dynamic t q -> m ()
- queryDyn :: (Reflex t, Monad m, MonadQuery t q m) => Dynamic t q -> m (Dynamic t (QueryResult q))
- mapQuery :: QueryMorphism q q' -> q -> q'
- mapQueryResult :: QueryMorphism q q' -> QueryResult q' -> QueryResult q
Documentation
class (Monoid (QueryResult a), Semigroup (QueryResult a)) => Query a where Source #
type QueryResult a :: * Source #
crop :: a -> QueryResult a -> QueryResult a Source #
Instances
(Ord k, Query v) => Query (MonoidalMap k v) Source # | |
Defined in Reflex.Query.Class type QueryResult (MonoidalMap k v) :: * Source # crop :: MonoidalMap k v -> QueryResult (MonoidalMap k v) -> QueryResult (MonoidalMap k v) Source # |
data QueryMorphism q q' Source #
NB: QueryMorphism's must be group homomorphisms when acting on the query type and compatible with the query relationship when acting on the query result
QueryMorphism | |
|
Instances
Category QueryMorphism Source # | |
Defined in Reflex.Query.Class id :: QueryMorphism a a # (.) :: QueryMorphism b c -> QueryMorphism a b -> QueryMorphism a c # |
newtype SelectedCount Source #
This type keeps track of the multiplicity of elements of the view selector that are being used by the app
Instances
combineSelectedCounts :: SelectedCount -> SelectedCount -> Maybe SelectedCount Source #
The SemigroupMonoidGroup instances for a ViewSelector should use this function which returns Nothing if the result is 0. This allows the pruning of leaves that are no longer wanted.
class (Group q, Additive q, Query q) => MonadQuery t q m | m -> q t where Source #
tellQueryIncremental :: Incremental t (AdditivePatch q) -> m () Source #
askQueryResult :: m (Dynamic t (QueryResult q)) Source #
queryIncremental :: Incremental t (AdditivePatch q) -> m (Dynamic t (QueryResult q)) Source #
Instances
tellQueryDyn :: (Reflex t, MonadQuery t q m) => Dynamic t q -> m () Source #
queryDyn :: (Reflex t, Monad m, MonadQuery t q m) => Dynamic t q -> m (Dynamic t (QueryResult q)) Source #
mapQuery :: QueryMorphism q q' -> q -> q' Source #
mapQueryResult :: QueryMorphism q q' -> QueryResult q' -> QueryResult q Source #