Heterogenous collections: Difference between revisions
(Category:Idioms) |
(Category:FAQ) |
||
Line 160: | Line 160: | ||
[[Category:FAQ]] | |||
[[Category:Idioms]] | [[Category:Idioms]] | ||
[[Category:Glossary]] | [[Category:Glossary]] |
Revision as of 14:03, 20 November 2006
Techniques for implementing heterogenous lists in Haskell.
The problem
Does some kind of collection of objects with different types in Haskell exist? Obviously, tuples are an example, but they have a fixed length. To compare tuples vs lists:
Tuples | Lists |
---|---|
Heterogeneous | Homogeneous |
Fixed length (per tuple type) | Variable length |
Always finite | May be infinite |
However, the need is for heterogeneous and non-fixed length. When one is used to Java, with its loose typing of collections,not having this immediately and easily available seems strange. As an example, the need is for something like LinkedList<Object> from Java.
Algebraic datatypes
If the number of types to cover is fixed, then the problem can be solved by a list of data types such as
data T
= ConsInt Int
| ConsString String
| ConsChar Char
or:
data Object = IntObject Int | StringObject String
objectString :: Object -> String
objectString (IntObject v) = show v
objectString (StringObject v) = v
main = mapM_ (putStrLn . objectString) [(IntObject 7), (StringObject "eight")]
This is a very basic solution, and often preferable. Limitations: You have to type-switch all the time if you want to do anything with the objects in the List, and the collections are clumsy to extend by new types.
A Universal type
Similar to the Object type in Java, the Dynamic
type in
Haskell can be used to wrap any type in the Typeable class, creating a
suitable wrapper:
import Data.Dynamic
import Data.Maybe
--
-- A list of dynamic
--
hlist :: [Dynamic]
hlist = [ toDyn "string"
, toDyn (7 :: Int)
, toDyn (pi :: Double)
, toDyn 'x'
, toDyn ((), Just "foo")
]
dyn :: Dynamic
dyn = hlist !! 1
--
-- unwrap the dynamic value, checking the type at runtime
--
v :: Int
v = case fromDynamic dyn of
Nothing -> error "Type mismatch"
Just x -> x
Existential types
Depending on needs and comfort level with fancier types, the existential approach to ADTs might solve the problem. The types aren't that scary.
This is example akin to upcasting in Java to an interface that lets you print things. That way you know how to print every object (or do whatever else it is you need to do) in the list. Beware: there is no safe downcasting (that's what Typeable would be for); that would likely be more than you need.
Essentially existential values pack up a value with operations on that value, and hide the actual value's types. Thus objects of differing types can be used, as long as they all provide a common interface.
The most convenient way to pack a value with its methods is to use a typeclass dictionary. The typeclass declaration defines the api to be wrapped with each value. You can also pack up your own interface as an explicit field in the data type, if you want to avoid type classes.
{-# OPTIONS -fglasgow-exts #-}
--
-- An existential type encapsulating types that can be Shown
-- The interface to the type is held in the show method dictionary
--
-- Create your own typeclass for packing up other interfaces
--
data Showable = forall a . Show a => Showable a
--
-- And a nice existential builder
--
pack :: Show a => a -> Showable
pack = Showable
--
-- A heteoregenous list of Showable values
--
hlist :: [Showable]
hlist = [ pack 3
, pack 'x'
, pack pi
, pack "string"
, pack (Just ()) ]
--
-- The only thing we can do to Showable values is show them
--
main :: IO ()
main = print $ map f hlist
where
f (Showable a) = show a
{-
*Main> main
["3","'x'","3.141592653589793","\"string\"","Just ()"]
-}
HLists, OOHaskell, type-level programming
This is the cleanest solution, but very advanced and a little restrictive. Read these two articles:
There is also some related material here: