| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Morpheus.Types.Internal.Subscription
Synopsis
- connect :: MonadIO m => m (Input WS)
- disconnect :: Scope WS e m -> Input WS -> m ()
- connectionThread :: MonadUnliftIO m => (Input WS -> Stream WS e m) -> Scope WS e m -> m ()
- toOutStream :: Monad m => (GQLRequest -> ResponseStream e m (Value VALID)) -> Input api -> Stream api e m
- runStreamWS :: Monad m => Scope WS e m -> Stream WS e m -> m ()
- runStreamHTTP :: Monad m => Scope HTTP e m -> Stream HTTP e m -> m GQLResponse
- data Stream (api :: API) e (m :: * -> *)
- data Scope (api :: API) event (m :: * -> *) where
- data Input (api :: API) where
- type WS = WS
- type HTTP = HTTP
- acceptApolloRequest :: MonadIO m => PendingConnection -> m Connection
- publish :: (Monad m, Eq channel) => Event channel content -> ClientConnectionStore (Event channel content) m -> m ()
- data Store e m = Store {
- readStore :: m (ClientConnectionStore e m)
- writeStore :: (ClientConnectionStore e m -> ClientConnectionStore e m) -> m ()
- initDefaultStore :: (MonadIO m, MonadIO m2) => m2 (Store event m)
- publishEventWith :: (MonadIO m, Eq channel) => Store (Event channel cont) m -> Event channel cont -> m ()
- data ClientConnectionStore e (m :: * -> *)
- empty :: Collection a coll => coll
- toList :: ClientConnectionStore e m -> [(UUID, ClientConnection e m)]
- connectionSessionIds :: ClientConnection e m -> [SessionID]
- type SessionID = Text
Documentation
connectionThread :: MonadUnliftIO m => (Input WS -> Stream WS e m) -> Scope WS e m -> m () Source #
toOutStream :: Monad m => (GQLRequest -> ResponseStream e m (Value VALID)) -> Input api -> Stream api e m Source #
runStreamHTTP :: Monad m => Scope HTTP e m -> Stream HTTP e m -> m GQLResponse Source #
data Stream (api :: API) e (m :: * -> *) Source #
Instances
| Interpreter (Event ch cont) m (Input api) (Stream api (Event ch cont) m) Source # | |
Defined in Data.Morpheus.Server.Deriving.Interpreter Methods interpreter :: (Monad m, RootResolverConstraint m (Event ch cont) query mut sub) => RootResolver m (Event ch cont) query mut sub -> Input api -> Stream api (Event ch cont) m Source # debugInterpreter :: (Monad m, RootResolverConstraint m (Event ch cont) query mut sub) => RootResolver m (Event ch cont) query mut sub -> Input api -> Stream api (Event ch cont) m Source # | |
data Scope (api :: API) event (m :: * -> *) where Source #
Constructors
| ScopeHTTP | |
Fields
| |
| ScopeWS | |
Fields
| |
data Input (api :: API) where Source #
Instances
| Interpreter (Event ch cont) m (Input api) (Stream api (Event ch cont) m) Source # | |
Defined in Data.Morpheus.Server.Deriving.Interpreter Methods interpreter :: (Monad m, RootResolverConstraint m (Event ch cont) query mut sub) => RootResolver m (Event ch cont) query mut sub -> Input api -> Stream api (Event ch cont) m Source # debugInterpreter :: (Monad m, RootResolverConstraint m (Event ch cont) query mut sub) => RootResolver m (Event ch cont) query mut sub -> Input api -> Stream api (Event ch cont) m Source # | |
acceptApolloRequest :: MonadIO m => PendingConnection -> m Connection Source #
publish :: (Monad m, Eq channel) => Event channel content -> ClientConnectionStore (Event channel content) m -> m () Source #
PubSubStore interface shared GraphQL state between websocket and http server, you can define your own store if you provide write and read methods to work properly Morpheus needs all entries of ClientConnectionStore (+ client Callbacks) that why it is recomended that you use many local ClientStores on evenry server node rathen then single centralized Store.
Constructors
| Store | |
Fields
| |
initDefaultStore :: (MonadIO m, MonadIO m2) => m2 (Store event m) Source #
initializes empty GraphQL state
publishEventWith :: (MonadIO m, Eq channel) => Store (Event channel cont) m -> Event channel cont -> m () Source #
data ClientConnectionStore e (m :: * -> *) Source #
Instances
| Show (ClientConnectionStore e m) Source # | |
Defined in Data.Morpheus.Types.Internal.Subscription.ClientConnectionStore Methods showsPrec :: Int -> ClientConnectionStore e m -> ShowS # show :: ClientConnectionStore e m -> String # showList :: [ClientConnectionStore e m] -> ShowS # | |
empty :: Collection a coll => coll #
toList :: ClientConnectionStore e m -> [(UUID, ClientConnection e m)] Source #
connectionSessionIds :: ClientConnection e m -> [SessionID] Source #