Difference between revisions of "Heterogenous collections"

From HaskellWiki
Jump to navigation Jump to search
 
(Changed some wordings and fixed some general spelling mistakes.)
 
(15 intermediate revisions by 8 users not shown)
Line 1: Line 1:
  +
Techniques for implementing heterogeneous lists in Haskell.
This page is a very hasty and ad-hoc summary of a common discussion on
 
the haskell-cafe list. If you find it hard to read, please complain
 
there and somebody hopefully will come to help.
 
   
  +
== The problem ==
   
  +
Does some kind of collection of objects with different types in Haskell
=== The problem ===
 
  +
exist? Obviously, tuples are an example, but they have a fixed length.
  +
To compare tuples vs lists:
   
  +
{| border="1" cellpadding="2" align="center"
Is some kind of collection of object with different types in Haskell
 
  +
|-
exist? Except the tuples, which have fixed length. I find this
 
  +
!Tuples!!Lists
  +
|-
  +
|Heterogeneous||Homogeneous
  +
|-
  +
|Fixed length (per tuple type)||Variable length
  +
|-
  +
|Always finite||May be infinite
  +
|}
   
  +
However, what if we need a heterogeneous ''and'' non-fixed length collection? When one is
* Tuples heterogeneous, lists homogeneous.
 
  +
used to Java, with its loose typing of collections, not having this
* Tuples have a fixed length, or at least their length is encoded in their type. That is, two tuples with different lengths will have different types.
 
  +
immediately and easily available may seem strange. (Consider, for example, LinkedList<Object> from Java.)
* Tuples always finite.
 
   
  +
== Algebraic datatypes ==
But I need something which is heterogeneous and non-fixed length. I'm
 
used do Java, and this switch to functional languages is very strange to
 
me. So, to be clear, I need something like LinkedList<Object> in java.
 
   
  +
If the number of [[type]]s to cover is fixed, then the problem can be
 
  +
solved by a making a type with various data constructors, each representing a type:
=== Algebraic Datatypes ===
 
 
If the number of types to cover is fixed, then I suggest a data type
 
like
 
   
 
<haskell>
 
<haskell>
data T =
+
data T
ConsInt Int
+
= ConsInt Int
 
| ConsString String
 
| ConsString String
 
| ConsChar Char
 
| ConsChar Char
  +
</haskell>
  +
  +
which can be used like this:
  +
  +
<haskell>
  +
[ConsInt 42, ConsChar 'a', ConsString "foo"]
 
</haskell>
 
</haskell>
   
Line 35: Line 45:
 
data Object = IntObject Int | StringObject String
 
data Object = IntObject Int | StringObject String
   
  +
-- Note that it would be preferable to implement objectString as an instance of Show Object, this is just an example.
 
objectString :: Object -> String
 
objectString :: Object -> String
 
objectString (IntObject v) = show v
 
objectString (IntObject v) = show v
 
objectString (StringObject v) = v
 
objectString (StringObject v) = v
   
main = mapM (putStrLn . objectString) [(IntObject 7), (StringObject "eight")]
+
main = mapM_ (putStrLn . objectString) [(IntObject 7), (StringObject "eight")]
 
</haskell>
 
</haskell>
   
 
This is a very basic solution, and often preferable. Limitations: You
 
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
+
will have to pattern-match all the time if you want to do anything with the
objects in the List, and the collections are clumsy to extend by new
+
data stored in the list, and it will be cumbersome to add new types, as you'll
  +
have to handle them everywhere you use said list.
types.
 
   
  +
== A Universal type ==
   
  +
Similar to the Object type in Java, the <hask>Dynamic</hask> type in Haskell can be used to wrap any type in the Typeable class, creating a suitable wrapper:
   
  +
<haskell>
=== HLists, OOHaskell, Type-Level Programming ===
 
  +
import Data.Dynamic
  +
import Data.Maybe
   
  +
--
This is the cleanest solution, but very advanced and a little
 
  +
-- A list of dynamic
restrictive. Read these two articles:
 
  +
--
  +
hlist :: [Dynamic]
  +
hlist = [ toDyn "string"
  +
, toDyn (7 :: Int)
  +
, toDyn (pi :: Double)
  +
, toDyn 'x'
  +
, toDyn ((), Just "foo")
  +
]
   
  +
dyn :: Dynamic
* http://homepages.cwi.nl/~ralf/HList/
 
  +
dyn = hlist !! 1
* http://homepages.cwi.nl/~ralf/OOHaskell/
 
   
  +
--
There is also some related material here:
 
  +
-- unwrap the dynamic value, checking the type at runtime
  +
--
  +
v :: Int
  +
v = case fromDynamic dyn of
  +
Nothing -> error "Type mismatch"
  +
Just x -> x
  +
</haskell>
   
  +
== [[Existential types]] ==
* http://www.haskell.org/haskellwiki/Extensible_record
 
   
  +
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 akin to upcasting in Java to an interface that lets you print
=== Existential Types ===
 
  +
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,
Depending on your needs and your comfort level with fancier types, the
 
  +
and hide the actual value's types. Thus, objects of differing types can be used,
existential approach to ADTs might solve your problem. The following
 
  +
as long as they all provide a common interface.
code is a demonstration you can cut-and-paste-and-run.
 
   
  +
The most convenient way to pack a value with its methods is to use a typeclass
This is example akin to upcasting in Java to an interface that lets
 
  +
dictionary. The typeclass declaration defines the API to be wrapped with each
you print things. That way you know how to print every object (or do
 
  +
value. You can also pack up your own interface as an explicit field in the data
whatever else it is you need to do) in the list. Beware: there is no
 
  +
