简体   繁体   中英

mapping list of different types implementing same function?

I want to apply a function to every element in a list (map) but the elements may have different types but all implement the same function (here "putOut") like an interface. However I cannot create a list of this "interface" type (here "Outputable").

How do I map a list of different types implementing the same function?

import Control.Monad

main :: IO ()
main = do
 mapM_ putOut lst
 where
  lst :: [Outputable] -- ERROR: Class "Outputable" used as a type
  lst = [(Out1 1),(Out2 1 2)]

class Outputable a where
 putOut :: a -> IO ()

-- user defined:

data Out1 = Out1 Int deriving (Show)
data Out2 = Out2 Int Int deriving (Show)

instance Outputable Out1 where
 putOut out1 = putStrLn $ show out1

instance Outputable Out2 where
 putOut out2 = putStrLn $ show out2

Haskell doesn't allow for heterogenous lists. So you cannot make a list of Outputables, because your Out1 and Out2 are two distinct types, even if they both belong to the same type class.

But there is a workaround which allows to simulate heterogeneous lists with ExistentialQuantification . See an example of heterogeneous lists in Haskell wikibook.

How to use

  1. Put {-# LANGUAGE ExistentialQuantification #-} at the top of the module

  2. Define a box type, which hides heterogeneous elements inside:

      data ShowBox = forall s. Show s => SB s heteroList :: [ShowBox] heteroList = [SB (), SB 5, SB True] 
  3. Define a necessary class instance for the box type itself:

      instance Show ShowBox where show (SB s) = show s 
  4. Use a list of boxes.

An example

Your example may be rewritten as:

{-# LANGUAGE ExistentialQuantification #-}

main :: IO ()
main = do
 mapM_ print lst
 putStrLn "end"
 where
  lst :: [Printable]
  lst = [P (Out1 1),P (Out2 1 2)]

-- box type (2)
data Printable = forall a . Show a => P a

-- necessary Show instance for the box type (3)
instance Show Printable where show (P x) = show x

-- user defined:
data Out1 = Out1 Int deriving (Show)
data Out2 = Out2 Int Int deriving (Show)

Are you sure you really want to put different types in a list?

You could use something like jetxee 's example with existential quantification, but think about what that actually does: You have a list of terms of unknown type, and the only thing you can do with them is apply putOut to get an IO () value back. That is to say, if the "interface" only provides one function with a known result type, there's no difference between a list of existentials and a list of results . The only possible use of the former involves converting it to the latter, so why add the extra intermediate step? Use something like this instead:

main :: IO ()
main = do
    sequence_ lst
    where lst :: [IO ()]
          lst = [out1 1, out2 1 2]

out1 x = putStrLn $ unwords ["Out1", show x]
out2 x y = putStrLn $ unwords ["Out2", show x, show y]

This may seem counterintuitive at first, because it relies on some unusual features of Haskell. Consider:

  • No extra computation is done--lazy evaluation means that show , unwords , &c. won't be run unless the IO action is executed.
  • No side effects are involved in simply creating IO () values--they can be stored in lists, passed around in pure code, and so on. It's only the sequence_ function in main that runs them.

The same argument applies to lists of "instances of Show " and whatnot. It doesn't work well for instances of something like Eq , where you need two values of the type, but a list of existentials wouldn't work any better because you don't know if any two values are the same type. All you could do in that case would be check each element to be equal to itself, and then you might as well (as above) just create a list of Bool s and be done with it.


In more general cases, it's best to keep in mind that Haskell type classes are not OOP interfaces . Type classes are a powerful means of implementing ad-hoc polymorphism, but are not as well-suited to hiding implementation details. OOP languages tend to conflate ad-hoc polymorphism, code reuse, data encapsulation, behavioral subtyping, and such by tying everything to the same class hierarchy; in Haskell you can (and often must ) deal with each separately.

An object in an OOP language is, roughly speaking, a collection of (hidden, encapsulated) data bundled with functions to manipulate that data, each of which takes the encapsulated data as an implicit argument ( this , self , etc.). To replicate this in Haskell, you don't need type classes at all:

  • Write each "class method" as a regular function, with the self parameter made explicit.
  • Partially apply each function to a value of the "encapsulated" data
  • Combine the partially applied functions into a single record type

The record type replaces the interface ; any collection of functions with the proper signatures represents an implementation of the interface. In some ways this is actually better object-oriented style , because the private data is completely hidden and only the exterior behavior is exposed.

As in the simpler case above, this is almost exactly equivalent to the existential version; the record of functions is what you'd get by applying each method of the type class to each existential.

There are some type classes where using a record of functions wouldn't work well-- Monad , for instance--which are generally also the same type classes that can't be expressed by conventional OOP interfaces , as demonstrated by modern versions of C# making extensive use of monadic style yet not providing any sort of generic IMonad interface.

See also this article covering the same things I'm saying. You may also want to look at Graphics.DrawingCombinators for an example of a library offering extensible, composable graphics without using type classes .

The technical post webpages of this site follow the CC BY-SA 4.0 protocol. If you need to reprint, please indicate the site URL or the original address.Any question please contact:yoyou2525@163.com.

 
粤ICP备18138465号  © 2020-2024 STACKOOM.COM