
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)