type, if you want to avoid type classes.
safe downcasting (that's what Typeable would be for); that would
 
likely be more than you need.
 
 
There are other ways to do this with existentials (e.g. bounded
 
existentials), but this is what came out of my head when I read your
 
post. Existentials seems to be the "Haskellish" way to reduce a
 
hetergenous list to a collection of objects with common operations.
 
HList would be the Haskellish way for more static and flexible
 
assurances.
 
   
 
<haskell>
 
<haskell>
{-# OPTIONS -fglasgow-exts #-}
+
{-# LANGUAGE ExistentialQuantification #-}
  +
--
  +
-- 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 => MkShowable a
   
  +
--
module Test where
 
  +
-- And a nice existential builder
  +
--
  +
pack :: Show a => a -> Showable
  +
pack = MkShowable
   
  +
--
data PrintPackage = forall a . PrintPackage a (a -> String)
 
  +
-- A heteoregenous list of Showable values
  +
--
  +
hlist :: [Showable]
  +
hlist = [ pack 3
  +
, pack 'x'
  +
, pack pi
  +
, pack "string"
  +
, pack (Just ()) ]
   
  +
--
instance Show PrintPackage where
 
  +
-- The only thing we can do to Showable values is show them
show (PrintPackage val showMethod) = showMethod val
 
  +
--
  +
main :: IO ()
  +
main = print $ map f hlist
  +
where
  +
f (MkShowable a) = show a
   
  +
{-
list = [ PrintPackage 3 show
 
, PrintPackage "string" show
 
, PrintPackage 3.4 show
 
]
 
   
  +
*Main> main
main = print list
 
  +
["3","'x'","3.141592653589793","\"string\"","Just ()"]
  +
  +
-}
 
</haskell>
 
</haskell>
  +
  +
One can of course make the type <hask>Showable</hask> an instance of the type class <hask>Show</hask> itself
  +
<haskell>
  +
--
  +
-- Make Showable itself an instance of Show
  +
--
  +
instance Show Showable
  +
where
  +
showsPrec p (MkShowable a) = showsPrec p a
  +
  +
--
  +
-- The only thing we can do to Showable values is show them
  +
--
  +
main :: IO ()
  +
main = print hlist
  +
  +
{-
  +
*Main> main
  +
[3,'x',3.14159265358979,"string",Just ()]
  +
-}
  +
</haskell>
  +
Note how we didn't need to unwrap and show the values explicitly ourselves.
  +
  +
There's an alternative way of defining an existential datatype, using [[Generalised algebraic datatype | GADT]] syntax. Instead of writing
  +
<haskell>
  +
data Showable = forall a . Show a => MkShowable a
  +
</haskell>
  +
one writes
  +
<haskell>
  +
data Showable
  +
where
  +
MkShowable :: Show a => a -> Showable
  +
</haskell>
  +
i.e. giving an explicit type signature for the <hask>MkShowable</hask> data constructor.
  +
(Using explicit <hask>forall a.</hask> before the <hask>Show a =></hask> part is allowed, but not required, just as for ordinary type signatures.)
  +
  +
== HLists, OOHaskell, type-level programming ==
  +
  +
This is the cleanest solution, but very advanced and a little restrictive.
  +
Read these two articles:
  +
  +
* [http://okmij.org/ftp/Haskell/HList-ext.pdf Haskell's overlooked object system] (PDF)
  +
* [http://okmij.org/ftp/Haskell/types.html#HList Strongly typed heterogeneous collections]
  +
  +
There is also some related material here:
  +
  +
* [[Extensible record]]
  +
  +
  +
  +
[[Category:FAQ]]
  +
[[Category:Idioms]]
  +
[[Category:Glossary]]

Latest revision as of 11:44, 22 August 2021

Techniques for implementing heterogeneous 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, what if we need a heterogeneous and non-fixed length collection? When one is used to Java, with its loose typing of collections, not having this immediately and easily available may seem strange. (Consider, for example, LinkedList<Object> from Java.)

Algebraic datatypes

If the number of types to cover is fixed, then the problem can be solved by a making a type with various data constructors, each representing a type:

data T
   = ConsInt    Int
   | ConsString String
   | ConsChar   Char

which can be used like this:

[ConsInt 42, ConsChar 'a', ConsString "foo"]

or:

data Object = IntObject Int | StringObject String

-- Note that it would be preferable to implement objectString as an instance of Show Object, this is just an example.
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 will have to pattern-match all the time if you want to do anything with the data stored in the list, and it will be cumbersome to add new types, as you'll have to handle them everywhere you use said list.

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 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.

{-# LANGUAGE ExistentialQuantification #-}
--
-- 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 => MkShowable a

--
-- And a nice existential builder
--
pack :: Show a => a -> Showable
pack = MkShowable

--
-- 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 (MkShowable a) = show a

{-

*Main> main
["3","'x'","3.141592653589793","\"string\"","Just ()"]

-}

One can of course make the type Showable an instance of the type class Show itself

--
-- Make Showable itself an instance of Show
--
instance Show Showable
  where
  showsPrec p (MkShowable a) = showsPrec p a

--
-- The only thing we can do to Showable values is show them
--
main :: IO ()
main = print hlist

{-
*Main> main
[3,'x',3.14159265358979,"string",Just ()]
-}

Note how we didn't need to unwrap and show the values explicitly ourselves.

There's an alternative way of defining an existential datatype, using GADT syntax. Instead of writing

data Showable = forall a . Show a => MkShowable a

one writes

data Showable
  where
  MkShowable :: Show a => a -> Showable

i.e. giving an explicit type signature for the MkShowable data constructor. (Using explicit forall a. before the Show a => part is allowed, but not required, just as for ordinary type signatures.)

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: