Keean Schupke wrote:
Hmm... actually they can be used on the LHS...
{-# OPTIONS -fglasgow-exts #-}
module Main where
class Test a b | a -> b where test :: a -> b
newtype I = I (forall a . Integral a => a) newtype S = S (forall a . Show a => a)
instance Test I Int where test _ = 7
instance Test S String where test _ = "TEST"
main = do putStrLn $ show $ test (I undefined) putStrLn $ show $ test (S undefined)
Not sure how you would use them, but you can wrap a higher ranked type in a newtype and use it as a label.
It is actually the head of the type (I or S) that selects the instance, the rest is not useful. This raises the question of how you get your higher ranked type into the right wrapper... the answer is (I think) you can't... it must already be in the wrapper to differentiate it. This reduces to the same situation as before and you might as well have I and S as first class labels and drop the higher-ranked type.
Keean. _______________________________________________ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell