I’m playing around with Redis and trying out a type for commands that look like this:
type Cmd a = forall m. (Monad m) => (ByteString -> m Value) -> m (Either FromRespError a)
that is, a command is a higher-order function that’s given a function for “sending itself.” This makes for a rather nice API when sending a single command and receiving its response.
Redis support sending multiple commands at once, called pipelining, which simply is sending of multiple commands at once, and receiving all the responses in one go. The commands in a pipeline must be completely independent, i.e. it matches the semantics of Applicative
. I think it might be nice to have an instance of Applicative
for Cmd
, but I’m not sure how to approach it.
Basically what has to happen when “running the Applicative
” is
- collect all the Redis raw commands (the
ByteString
given to the sending function),
- concatenate all raw commands and send them to Redis in one go
- receive the raw responses and turn them into a bunch of
Value
- resume each sending function giving it its
Value
I found monad-coroutine on Hackage that would let me run a part of a sending function, pass the raw command and control back, and then resume the sending function once there’s a Value
to give it.
What I’m struggling with is how to approach the Applicative
instance itself. Cmd a
is a functor ((->) r
) so I could use free to get an applicative, but I’m not sure how to achieve the collect/resume part given the API offered.
I’d love to hear thoughts on this. What am I missing? Should I rethink the command type? Suggestions and insights are more than welcome.
You might like the paper Free delivery.
Abstract
Remote procedure calls are computationally expensive, because
network round-trips take several orders of magnitude longer than
local interactions. One common technique for amortizing this cost
is to batch together multiple independent requests into one com-
pound request. Batching requests amounts to serializing the ab-
stract syntax tree of a small program, in order to transmit it and
run it remotely. The standard representation for abstract syntax is
to use free monads; we show that free applicative functors are ac-
tually a better choice of representation for this scenario.
6 Likes
I think this type won’t work for what you’re trying to do.
badExample :: Cmd Value
badExample eval = Right <$> do
val <- eval "some query"
if predicate val then
eval "another query"
else
eval "yet another query"
This is inherently unbatchable. Your commands are presumably not of this form, but that’s an additional restriction not captured by the type.
The types in Free Delivery are probably a better starting point for you.
Yes, the best I’ve manage to come up with is batching a list of Cmd Value
, which requires a separate sender function too. Pretty far from as convenient as an Applicative
instance.
If you can use something like this instead (corresponding to ActionA
in Free Delivery):
data Cmd m a = Cmd ByteString (Value -> m a)
then Ap (Cmd m)
will serve you nicely, I think.
Yes indeed, the Free delivery paper pretty much outlined a solution nicely. I’m working my way slowly through it but now I have both
serializeA :: ProgramA a -> ByteString
and
deserializeA :: ProgramA a -> [Value] -> Validation [FromRespError] a
that I ought to be able to combine easily.
A few things I noted on the way
- The free applicative I found in free is a bit different from the one in the paper, and I failed at writing a
deserializeA
for it. I can’t work out how the library’s API would support working through the list of Value
. (serializeA
was easily written using runAp_
.)
- I needed to add a
Functor
instance for FreeA f
which seems to be missing from the paper. It wasn’t very difficult though.
This should do:
deserializeA :: Ap ActionA a -> [String] -> a
deserializeA (Pure a) [] = a
deserializeA (Ap (ActionA c k) p) (s : ss) =
deserializeA p ss $ k $ readReply c s
If you prefer going through runAp
, you can use State
as the target functor:
pop :: State [a] a
pop = state $ \(x : xs) -> (x, xs)
deserializeAS :: Ap ActionA a -> State [String] a
deserializeAS = runAp $ \(ActionA c k) -> k . readReply c <$> pop
2 Likes
This looks like a problem that might be suited for the monad-batcher library. Especially useful when combined with the ApplicativeDo language extension.
1 Like