20 Jun 2025

Finding a type for Redis commands

Arriving at a type for Redis commands required a bit of exploration. I had some ideas early on that I for various reasons ended up dropping on the way. This is a post about my travels, hopefully someone finds it worthwhile reading.

The protocol

The Redis Serialization Protocol (RESP) initially reminded me of JSON and I thought that following the pattern of aeson might be a good idea. I decided up-front that I'd only support the latest version of RESP, i.e. version 3. So, I thought of a data type, Resp with a constructor for each RESP3 data type, and a pair of type classes, FromResp and ToResp for converting between Haskell types and RESP3. Then after some more reflection I realised that converting to RESP is largely pointless. The main reason to convert anything to RESP3 is to assemble a command, with its arguments, to send to Redis, but all commands are arrays of bulk strings so it's unlikely that anyone will actually use ToResp.1 So I scrapped the idea of ToResp. FromResp looked like this

class FromResp a where
    fromResp :: Value -> Either FromRespError a

When I started defining commands I didn't like the number of ByteString arguments that resulted in, so I defined a data type, Arg, and an accompanying type class for arguments, ToArg:

newtype Arg = Arg {unArg :: [ByteString]}
    deriving (Show, Semigroup, Monoid)

class ToArg a where
    toArg :: a -> Arg

Later on I saw that it might also be nice to have a type class specifically for keys, ToKey, though that's a wrapper for a single ByteString.

Implementing the functions to encode/decode the protocol were straight-forward applications of attoparsec and bytestring (using its Builder).

A command is a function in need of a sender

Even though supporting pipelining was one of the goals I felt a need to make sure I'd understood the protocol so I started off with single commands. The protocol is a simple request/response protocol at the core so I settled on this type for commands

type Cmd a = forall m. (Monad m) => (ByteString -> m ByteString) -> m (Either FromRespError a)

that is, a command is a function accepting a sender and returning an a.

I wrote a helper function for defining commands, sendCmd

sendCmd :: (Monad m, FromResp a) => [ByteString] -> (ByteString -> m ByteString) -> m (Either FromRespError a)
sendCmd cmdArgs send = do
    let cmd = encode $ Array $ map BulkString cmdArgs
    send cmd <&> decode >>= \case
        Left desc -> pure $ Left $ FromRespError "Decode" (Text.pack desc)
        Right v -> pure $ fromValue v

which made it easy to define commands. Here are two examples, append and mget:

append :: (ToArg a, ToArg b) => a -> b -> Cmd Int
append key val = sendCmd $ ["APPEND"] <> unArg (toArg key <> toArg val)

-- | https://redis.io/docs/latest/commands/mget/
mget :: (ToArg a, FromResp b) => NE.NonEmpty a -> Cmd (NE.NonEmpty b)
mget ks = sendCmd $ ["MGET"] <> unArg (foldMap1 toArg ks)

The function to send off a command and receive its response, sendAndRecieve, was just a call to send followed by a call to recv in network (the variants for lazy bytestrings).

I sort of liked this representation – there's always something pleasant with finding a way to represent something as a function. There's a very big problem with it though: it's difficult to implement pipelining!

Yes, Cmd is a functor since (->) r is a functor, and thus it's possible to make it an Applicative, e.g. using free. However, to implement pipelining it's necessary to

  1. encode all commands, then
  2. concatenate them all into a single bytestring and send it
  3. read the response, which is a concatenation of the individual commands' responses, and
  4. convert each separate response from RESP3.

That isn't easy when each command contains its own encoding and decoding. The sender function would have to relinquish control after encoding the command, and resume with the resume again later to decode it. I suspect it's doable using continuations, or monad-coroutine, but it felt complicated and rather than travelling down that road I asked for ideas on the Haskell Discourse. The replies lead me to a paper, Free delivery, and a bit later a package, monad-batcher. When I got the pointer to the package I'd already read the paper and started implementing the ideas in it, so I decided to save exploring monad-batcher for later.

A command for free delivery

