Depending on your needs and your comfort level with fancier types, the
existential approach to ADTs might solve your problem. The following
code is a demonstration you can cut-and-paste-and-run.

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.

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.

{-# OPTIONS -fglasgow-exts #-}

module Test where

data PrintPackage = forall a . PrintPackage a (a -> String)

instance Show PrintPackage where
   show (PrintPackage val showMethod) = showMethod val

list = [ PrintPackage 3 show
      , PrintPackage "string" show
      , PrintPackage 3.4 show
      ]

main = print list

Hope that helps more than it confuses,
Nick

On 11/17/06, Henning Thielemann <[EMAIL PROTECTED]> wrote:

On Fri, 17 Nov 2006, Valentin Gjorgjioski wrote:

> Is some kind of collection of object with different types in Haskell exist?
> Except the tuples, which have fixed length.
> I find this
>
>    * Tuples heterogeneous, lists homogeneous.
>    * 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.
>    * Tuples always finite.
>
> 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.
>
> Can you please help me or suggest me, what can I use in this case?

If the number of types to cover is fixed, then I suggest a data type like

data T =
     ConsInt    Int
   | ConsString String
   | ConsChar   Char


Since this is a very FAQ I wonder why I don't find the answer in any of
the Haskell wikis.
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to