[Haskell-beginners] Re: Encapsulation and Polymorphism
Michael Vanier
mvanier42 at gmail.com
Thu Aug 26 16:40:22 EDT 2010
Stephen,
I agree with your first point: existentials are not equivalent to
subtyping in OO.
I disagree with your assertion that existentials are too inert to be
useful. In fact, with Data.Typeable you can simulate full-blown dynamic
typing quite effectively. Here's a simple example:
{-# LANGUAGE
ExistentialQuantification,
DeriveDataTypeable
#-}
import Data.Typeable
data Obj = forall a . Typeable a => Obj a
deriving Typeable
getValue :: Typeable a => Obj -> Maybe a
getValue (Obj o) = cast o
intObj :: Obj
intObj = Obj (100 :: Integer)
strObj :: Obj
strObj = Obj "foobar"
floatObj :: Obj
floatObj = Obj (3.1415 :: Float)
test :: Obj -> IO ()
test o =
case getValue o of
(Just i :: Maybe Integer) -> print i
_ -> print "not an integer"
isInt :: Obj -> Bool
isInt o =
case getValue o of
(Just _ :: Maybe Integer) -> True
_ -> False
isFloat :: Obj -> Bool
isFloat o =
case getValue o of
(Just _ :: Maybe Float) -> True
_ -> False
isStr :: Obj -> Bool
isStr o =
case getValue o of
(Just _ :: Maybe String) -> True
_ -> False
test2 :: Obj -> IO ()
test2 o =
if isInt o
then print "int"
else if isFloat o
then print "float"
else if isStr o
then print "string"
else print "unknown"
Trying this code out, we have:
ghci> test intObj
100
ghci> test strObj
"not an integer"
ghci> test floatObj
"not an integer"
ghci> test2 intObj
"int"
ghci> test2 strObj
"string"
ghci> test2 floatObj
"float"
Existentials with type classes are equivalent to interfaces in most OO
languages. Existentials with Typeable give you dynamic typing. The
Data.Dynamic library provides the dynamic typing functions for you.
There are some limitations to this approach with respect to
polymorphism, but the same (or worse) limits would be seen in most OO
languages.
Mike
On 8/26/10 12:08 AM, Stephen Tetley wrote:
> Hi Drew
>
> Bear in mind though that existentials are not equivalent to subtyping in OO.
>
> For instance, with example 2.1 from [1] all you can do with an Obj is
> show it, so for the list xs all you can do is show the elements:
>
> data Obj = forall a. (Show a) => Obj a
>
> xs :: [Obj]
> xs = [Obj 1, Obj "foo", Obj 'c']
>
> Because Obj is an existential you can't do an case analysis on it - so
> you can't write a function like this:
>
> add_one_if_int (Obj (n::Int)) = Obj (n+1)
> add_one_if_int (Obj other) = Obj other
>
> There really is nothing you can do with Obj other than show it.
>
>
> If you are trying to transliterate OO designs, you might quickly find
> existentials are too inert to be useful.
>
> Best wishes
>
> Stephen
>
> [1] http://www.haskell.org/haskellwiki/Existential_type
>
>
> On 26 August 2010 07:45, Drew Haven<drew.haven at gmail.com> wrote:
>> I think I found the answers to all my questions at
>> http://www.haskell.org/haskellwiki/Existential_type
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
More information about the Beginners
mailing list