The paper Free delivery is a perfect match for pipelining in Redis, and my understanding is that it proposes a solution where

  1. Commands are defined as a GADT, Command a.
  2. Two functions are defined to serialise and deserialise a Command a. In the paper they use String as the serialisation, so show and read is used.
  3. A type, ActionA a, is defined that combines a command with a modification of its a result. It implements Functor.
  4. A free type, FreeA f a is defined, and made into an Applicative with the constraint that f is a Functor.
  5. A function, serializeA, is defined that traverses a FreeA ActionA a serialising each command.
  6. A function, deserializeA, is defined that traverses a FreeA ActionA a deserialising the response for each command.

I defined a command type, Command a, with only three commands in it, echo, hello, and ping. I then followed the recipe above to verify that I could get it working at all. The Haskell used in the paper is showing its age, and there seems to be a Functor instance missing, but it was still straight forward and I could verify that it worked against a locally running Redis.

Then I made a few changes…

I renamed the command type to Cmd so I could use Command for what the paper calls ActionA.

data Cmd r where
    Echo :: Text -> Cmd Text
    Hello :: Maybe Int -> Cmd ()
    Ping :: Maybe Text -> Cmd Text

data Command a = forall r. Command !(r -> a) !(Cmd r)

instance Functor Command where
    fmap f (Command k c) = Command (f . k) c

toWireCmd :: Cmd r -> ByteString
toWireCmd (Echo msg) = _
toWireCmd (Hello ver) = _
toWireCmd (Ping msg) = _

fromWireResp :: Cmd r -> Resp -> Either RespError r
fromWireResp (Echo _) = fromResp
fromWireResp (Hello _) = fromResp
fromWireResp (Ping _) = fromResp

(At this point I was still using FromResp.)

I also replaced the free applicative defined in the paper and started using free. A couple of type aliases make it a little easier to write nice signatures

type Pipeline a = Ap Command a

type PipelineResult a = Validation [RespError] a

and defining individual pipeline commands turned into something rather mechanical. (I also swapped the order of the arguments to build a Command so I can use point-free style here.)

liftPipe :: (FromResp r) => Cmd r -> Pipeline r
liftPipe = liftAp . Command id

echo :: Text -> Pipeline Text
echo = liftPipe . Echo

hello :: Maybe Int -> Pipeline ()
hello = liftPipe . Hello

ping :: Maybe Text -> Pipeline Text
ping = liftPipe . Ping

One nice thing with switching to free was that serialisation became very simple

toWirePipeline :: Pipeline a -> ByteString
toWirePipeline = runAp_ $ \(Command _ c) -> toWireCmd c

On the other hand deserialisation became a little more involved, but it's not too bad

fromWirePipelineResp :: Pipeline a -> [Resp] -> PipelineResult a
fromWirePipelineResp (Pure a) _ = pure a
fromWirePipelineResp (Ap (Command k c) p) (r : rs) = fromWirePipelineResp p rs <*> (k <$> liftError singleton (fromWireResp c r))
fromWirePipelineResp _ _ = Failure [RespError "fromWirePipelineResp" "Unexpected wire result"]

Everything was working nicely and I started adding support for more commands. I used the small service from work to guide my choice of what commands to add. First out was del, then get and set. After adding lpush I was pretty much ready to try to replace hedis in the service from work.

data Cmd r where
    -- echo, hello, ping
    Del :: (ToKey k) => NonEmpty k -> Cmd Int
    Get :: (ToKey k, FromResp r) => k -> Cmd r
    Set :: (ToKey k, ToArg v) => k -> v -> Cmd Bool
    Lpush :: (ToKey k, ToArg v) => k -> NonEmpty v -> Cmd Int

However, when looking at the above definition started I thinking.

  • Was it really a good idea to litter Cmd with constraints like that?
  • Would it make sense to keep the Cmd type a bit closer to the actual Redis commands?
  • Also, maybe FromResp wasn't such a good idea after all, what if I remove it?

That brought me to the third version of the type for Redis commands.

Converging and simplifying

