3

This seems like a reasonable thing to want, but I'm having type troubles. I'd like to have a Client that can send a list of options to a Server, which will choose one and return the chosen element. So something like this:

module Toy where

import Pipes

asker :: Monad m => () -> Client ([a], a -> String) a m ()
asker () = do
    _ <- request ([0.0, 2.0], show)
    _ <- request (["3", "4"], show)
    return ()

The idea is that the server can call the a -> String function on each element of the list to display them to a user. I'd like to be able to vary a, as long as the list and function match.

Is something like this possible? Maybe the constraints I want can be encoded into a GADT somehow?

Davorak
  • 7,362
  • 1
  • 38
  • 48
ajp
  • 1,723
  • 14
  • 22
  • 2
    What does the server do with the request? What could it do if it doesn't even know what type it will get? If it can only convert that type to a String (using the function), why don't you pass a String in the first case? – bennofs Jul 06 '13 at 22:59
  • I guess that's true. It would be nice to not have to convert the response back from a String, but it's not a huge deal. – ajp Jul 07 '13 at 00:22
  • 2
    @ajp: Is the idea that (a) the client sends values of *some* type that conforms to an interface (*e.g.* `Show`); (b) the server accepts values of *any* such type; and (c) when the client receives a response from the server, it knows which type it was that it sent? Step (c) is going to be the sticking point (consider what happens if the server decides to respond with the same value twice, or not at all); you'll probably either want a sum type or something like `Typeable`/`Dynamic`. Existentials (what you're getting at with GADTs) can never be unpacked to learn what the original type was. – Antal Spector-Zabusky Jul 07 '13 at 01:07
  • yes, that's pretty much it. Thanks! – ajp Jul 07 '13 at 03:05

1 Answers1

4

You can't do it quite the way you asked, but you can cheat a little bit and get something that's almost as good:

{-# LANGUAGE ExistentialQuantification #-}

module Toy where

import Control.Monad
import Pipes
import Pipes.Prelude (foreverK)

data Request = forall a . Request [a] (a -> String)

asker :: Monad m => () -> Client Request Int m ()
asker () = do
    _ <- request (Request [0.0, 2.0] show)
    _ <- request (Request ["3", "4"] show)
    return ()

server :: Request -> Server Request Int IO r
server = foreverK $ \req -> case req of
    Request as f -> do
        choice <- lift $ do
            let select = do
                putStrLn "Select an option"
                forM_ (zip [0..] as) $ \(n, a) ->
                    putStrLn $ show n ++ ": " ++ f a
                n <- readLn
                if (n >= length as)
                then do
                    putStrLn "Invalid selection"
                    select
                else return n
            select
        respond choice

Instead of returning back the value selected, you return back an Int corresponding to the index of the selected element. The rest is just using ExistentialQuantification.

Like others recommended, I suggest that you actually just send a list of Strings instead of using the existential quantification trick, but I included it just to show how that would be done just in case you were curious.

Gabriella Gonzalez
  • 34,863
  • 3
  • 77
  • 135