How to implement streaming with a custom monad - Why does the effect type have to be part of the API type?
I'm currently trying to create a Servant API including a streaming endpoint with a server implemented using MTL + Conduit .
An API type with a streaming endpoint looks like this (according to the cookbook):
type Routes =
"get" :> Get '[JSON] [User]
:<|> "stream" :> StreamGet NewlineFraming JSON (SourceIO User)
It becomes immediately obvious that for a regular Get endpoint the API type is independent of the server effect type whereas the streaming endpoint includes the effect type (IO in case of SourceIO). This is problematic for three reasons:
-
Conceptually, the API type is completely independent of effects. We could theoretically implement the same API type using different effects (for example an
IObased server in production and anIdentitybased server for testing) -
When using MTL the source type is parameterized, thus we have to add the parameter also to the API type!
type Routes m = "get" :> Get '[JSON] [User] :<|> "stream" :> StreamGet NewlineFraming JSON (ConduitT () User m ())At a later point both
Servant.serveandServant.hoistServerexpect aProxy (Routes m). You can imagine that with MTL the transformer stack type can become very large and typically you never write it out because it is so long. It's supposed to be inferred based on therunFooTfunctions you use to discharge the class constraints. -
According to the cookbook,
hoistServeris used to turn aServerT api mintoServerT api Handler. If we look at the definition of theHasServerinstance for theStreamcombinator, we find thathoistServerWithContexthas the typehoistServerWithContext :: Proxy (Stream method status framing ctype (Headers h a)) -> Proxy context -> (forall x. m x -> n x) -> ServerT (Stream method status framing ctype (Headers h a)) m -> ServerT (Stream method status framing ctype (Headers h a)) nwhere
awould beConduitT () User m ()in our example. It seems thathoistServerwould only turnm (ConduitT () User m ())intoHandler (ConduitT () User m ())leaving the innermthatServant.servedoesn't know how to deal with. Writing an instance forConduitToSourceIO mis also not possible because instances have to be global (unless you abuse reflection maybe) and the natural transformationntgiven tohoistServermay depend on local state from the enclosing scope. This problem also applies if you use a concrete custom monad instead of type classes. So far I haven't been able to figure out how to solve it. Perhaps it's possible to somehow maphoist ntover the resulting server.
Does anyone have an idea (or example preferable) how to make a Stream endpoint work with MTL?
I have tried solving problem 2 by implementing an immensely complicated concoction of type families that allow me to rewrite an API type replacing every SourceIO a with ConduitT () a m (). I can now successfully declare an unparameterized generic API type in terms of SourceIO a but provide a generic server in terms of ConduitT () a m (). However, I have been unable to figure out how to write a hoistServer function for that. It's probably a dead end.
Another option would be to create completely new Stream endpoint types that are independent of effect types and throw out Servant.API.Streaming completely. The existing implementation for HasServer Stream is
instance {-# OVERLAPPING #-}
( MimeRender ctype chunk, ReflectMethod method, KnownNat status,
FramingRender framing, ToSourceIO chunk a,
GetHeaders (Headers h a)
) => HasServer (Stream method status framing ctype (Headers h a)) context where
type ServerT (Stream method status framing ctype (Headers h a)) m = m (Headers h a)
hoistServerWithContext :: Proxy (Stream method status framing ctype (Headers h a))
-> Proxy context
-> (forall x. m x -> n x)
-> ServerT (Stream method status framing ctype (Headers h a)) m
-> ServerT (Stream method status framing ctype (Headers h a)) n
hoistServerWithContext _ _ nt s = nt s
If we change a to be (MFunctor s) => s b then it might be possible to write an implementation of hoistServerWithContext that also hoists the inner m in ConduitT () b m () but I fear that the type of hoistServerWithContext will not allow changing the a (unless you can do some trickery with the ServerT family). Is it even necessary that we have to have to wrap ConduitT () b m () inside another m in ServerT?
Conceptually, the API type is completely independent of effects.
is IMO absolutely spot on. I would be delighted if someone found a way to disentangle the streaming response specification in the API type from how it's produced. I don't have an answer for how we could get there, and I suspect you're right now in a much better position than most people to explore this question. The ToSourceIO constraint in that last code snippet of yours seem to prevent any kind of "deep hoisting" (including hoisting of the stream effects), so perhaps you could first try to write a hoisting function that does what you want, outside of all that HasServer business, and see what it requires.
I have explored the option of new HasServer instances a bit yesterday and now believe that it is impossible to make ServerT = m (s m a) work in the current framework, at least not without a backwards incompatible change to hoistServerWithContext to add a Monad m constraint (which is probably always satisfied in practice anyway). Even if you do that, there is the problem that hoistServer nt server = nt (hoist nt <$> server) will run the natural transformation nt twice. If nt includes a stateful monad (anything that isn't a Reader IORef created in the enclosing scope), then the outer m will use a different state than the inner m of ConduitT. Very surprising for users! hoisterver nt server = return $ hoist nt $ join $ lift server may work for m (s m a). In that case, the outer m becomes superfluous. My feeling is that the outer m is not needed and a server type that involves a stream endpoint should have two independent effect types: one for the regular endpoints and one for streaming endpoints. The question is: Is it always possible to define a server returning t m a instead of m (t m a)? With join . lift trick it should be possible though I would never have been able to come up with that on my own.
I can now see why you included the effect type in the Stream endpoint originally: You can not define ServerT without it because ServerT is lacking the type variable to be polymorphic in s and partially applying the Stream type (so you can introduce s later in the instance head) doesn't work inside generic API types. This makes the rewriting type family I mentioned earlier necessary (we can then define an effect-independent Stream API type and replace it with an effect-dependent SpecializedStream type at the point where we define the server. To make type inference and proxies work ergonomically, I will probably have to make stream-specific versions of ServerT, HasServer, genericServerT and hoistServer. I'll try to whip something up and keep you updated.
I think I've hit a roadblock. Getting the effect type out of the API type is quite easy to do, either with existential types or by rewriting the API type when declaring the Server to use another Stream combinator that is "specialized" in terms of an effect type. However, doing so is pointless because you can not hoist the Server type in any sensible way. IO is the only effect that works.
The crux of the issue is how the HTTP streaming protocol works: You respond with an HTTP status and then you stream the body. That means a ServerError may only happen right at the beginning but not in the middle of the stream. Thus, SourceT Handler a is ruled out because it can have ExceptT ServerError effects at any time. Something like ExceptT ServerError IO (SourceT IO a) is needed when running the server. But how do you hoist that? We would need a hoistServer function that looks essentially like this
hoistServer ::
forall
(t :: (Type -> Type) -> Type -> Type)
(s :: (Type -> Type) -> Type -> Type)
(m :: Type -> Type)
(n :: Type -> Type)
a.
(Monad m, MFunctor t, MFunctor s, MonadTrans t, MonadTrans s, Monad (t m), Monad (s m)) =>
(forall b. m b -> n b) ->
(t m) (s m a) ->
(t n) (s n a)
because t can be anything, not necessarily ExceptT ServerError and s can also be anything, not necessarily SourceT. The vigilant reader would suggest something like hoistServer nt = hoist nt . fmap (hoist nt) but this would run the natural transformation twice and throw away state, which is semantically wrong. You probably have to join the inner and outer monad to have any chance of sharing state using mmorph and monad-control machinery. That means lifting the inner m to ExceptT ServerError m so that we have ExceptT ServerError m (SourceT (ExceptT ServerError m) a). Then it should be possible to turn that into SourceT (ExceptT ServerError m) a with join . lift and we can finally hoist nt. But there is no way to go back and "unjoin" everything.
Do you have any ideas @alpmestan?
@tschuchortdev I'm afraid I don't, at the moment, sorry. This does seem to be quite tricky.