While adding new commands and writing instances of FromResp I slowly realised that my initial thinking of RESP3 as somewhat similar to JSON didn't really pan out. I had quickly dropped ToResp and now the instances of FromResp didn't sit right with me. They obviously had to "follow the commands", so to speak, but at the same time allow users to bring their own types. For instance, LSPUSH returns the number of pushed messages, but at the same time GET should be able to return an Int too. This led to Int's FromResp looking like this

instance FromResp Int where
    fromResp (BulkString bs) =
        case parseOnly (AC8.signed AC8.decimal) bs of
            Left s -> Left $ RespError "FromResp" (TL.pack s)
            Right n -> Right n
    fromResp (Number n) = Right $ fromEnum n
    fromResp _ = Left $ RespError "FromResp" "Unexpected value"

I could see this becoming worse, take the instance for Bool, I'd have to consider that

  • for MOVE Integer 1 means True and Integer 0 means False
  • for SET SimpleString "OK" means True
  • users would justifiably expect a bunch of bytestrings to be True, e.g. BulkString "true", BulkString "TRUE", BulkString "1", etc

However, it's impossible to cover all ways users can encode a Bool in a ByteString so no matter what I do users will end up having to wrap their Bool with newtype and implement a fitting FromResp. On top of that, even thought I haven't found any example of it yet, I fully expect there to be, somewhere in the large set of Redis commands, at least two commands each wanting an instance of a basic type that simply can't be combined into a single instance, meaning that the client library would need to do some newtype wrapping too.

No, I really didn't like it! So, could I get rid of FromResp and still offer users an API where they can user their own types as the result of commands?

To be concrete I wanted this

data Cmd r where
    -- other commands
    Get :: (ToKey k) => k -> Cmd (Maybe ByteString)

and I wanted the user to be able to conveniently turn a Cmd r into a Cmd s. In other words, I wanted a Functor instance. Making Cmd itself a functor isn't necessary and I just happened to already have a functor type that wraps Cmd, the Command type I used for pipelining. If I were to use that I'd need to write wrapper functions for each command though, but if I did that then I could also remove the ToKey~/~ToArg constraints from the constructors of Cmd r and put them on the wrapper instead. I'd get

data Cmd r where
    -- other commands
    Get :: Key -> Cmd (Maybe ByteString)

get :: (ToKey k) => k -> Command (Maybe ByteString)
get = Command id . Get . toKey

I'd also have to rewrite fromWireResp so it's more specific for each command. Instead of

fromWireResp :: Cmd r -> Resp -> Either RespError r
fromWireResp (Get _) = fromResp
...

I had to match up exactly on the possible replies to GET

fromWireResp :: Cmd r -> Resp -> Either RespError r
fromWireResp _ (SimpleError err desc) = Left $ RespError (T.decodeUtf8 err) (T.decodeUtf8 desc)
fromWireResp (Get _) (BulkString bs) = Right $ Just bs
fromWireResp (Get _) Null = Right Nothing
...
fromWireResp _ _ = Left $ RespError "fromWireResp" "Unexpected value"

Even though it was more code I liked it better than before, and I think it's slightly simpler code. I also hope it makes the use of the API is a bit simpler and clear.

Here's an example from the code for the service I wrote for work. It reads a UTC timestamp stored in timeKey, the timestamp is a JSON string so it needs to be decoded.

readUTCTime :: Connection -> IO (Maybe UTCTime)
readUTCTime conn =
    sendCmd conn (maybe Nothing decode <$> get timeKey) >>= \case
        Left _ -> pure Nothing
        Right datum -> pure datum

What's next?

I'm pretty happy with the command type for now, though I have a feeling I'll have to revisit Arg and ToArg at some point.

I've just turned the Connection type into a pool using resource-pool, and I started looking at pub/sub. The latter thing, pub/sub, will require some thought and experimentation I think. Quite possibly it'll end up in a post here too.

I also have a lot of commands to add.

Footnotes:

1

Of course one could use RESP3 as the serialisation format for storing values in Redis. Personally I think I'd prefer using something more widely used, and easier to read, such as JSON or BSON.

Tags: haskell redis
Comment here.