
the standard way to do that is use an existential wrapper: (This needs -fglasgow-exts or some flags)
module Main where
class Interface x where withName :: x -> String
data A = A String
instance Interface A where withName (A string) = "< Interface A with " ++ string ++ " >"
data B = B Int
instance Interface B where withName (B int) = "< Interface B with " ++ show int ++ " >"
data WrapInterface where WrapInterface :: forall z. Interface z => z -> WrapInterface
a :: A a = A "seven"
b :: B b = B 7
listOfWrapInterface :: [WrapInterface] listOfWrapInterface = [ WrapInterface a , WrapInterface b , WrapInterface (A "()") , WrapInterface (B (-2007)) ]
nameOfWrapped :: WrapInterface -> String nameOfWrapped (WrapInterface q) = withName q
instance Interface WrapInterface where withName = nameOfWrapped
main = do putStrLn (show (map nameOfWrapped listOfWrapInterface)) putStrLn (show (map withName listOfWrapInterface))
In ghci this prints: *Main> main ["< Interface A with seven >","< Interface B with 7 >","< Interface A with ()
","< Interface B with -2007 >"] ["< Interface A with seven >","< Interface B with 7 >","< Interface A with () ","< Interface B with -2007 >"]