Search code examples
haskellserializationtypesrpcexistential-type

RPC (Or: How do I disambiguate function application based on TypeRep values?)


I'm building some infrastructure for doing remote procedure calls in Haskell, and for reasons that are too long to explain here, I cannot reuse existing libraries.

So here's the setup: I have a type class for serializing and deserializing data:

class Serializable a where
  encode :: a -> B.ByteString
  decode :: B.ByteString -> Maybe a
  maxSize :: a -> Int

where B is Data.ByteString.

I can use this to implement serialization of integers, booleans, lists of serializables, tuples of serializables ect.

Now I want to send some arguments across a network to a server, which then performs a computation based on these arguments, and sends back a result. So I create an existential type representing things that can be serialized:

data SerializableExt = forall t . Serializable t => SerializableExt t

because I want to send something of type [SerializableExt].

So, of course, I need to create an instance Serializable SerializableExt. This is where the problem starts:

In order to implement decode :: B.ByteString -> Maybe SerializableExt I need to know the concrete type that the existential type SerializableExt wraps.

So I implement encode :: SerializableExt -> B.ByteString as serializing the concrete type along with the value:

encode (SerializableExt x) = encode (typeOf x, x)

using typeOf from Data-Typeable. The problem is now the implementation of decode :: B.ByteString -> Maybe SerializableExt:

decode bs =
  let (tyenc, xenc) = splitPair bs -- Not really important. It just splits bs into the two components
  in case (decode tyenc :: Maybe TypeRep) of
       Just ty -> SerializableExt <$> _ -- Somehow invoke decode xenc, where the choice of which decode to execute depends on the value of ty.
       _ -> Nothing

But I can't see how to fill in the hole here. Because of Haskell's separation of the value level and the type level I can't use the value of ty to disambiguate the invocation of decode xenc, right?

Is there a way to solve this issue, and actually put something in the hole which will do what I want? Or can you come up with another design?

EDIT: One way of doing it would be the following:

decode bs =
  let (tyenc, xenc) = splitPair bs
  in SerializableExt <$>
       case (decode tyenc :: Maybe TypeRep) of
         Just ty
           | ty == typeRep (Proxy :: Proxy Int) -> decode xenc :: Maybe Int
           | ty = typeRep (Proxy :: Proxy ()) -> decode xenc :: Maybe ()
           | ...
         _ -> Nothing

but this is bad for several reasons:

  1. It's tedious to extend.
  2. It cannot handle pairs (or generally: tuples) generically; every combination of types needs to be handled.
  3. It's not very Haskelly

Solution

  • Data.Dynamic lets us put arbitrary Haskell values into a single container, and get them out again in a type-safe way. That's a good start towards inter-process communication; I'll come back to serialization below.

    We can write a program that takes a list of Dynamic values, checks for the number & types it needs, and returns a result in the same way.

    {-# LANGUAGE GADTs #-}
    {-# LANGUAGE KindSignatures #-}
    {-# LANGUAGE ScopedTypeVariables #-}
    -- | Experiments with type-safe serialization.
    
    module Main where
    
    import Data.Proxy
    import Data.Dynamic
    import Data.Foldable
    import Data.Type.Equality
    import Type.Reflection
    
    foo :: Int -> String -> String
    foo i s = concat (replicate i s)
    
    actor :: [Dynamic] -> Either String [Dynamic]
    actor (di : ds : _) = case (fromDynamic di, fromDynamic ds) of
        (Just i, Just s) -> Right [toDyn (foo i s)]
        _ -> Left "Wrong types of arguments"
    actor _ = Left "Not enough arguments"
    
    caller :: Either String [Dynamic]
    caller = actor [ toDyn (3::Int), toDyn "bar" ]
    
    main :: IO ()
    main = case caller of
        Left err -> putStrLn err
        Right dyns -> for_ dyns (\d -> case fromDynamic d of
                                        Just s -> putStrLn s
                                        Nothing -> print d)
    

    We can use a TypeRep to guide selection of a class instance. (For ease of testing my code, I used String.)

    class Serial a where
        encode :: a -> String
        decode :: String -> Maybe a
    
    decodeAs :: Serial a => TypeRep a -> String -> Maybe a
    decodeAs _ s = decode s
    

    Finally, we'd like to serialize the TypeRep, and when decoding, check that the encoded type matches the type that we're decoding at.

    instance Serial SomeTypeRep
    
    encodeDyn :: (Typeable a, Serial a) => a -> (String, String)
    encodeDyn a = (encode (SomeTypeRep (typeOf a)), encode a)
    
    decodeDynamic :: forall a. (Typeable a, Serial a) => String -> String -> Maybe a
    decodeDynamic tyStr aStr = case decode tyStr of
        Nothing -> Nothing
        Just (SomeTypeRep ty) ->
            case eqTypeRep ty (typeRep :: TypeRep a) of
                   Nothing -> Nothing
                   Just HRefl -> decodeAs ty aStr