| 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, Eq (StreamChannel e), GQLChannel e, Functor 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 :: (Eq (StreamChannel event), GQLChannel event, Monad m) => event -> ClientConnectionStore event 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, Eq (StreamChannel event), GQLChannel event) => m2 (Store event m)
- publishEventWith :: (MonadIO m, Eq (StreamChannel event), GQLChannel event) => Store event m -> event -> m ()
- class GQLChannel a where
- type StreamChannel a :: Type
- streamChannels :: a -> [Channel a]
- 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, Eq (StreamChannel e), GQLChannel e, Functor 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 e m (Input api) (Stream api e m) Source # | |
Defined in Data.Morpheus.Server.Deriving.Interpreter Methods interpreter :: (Monad m, RootResCon m e query mut sub) => RootResolver m e query mut sub -> Input api -> Stream api e m Source # | |
data Scope (api :: API) event (m :: * -> *) where Source #
Constructors
| ScopeHTTP | |
Fields
| |
| ScopeWS | |
Fields
| |
data Input (api :: API) where Source #
Instances
| Interpreter e m (Input api) (Stream api e m) Source # | |
Defined in Data.Morpheus.Server.Deriving.Interpreter Methods interpreter :: (Monad m, RootResCon m e query mut sub) => RootResolver m e query mut sub -> Input api -> Stream api e m Source # | |
acceptApolloRequest :: MonadIO m => PendingConnection -> m Connection Source #
publish :: (Eq (StreamChannel event), GQLChannel event, Monad m) => event -> ClientConnectionStore event 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, Eq (StreamChannel event), GQLChannel event) => m2 (Store event m) Source #
initializes empty GraphQL state
publishEventWith :: (MonadIO m, Eq (StreamChannel event), GQLChannel event) => Store event m -> event -> m () Source #
class GQLChannel a where #
Associated Types
type StreamChannel a :: Type #
Methods
streamChannels :: a -> [Channel a] #
Instances
| GQLChannel () | |
Defined in Data.Morpheus.Types.Internal.Resolving.Core Associated Types type StreamChannel () :: Type # Methods streamChannels :: () -> [Channel ()] # | |
| GQLChannel (Event channel content) | |
Defined in Data.Morpheus.Types.Internal.Resolving.Core Associated Types type StreamChannel (Event channel content) :: Type # Methods streamChannels :: Event channel content -> [Channel (Event channel content)] # | |
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 #