[Haskell-cafe] Client-extensible heterogeneous types (Duck-typed variadic functions?)

Jacek Generowicz jacek.generowicz at cern.ch
Wed Oct 13 19:07:29 EDT 2010


On 2010 Oct 13, at 23:52, Evan Laforge wrote:

> I admit I haven't read this whole thread in detail, but when I want
> something with an implementation that can vary dynamically I just pass
> a different function.

Of course.

> Your original python example is equivalent to
> just passing strings in haskell,

Sure. The original example was kept trivial, thereby hiding the true  
problem.

> so lets add an argument:
>
> type Process = Int -> String
>
> heterogeneousProcessor :: [Process] -> [String]
> heterogeneousProcessor ps = [p 42 | p <- ps] -- or map ($42) ps
>
> variant1 n = "variant1 stuff " ++ show n
> -- etc.
>
> Now the user of your library can pass their own Process.

Which works just fine, if all the different things I might wish to  
express can be expressed within (Int -> String) (or any other function  
type).

> I have a number of records in my program like "State { lookup_x ::
> Name -> Maybe X, lookup_y :: Name -> Maybe Y, do_something_important
> :: X -> Result }".  They reduce dependencies by not exposing the
> (complicated) lookup details and types, and aid testing because I can
> just pass a state with a dummy 'do_something_important' (in my case,
> it's "update GUI", which is important to stub out for a test).

I think I'm starting too see what my problem is. I think it boils down  
to hankering for Duck Typing and variadic functions. I fully  
appreciate that passing functions is a wonderful and powerful  
technique for catering for variation, but Haskell's type system cramps  
my style by insisting that I can't put a (Banana -> Cake) in the same  
container as an (Octopus -> Truffles -> DogsBreakfast).

I can get around this by creating a variant type which contains both  
of these (and any others I might ever need to use), but

a) It's bloody tedious (compared to having to do exactly nothing in  
Duck Typing),

b) The set of acceptable function types is not extensible by clients.

Put another way, your X and Y types aren't flexible/large enough.

> This may be simpler than what you had in mind, but to narrow it down,
> could you provide a more specific example where this is inadequate?

How about this?

-- Imagine that I want to write a program which will help me practice
-- basic arithmetic.

-- At its core I might have the following three functions

ask :: (Int, Int) -> String
ask (a,b) = show a ++ " + " ++ show b

answer :: (Int, Int) -> Int
answer (a,b) = a + b

check :: (Int, Int) -> String -> Bool
check  q ans = (read ans :: Int) == answer q

-- which present the question, and check whether a given answer is
-- correct.

-- Now, imagine I've got addition down pat, and want to extend my
-- repertoire to subtraction. I could introduce some flexibility into
-- my core functions thus

data Operation = Operation (Int -> Int -> Int) String

ask' :: (Int, Int) -> Operation -> String
ask'    (a,b) (Operation _ sym) = show a ++ " " ++ sym ++ " " ++ show b

answer' :: (Int, Int) -> Operation -> Int
answer' (a,b) (Operation op _)  = op a b

check' :: (Int, Int) -> Operation -> String -> Bool
check' q op ans = (read ans :: Int) == answer' q op

-- Now my program can deal with any binary infix operations on
-- Ints. But what if I now want to practice a unary operation
-- (e.g. sqrt)? How about a binary prefix one (e.g. gdc) ?

-- Maybe this is the way forward?

data Question =
     BinaryInfix  (Int -> Int -> Int) String Int Int |
     BinaryPrefix (Int -> Int -> Int) String Int Int |
     UnaryPrefix  (Int -> Int)        String Int

ask'' :: Question -> String
ask'' (BinaryInfix  _ sym a b) = show a ++ " " ++ sym ++ " " ++ show b
ask'' (BinaryPrefix _ sym a b) = sym ++ " " ++ show a ++ " " ++ show b
ask'' (UnaryPrefix  _ sym a)   = sym ++ " " ++ show a

answer'' :: Question -> Int
answer'' (BinaryInfix  op _ a b) = op a b
answer'' (BinaryPrefix op _ a b) = op a b
answer'' (UnaryPrefix  op _ a)   = op a

check'' :: Question -> String -> Bool
check'' q a = (read a :: Int) == answer'' q

-- So far, so ... not too bad.

-- I'm a little annoyed by the repetitive tedium of answer'': this
-- will really wind me up when I get on to TernaryPrefix,
-- QuaternaryPrefix etc. and I will hanker for something like Python's
-- *args.

-- Now, I go to a party and thoroughly impress my friends with my
-- newly-acquired arithmetic wizardry. One thing leads to another and
-- my program ends up in the hands of another soul or two, desperate
-- to match my mental calculation powers: I acquire some users. And as
-- every schoolboy knows, users are closely followed by feature
-- requests.

-- John wants to practice adding fractions. Cindy needs to learn to
-- find all prime factors of a given number.

-- Clearly
--
--      check'' q a = (read a :: Int) == answer'' q
--
-- won't cut the mustard any more.

-- Now, I can't see any obvious reason why I can't just keep adding
-- new constructors to Question, and corresponding patterns to ask,
-- answer and check, but I'm a lazy bugger and want to palm this off
-- onto the users by telling them that I am empowering them by giving
-- them the ability to add new question types to the framework.

-- How would I enable them to do this without them having to mess with
-- the original source?

-- More generally, I'd be happy to be given advice on how to structure
-- this sort of program in Haskell.



More information about the Haskell-Cafe mailing list