Functions with generic return types

Hi, I'm trying to write a small module for conveniently writing functions that can return any of a finite number of types. That is, I'd like to be able to write something like foo :: StringOrInt t => String -> IO t This is pretty easy to do if I hard-code the classes as above, but I run into difficulties making it more general. In particular, it's convenient to use incoherent instances so that I can insert the polymorphism at whatever level I choose (see the third instance declaration below, as well as the function foo). But when I try to make this work for monads, it fails - that is, my function bar (below) always prints both "str" and "int" because I can't make it lazy enough - in order to get even a thunk in the non-monadic type, it seems like the side effect has to happen (unsafeInterleaveIO + seq would sort of fix this here, but not generally), whereas the type alone should be sufficient in selecting which monad needs to be evaluated. I'm having a hard time explaining this abstractly, but I think the following concrete code explains pretty clearly what I'm trying to do, and I would appreciate any comments or suggestions for either a better way to go about this, or something already written that achieves something similar? Thanks, steve ==== {-# LANGUAGE TypeSynonymInstances, MultiParamTypeClasses, FlexibleInstances, FlexibleContexts, IncoherentInstances #-} class Pick c a where pick :: c -> a instance Pick (a,b) a where pick = fst instance Pick (a,b) b where pick = snd instance Pick (a,b) c => Pick (d -> a, d -> b) (d -> c) where pick (a,b) d = pick (a d,b d) -- This instance definition is broken... instance (Monad m,Pick (a,b) c) => Pick (m a,m b) (m c) where pick (ma,mb) = do { a <- ma; b <- mb; return $ pick (a,b) } foo :: Pick (String,Int) t => String -> t foo = pick (id :: String -> String, length :: String -> Int) toStr :: String -> IO String toStr s = putStrLn "str" >> return s toInt :: String -> IO Int toInt s = putStrLn "int" >> return (length s) bar :: Pick (String,Int) t => String -> IO t bar = pick (toStr,toInt)

On Mon, Jan 12, 2009 at 5:56 PM, Stephen Hicks
-- This instance definition is broken... instance (Monad m,Pick (a,b) c) => Pick (m a,m b) (m c) where pick (ma,mb) = do { a <- ma; b <- mb; return $ pick (a,b) }
First, and I know these types of comments are generally unwanted, but I recommend you *not do this*. You are only making pain for yourself later. Haskell is not good at this type of ad-hoc polymorphism (partially because it does not play well with inference). I.e. whyever you think you need this machinery, I suggest you spend some time rethinking why this is really necessary. Okay, now to explain this instance. An instance Pick (a,b) c is just a function (a,b) -> c. So this instance reduces to the possibility of writing a function: monadify :: ((a,b) -> c) -> ((m a, m b) -> m c) Which is only implementable by executing both actions m a and m b (because you need both an a and a b to pass to c). Consider what would happen if a pick function looked at the contents of its argument? e.g. maybe someone writes: instance Pick (Int,Int) Int where pick (x,y) = min x y Then you would have to know the actual values to decide what to return, thus both actions must be executed. One thing I always like to do when I'm writing typeclasses is write the proof term library first (i.e. explicit dictionary passing) and then start turning those into typeclasses. This practice helps to weed out impossible ideas (eg. if you can't do what you want by explicitly passing dictionaries, how is the compiler going to infer the dictionaries for you?), and also to make more transparent what terms are being constructed. As an example, you might start: type PickD a b = a -> b leftTuple :: PickD (a,b) a leftTuple = fst rightTuple :: PickD (a,b) b rightTuple = snd func :: PickD (a,b) c -> PickD (d -> a, d -> b) (d -> c) func p (f,g) x = p (f x, g x) ... And do this for each of your proposed instances. Then do an example use case, using these functions explicitly, and try to envisage an algorithm which might pick the functions for you. Then it will be much more obvious if it is possible to typeclassify these, and if so, how. Luke
foo :: Pick (String,Int) t => String -> t foo = pick (id :: String -> String, length :: String -> Int)
toStr :: String -> IO String toStr s = putStrLn "str" >> return s toInt :: String -> IO Int toInt s = putStrLn "int" >> return (length s)
bar :: Pick (String,Int) t => String -> IO t bar = pick (toStr,toInt) _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (2)
-
Luke Palmer
-
Stephen Hicks