reflex-0.8.1.1: Higher-order Functional Reactive Programming
Safe HaskellNone
LanguageHaskell2010

Reflex.Query.Base

Synopsis

Documentation

newtype QueryT t q m a Source #

Constructors

QueryT 

Fields

Instances

Instances details
EventWriter t w m => EventWriter t w (QueryT t q m) Source # 
Instance details

Defined in Reflex.Query.Base

Methods

tellEvent :: Event t w -> QueryT t q m () Source #

DynamicWriter t w m => DynamicWriter t w (QueryT t q m) Source # 
Instance details

Defined in Reflex.Query.Base

Methods

tellDyn :: Dynamic t w -> QueryT t q m () Source #

(Monad m, Group q, Additive q, Query q, Reflex t) => MonadQuery t q (QueryT t q m) Source # 
Instance details

Defined in Reflex.Query.Base

(Reflex t, MonadFix m, Group q, Additive q, Query q, Eq q, MonadHold t m, Adjustable t m) => Adjustable t (QueryT t q m) Source # 
Instance details

Defined in Reflex.Query.Base

Methods

runWithReplace :: QueryT t q m a -> Event t (QueryT t q m b) -> QueryT t q m (a, Event t b) Source #

traverseIntMapWithKeyWithAdjust :: (Key -> v -> QueryT t q m v') -> IntMap v -> Event t (PatchIntMap v) -> QueryT t q m (IntMap v', Event t (PatchIntMap v')) Source #

traverseDMapWithKeyWithAdjust :: GCompare k => (forall a. k a -> v a -> QueryT t q m (v' a)) -> DMap k v -> Event t (PatchDMap k v) -> QueryT t q m (DMap k v', Event t (PatchDMap k v')) Source #

traverseDMapWithKeyWithAdjustWithMove :: GCompare k => (forall a. k a -> v a -> QueryT t q m (v' a)) -> DMap k v -> Event t (PatchDMapWithMove k v) -> QueryT t q m (DMap k v', Event t (PatchDMapWithMove k v')) Source #

MonadReflexCreateTrigger t m => MonadReflexCreateTrigger t (QueryT t q m) Source # 
Instance details

Defined in Reflex.Query.Base

Methods

newEventWithTrigger :: (EventTrigger t a -> IO (IO ())) -> QueryT t q m (Event t a) Source #

newFanEventWithTrigger :: GCompare k => (forall a. k a -> EventTrigger t a -> IO (IO ())) -> QueryT t q m (EventSelector t k) Source #

PostBuild t m => PostBuild t (QueryT t q m) Source # 
Instance details

Defined in Reflex.Query.Base

Methods

getPostBuild :: QueryT t q m (Event t ()) Source #

Requester t m => Requester t (QueryT t q m) Source # 
Instance details

Defined in Reflex.Query.Base

Associated Types

type Request (QueryT t q m) :: Type -> Type Source #

type Response (QueryT t q m) :: Type -> Type Source #

Methods

requesting :: Event t (Request (QueryT t q m) a) -> QueryT t q m (Event t (Response (QueryT t q m) a)) Source #

requesting_ :: Event t (Request (QueryT t q m) a) -> QueryT t q m () Source #

TriggerEvent t m => TriggerEvent t (QueryT t q m) Source # 
Instance details

Defined in Reflex.Query.Base

Methods

newTriggerEvent :: QueryT t q m (Event t a, a -> IO ()) Source #

newTriggerEventWithOnComplete :: QueryT t q m (Event t a, a -> IO () -> IO ()) Source #

newEventWithLazyTriggerWithOnComplete :: ((a -> IO () -> IO ()) -> IO (IO ())) -> QueryT t q m (Event t a) Source #

PerformEvent t m => PerformEvent t (QueryT t q m) Source # 
Instance details

Defined in Reflex.Query.Base

Associated Types

type Performable (QueryT t q m) :: Type -> Type Source #

Methods

performEvent :: Event t (Performable (QueryT t q m) a) -> QueryT t q m (Event t a) Source #

performEvent_ :: Event t (Performable (QueryT t q m) ()) -> QueryT t q m () Source #

NotReady t m => NotReady t (QueryT t q m) Source # 
Instance details

Defined in Reflex.NotReady.Class

Methods

notReadyUntil :: Event t a -> QueryT t q m () Source #

notReady :: QueryT t q m () Source #

MonadHold t m => MonadHold (t :: Type) (QueryT t q m) Source # 
Instance details

Defined in Reflex.Query.Base

Methods

hold :: a -> Event t a -> QueryT t q m (Behavior t a) Source #

holdDyn :: a -> Event t a -> QueryT t q m (Dynamic t a) Source #

holdIncremental :: Patch p => PatchTarget p -> Event t p -> QueryT t q m (Incremental t p) Source #

buildDynamic :: PushM t a -> Event t a -> QueryT t q m (Dynamic t a) Source #

headE :: Event t a -> QueryT t q m (Event t a) Source #

now :: QueryT t q m (Event t ()) Source #

MonadSample t m => MonadSample (t :: Type) (QueryT t q m) Source # 
Instance details

Defined in Reflex.Query.Base

Methods

sample :: Behavior t a -> QueryT t q m a Source #

MFunctor (QueryT t q :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Reflex.Query.Base

Methods

hoist :: forall m n (b :: k). Monad m => (forall a. m a -> n a) -> QueryT t q m b -> QueryT t q n b #

MonadTrans (QueryT t q) Source # 
Instance details

Defined in Reflex.Query.Base

Methods

lift :: Monad m => m a -> QueryT t q m a #

Monad m => Monad (QueryT t q m) Source # 
Instance details

Defined in Reflex.Query.Base

Methods

(>>=) :: QueryT t q m a -> (a -> QueryT t q m b) -> QueryT t q m b #

(>>) :: QueryT t q m a -> QueryT t q m b -> QueryT t q m b #

return :: a -> QueryT t q m a #

Functor m => Functor (QueryT t q m) Source # 
Instance details

Defined in Reflex.Query.Base

Methods

fmap :: (a -> b) -> QueryT t q m a -> QueryT t q m b #

(<$) :: a -> QueryT t q m b -> QueryT t q m a #

MonadFix m => MonadFix (QueryT t q m) Source # 
Instance details

Defined in Reflex.Query.Base

Methods

mfix :: (a -> QueryT t q m a) -> QueryT t q m a #

Monad m => Applicative (QueryT t q m) Source # 
Instance details

Defined in Reflex.Query.Base

Methods

pure :: a -> QueryT t q m a #

(<*>) :: QueryT t q m (a -> b) -> QueryT t q m a -> QueryT t q m b #

liftA2 :: (a -> b -> c) -> QueryT t q m a -> QueryT t q m b -> QueryT t q m c #

(*>) :: QueryT t q m a -> QueryT t q m b -> QueryT t q m b #

(<*) :: QueryT t q m a -> QueryT t q m b -> QueryT t q m a #

MonadIO m => MonadIO (QueryT t q m) Source # 
Instance details

Defined in Reflex.Query.Base

Methods

liftIO :: IO a -> QueryT t q m a #

MonadException m => MonadException (QueryT t q m) Source # 
Instance details

Defined in Reflex.Query.Base

Methods

throw :: Exception e => e -> QueryT t q m a #

catch :: Exception e => QueryT t q m a -> (e -> QueryT t q m a) -> QueryT t q m a #

finally :: QueryT t q m a -> QueryT t q m b -> QueryT t q m a #

MonadAsyncException m => MonadAsyncException (QueryT t q m) Source # 
Instance details

Defined in Reflex.Query.Base

Methods

mask :: ((forall a. QueryT t q m a -> QueryT t q m a) -> QueryT t q m b) -> QueryT t q m b #

PrimMonad m => PrimMonad (QueryT t q m) Source # 
Instance details

Defined in Reflex.Query.Base

Associated Types

type PrimState (QueryT t q m) #

Methods

primitive :: (State# (PrimState (QueryT t q m)) -> (# State# (PrimState (QueryT t q m)), a #)) -> QueryT t q m a #

MonadRef m => MonadRef (QueryT t q m) Source # 
Instance details

Defined in Reflex.Query.Base

Associated Types

type Ref (QueryT t q m) :: Type -> Type #

Methods

newRef :: a -> QueryT t q m (Ref (QueryT t q m) a) #

readRef :: Ref (QueryT t q m) a -> QueryT t q m a #

writeRef :: Ref (QueryT t q m) a -> a -> QueryT t q m () #

modifyRef :: Ref (QueryT t q m) a -> (a -> a) -> QueryT t q m () #

modifyRef' :: Ref (QueryT t q m) a -> (a -> a) -> QueryT t q m () #

MonadAtomicRef m => MonadAtomicRef (QueryT t q m) Source # 
Instance details

Defined in Reflex.Query.Base

Methods

atomicModifyRef :: Ref (QueryT t q m) a -> (a -> (a, b)) -> QueryT t q m b #

atomicModifyRef' :: Ref (QueryT t q m) a -> (a -> (a, b)) -> QueryT t q m b #

(Semigroup a, Monad m) => Semigroup (QueryT t q m a) Source # 
Instance details

Defined in Reflex.Query.Base

Methods

(<>) :: QueryT t q m a -> QueryT t q m a -> QueryT t q m a #

sconcat :: NonEmpty (QueryT t q m a) -> QueryT t q m a #

stimes :: Integral b => b -> QueryT t q m a -> QueryT t q m a #

(Monoid a, Monad m) => Monoid (QueryT t q m a) Source # 
Instance details

Defined in Reflex.Query.Base

Methods

mempty :: QueryT t q m a #

mappend :: QueryT t q m a -> QueryT t q m a -> QueryT t q m a #

mconcat :: [QueryT t q m a] -> QueryT t q m a #

type PrimState (QueryT t q m) Source # 
Instance details

Defined in Reflex.Query.Base

type PrimState (QueryT t q m) = PrimState m
type Ref (QueryT t q m) Source # 
Instance details

Defined in Reflex.Query.Base

type Ref (QueryT t q m) = Ref m
type Request (QueryT t q m) Source # 
Instance details

Defined in Reflex.Query.Base

type Request (QueryT t q m) = Request m
type Response (QueryT t q m) Source # 
Instance details

Defined in Reflex.Query.Base

type Response (QueryT t q m) = Response m
type Performable (QueryT t q m) Source # 
Instance details

Defined in Reflex.Query.Base

type Performable (QueryT t q m) = Performable m

runQueryT :: (MonadFix m, Additive q, Group q, Reflex t) => QueryT t q m a -> Dynamic t (QueryResult q) -> m (a, Incremental t (AdditivePatch q)) Source #

mapQuery :: QueryMorphism q q' -> q -> q' Source #

Apply a QueryMorphism to a Query

dynWithQueryT :: (MonadFix m, PostBuild t m, Group q, Additive q, Group q', Additive q', Query q') => Dynamic t (QueryMorphism q q') -> QueryT t q m a -> QueryT t q' m a Source #

dynWithQueryT's (Dynamic t QueryMorphism) argument needs to be a group homomorphism at all times in order to behave correctly

withQueryT :: (MonadFix m, PostBuild t m, Group q, Group q', Additive q, Additive q', Query q') => QueryMorphism q q' -> QueryT t q m a -> QueryT t q' m a Source #

withQueryT's QueryMorphism argument needs to be a group homomorphism in order to behave correctly

mapQueryT :: (forall b. m b -> n b) -> QueryT t q m a -> QueryT t q n a Source #

Maps a function over a QueryT that can change the underlying monad