
|data Test = Test { foo :: Int, bar :: Char, baz :: Bool } |smallPrint t = concatMap (\f -> show $ f t) [foo, bar, baz] |In this code the list [foo, bar, baz] should have the type [exists a. Show a => Test -> a]. {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ExistentialQuantification #-} data EShow = forall a. Show a => EShow a smallPrint t = concatMap (\f-> case f t of EShow a -> show a) [EShow . foo, EShow . bar, EShow . baz] data Test = Test { foo :: Int, bar :: Char, baz :: Bool } Apart from the extra wrapping, this hardcodes the class. So perhaps you'd prefer something like data E t = forall a. E (a->t) a smallPrint' t = concatMap (\f-> case f t of E show a -> show a) [E show . foo, E show . bar, E show . baz] GHC does have existentials (Hugs has them, too, and HBC had them as well?), but is more conservative about their use than UHC seems to be. Claus PS there's also the old standby of applying the functions in the interface and letting non-strict evaluation taking care of the rest (keeping the intermediate type implicit, instead of explicitly hidden): smallPrint_ t = concatMap (\f-> f t) [show . foo, show . bar, show . baz]