Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class (Monoid (QueryResult a), Semigroup (QueryResult a)) => Query a where
- type QueryResult a :: Type
- crop :: a -> QueryResult a -> 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, Commutative q, Query q, Monad m) => MonadQuery t q m | m -> q t where
- tellQueryIncremental :: Incremental t (AdditivePatch q) -> m ()
- askQueryResult :: m (Dynamic t (QueryResult q))
- queryIncremental :: Incremental t (AdditivePatch q) -> m (Dynamic t (QueryResult q))
- tellQueryDyn :: (Reflex t, MonadQuery t q m) => Dynamic t q -> m ()
- queryDyn :: (Reflex t, MonadQuery t q m) => Dynamic t q -> m (Dynamic t (QueryResult q))
- subQuery :: (Reflex t, MonadQuery t q2 m) => QueryMorphism q1 q2 -> Dynamic t q1 -> m (Dynamic t (QueryResult q1))
- 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 #
A Query
can be thought of as a declaration of interest in some set of data.
A QueryResult
is the set of data associated with that interest set.
The crop
function provides a way to determine what part of a given QueryResult
is relevant to a given Query
.
type QueryResult a :: Type Source #
crop :: a -> QueryResult a -> QueryResult a Source #
Instances
Query () Source # | Trivial queries have trivial results. |
Defined in Reflex.Query.Class type QueryResult () Source # crop :: () -> QueryResult () -> QueryResult () Source # | |
Query Void Source # | The result of an absurd query is trivial; If you can ask the question, the answer cannot tell you anything you didn't already know. 'QueryResult Void = |
Defined in Reflex.Query.Class type QueryResult Void Source # crop :: Void -> QueryResult Void -> QueryResult Void Source # | |
(Query a, Query b) => Query (a, b) Source # | the result of two queries is both results. |
Defined in Reflex.Query.Class type QueryResult (a, b) Source # crop :: (a, b) -> QueryResult (a, b) -> QueryResult (a, b) Source # | |
(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 # | |
(Query q, Applicative f) => Query (Ap f q) Source # | We can lift queries into monoidal containers. But beware of Applicatives whose monoid is different from (pure mempty, liftA2 mappend) |
Defined in Reflex.Query.Class type QueryResult (Ap f q) Source # crop :: Ap f q -> QueryResult (Ap f q) -> QueryResult (Ap f q) Source # |
data QueryMorphism q q' Source #
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 :: forall (a :: k). QueryMorphism a a # (.) :: forall (b :: k) (c :: k) (a :: k). QueryMorphism b c -> QueryMorphism a b -> QueryMorphism a c # |
newtype SelectedCount Source #
This type can be used to track of the frequency of interest in a given Query
. See note on
combineSelectedCounts
Instances
combineSelectedCounts :: SelectedCount -> SelectedCount -> Maybe SelectedCount Source #
The Semigroup/Monoid/Group instances for a Query containing SelectedCount
s should use
this function which returns Nothing if the result is 0. This allows the pruning of leaves
of the Query
that are no longer wanted.
class (Group q, Commutative q, Query q, Monad m) => MonadQuery t q m | m -> q t where Source #
A class that allows sending of Query
s and retrieval of QueryResult
s. See queryDyn
for a commonly
used interface.
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 #
Produce and send an Incremental
Query
from a Dynamic
Query
.
queryDyn :: (Reflex t, MonadQuery t q m) => Dynamic t q -> m (Dynamic t (QueryResult q)) Source #
Retrieve Dynamic
ally updating QueryResult
s for a Dynamic
ally updating Query
.
subQuery :: (Reflex t, MonadQuery t q2 m) => QueryMorphism q1 q2 -> Dynamic t q1 -> m (Dynamic t (QueryResult q1)) Source #
Use a query morphism to operate on a smaller version of a query.
mapQuery :: QueryMorphism q q' -> q -> q' Source #
Apply a QueryMorphism
to a Query
mapQueryResult :: QueryMorphism q q' -> QueryResult q' -> QueryResult q Source #
Map a QueryMorphism
to a QueryResult