Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1. Re:  Re: Encapsulation and Polymorphism (Michael Vanier)
   2. Re:  Re: Encapsulation and Polymorphism (Stephen Tetley)
   3.  instances of different kinds (Greg)
   4. Fwd: [Haskell-beginners] instances of different kinds
      (Tobias Brandt)
   5. Re:  instances of different kinds (J?rgen Doser)


----------------------------------------------------------------------

Message: 1
Date: Thu, 26 Aug 2010 13:40:22 -0700
From: Michael Vanier <mvanie...@gmail.com>
Subject: Re: [Haskell-beginners] Re: Encapsulation and Polymorphism
To: Stephen Tetley <stephen.tet...@gmail.com>
Cc: beginners@haskell.org
Message-ID: <4c76d136.5050...@cs.caltech.edu>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

  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.ha...@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@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners



------------------------------

Message: 2
Date: Fri, 27 Aug 2010 08:23:06 +0100
From: Stephen Tetley <stephen.tet...@gmail.com>
Subject: Re: [Haskell-beginners] Re: Encapsulation and Polymorphism
Cc: beginners@haskell.org
Message-ID:
        <aanlktiml1yy_h2me2uclctnbrvhjjvqtisgrs099k...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Hello Michael

I think I put my point forward with too little nuance, my point wasn't
that existentials aren't useful[*] (I did call them inert rather then
useless...), but that they aren't the rosetta stone for getting to
flexible designs. They do solve the original posters problem of
putting objects different types in a list, but with the expense that
they need heavy use of classes afterwards to be able to manipulate
them.

For the original problem, dynamic typing with Data.Typeable would
probably be a better solution as it avoids annotating the existential
Obj type with every class the simulation needs.

Best wishes

Stephen


[*] I think with just existentials you can get dynamic types -
Data.Typeable itself use a couple of other tricks (unsafe coerce), see
"Typing Dynamic Typing" Arthur I. Baars and S. Doaitse Swierstra or "A
Lightweight Implementation of Generics and Dynamics" James Cheney and
Ralf Hinze.


------------------------------

Message: 3
Date: Fri, 27 Aug 2010 01:58:34 -0700
From: Greg <gregli...@me.com>
Subject: [Haskell-beginners] instances of different kinds
To: beginners@haskell.org
Message-ID: <e315c616-aa1c-4ef4-9efd-5a6d0a8c9...@me.com>
Content-Type: text/plain; charset="us-ascii"

Hi--

More silly typeclass questions.  I'm not sure the right way to ask it, so I'll 
start with a failed code snippet:

data Foo a = Foo a 

class TwoPi a where
  div2pi :: (Floating b) => a -> b

instance (Floating a) => TwoPi (Foo a) where
  div2pi (Foo a) = a / (2*pi)

instance TwoPi Float where
  div2pi a = a / (2*pi)


This code is obviously meaningless, but I'm trying to figure out how you can 
create instances of a typeclass for data types of different kinds.

I have a similar piece of code that works:

data Foo a = Foo a 


class Testable a where
  isPos :: a -> Bool

instance (Ord b, Num b) => Testable (Foo b) where
  isPos (Foo b) = b > 0

instance Testable Float where
  isPos a = a > 0


One obvious difference is that the type of isPos is a -> Bool, with a defined 
type as the return.  I'd rather not commit to a specific Floating type up front 
(I'd prefer sometimes Float sometimes Double, depending on the 'a' in Foo a, 
but trying to declare it as Float doesn't help me.  This fails:

data Foo a = Foo a 

class TwoPi a where
  div2pi :: a -> Float

instance (Floating b) => TwoPi (Foo b) where
  div2pi (Foo b) = b / (2*pi)

instance TwoPi Float where
  div2pi a = a / (2*pi)


The errors I'm getting are various permutations of:

    Couldn't match expected type `Float' against inferred type `b'
      `b' is a rigid type variable bound by
          the instance declaration at gcbTestBad.hs:8:19
    In the expression: b / (2 * pi)
    In the definition of `div2pi': div2pi (Foo b) = b / (2 * pi)
    In the instance declaration for `TwoPi (Foo b)'

What is the difference between these last two cases ("a -> Bool" and "a -> 
Float"), and is there anyway to make "a -> b" work? 

Thanks--
 Greg
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20100827/cf08a228/attachment-0001.html

------------------------------

Message: 4
Date: Fri, 27 Aug 2010 11:15:47 +0200
From: Tobias Brandt <tob.bra...@googlemail.com>
Subject: Fwd: [Haskell-beginners] instances of different kinds
To: beginners@haskell.org
Message-ID:
        <aanlkti=bbp-bg88nqn4hc3r17rja58ryx9jep+gqj...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Forgot to reply to the list, sorry.


---------- Forwarded message ----------
From: Tobias Brandt <tob.bra...@googlemail.com>
Date: 27 August 2010 11:14
Subject: Re: [Haskell-beginners] instances of different kinds
To: Greg <gregli...@me.com>


On 27 August 2010 10:58, Greg <gregli...@me.com> wrote:
> data Foo a = Foo a
>
> class TwoPi a where
>   div2pi :: (Floating b) => a -> b
>

div2pi is polymorphic in a AND b. They are completely independent.

> instance (Floating a) => TwoPi (Foo a) where
>   div2pi (Foo a) = a / (2*pi)
>

but here, div2pi has type Floating a => Foo a -> a.

>
> data Foo a = Foo a
>
> class TwoPi a where
>   div2pi :: a -> Float
>
> instance (Floating b) => TwoPi (Foo b) where
>   div2pi (Foo b) = b / (2*pi)
>

now div2pi has type Floating a :: Foo a -> a, but should
have Floating a :: Foo a -> Float


There are two possible solutions (I can think of).

1. make div2pi less polymorphic:

  class TwoPi a where div2pi :: a -> a

  then your first instance works


2. use associated types:

  class TwoPi a where
      type TwoPiRes a
      div2pi :: a -> TwoPiRes a

  instance Floating a => TwoPi (Foo a) where
      type TwoPiRes (Foo a) = a
      div2pi (Foo a) = a /(2*pi)


------------------------------

Message: 5
Date: Fri, 27 Aug 2010 11:31:38 +0200
From: J?rgen Doser <jurgen.do...@gmail.com>
Subject: Re: [Haskell-beginners] instances of different kinds
To: beginners@haskell.org
Message-ID: <1282901498.3469.15.ca...@imedia.irun.org>
Content-Type: text/plain; charset=utf-8

El vie, 27-08-2010 a las 01:58 -0700, Greg escribió:
> Hi--
> 
> 
> More silly typeclass questions.  I'm not sure the right way to ask it,
> so I'll start with a failed code snippet:
> 
> 
> data Foo a = Foo a 
> 
> class TwoPi a where
>   div2pi :: (Floating b) => a -> b
> 
> instance (Floating a) => TwoPi (Foo a) where
>   div2pi (Foo a) = a / (2*pi)
> 
a/(2*pi) has type Floating a => a, where a is the type of a in Foo a.
the class declaration however requires to be able to return a value of
type Floating b => b for any type b, no relation to a whatsoever.

> instance TwoPi Float where
>   div2pi a = a / (2*pi)
> 
a/(2*pi) has type Float (because a has type Float), so this again can
not work.
> 
You would need a function f::(Floating b) => Float -> b for this to
work. In the former, you would need a function f::(Floating a, Floating
b) => a -> b.

> This code is obviously meaningless, but I'm trying to figure out how
> you can create instances of a typeclass for data types of different
> kinds.
> 
> 
> I have a similar piece of code that works:
> 
> 
> data Foo a = Foo a 
> 
> 
> class Testable a where
>   isPos :: a -> Bool
> 
> instance (Ord b, Num b) => Testable (Foo b) where
>   isPos (Foo b) = b > 0
> 
b > 0 has type Bool, no matter what type of number b is. so this is ok. 

> instance Testable Float where
>   isPos a = a > 0
> 
same here
> 
> 
> 
> One obvious difference is that the type of isPos is a -> Bool, with a
> defined type as the return.  I'd rather not commit to a specific
> Floating type up front (I'd prefer sometimes Float sometimes Double,
> depending on the 'a' in Foo a, but trying to declare it as Float
> doesn't help me.  This fails:
> 
> 
> data Foo a = Foo a 
> 
> class TwoPi a where
>   div2pi :: a -> Float
> 
> instance (Floating b) => TwoPi (Foo b) where
>   div2pi (Foo b) = b / (2*pi)
> 
b/(2*pi) has type Floating b => b, not Float. You would need a function
of type Floating b => b -> Float.

> instance TwoPi Float where
>   div2pi a = a / (2*pi)
> 
This is ok

> 
> What is the difference between these last two cases ("a -> Bool" and
> "a -> Float"),

The difference is not between these type, but between (>), and (/).
(>) returns Bool, no matter the type of its arguments. (/) returns sth
of the same type as its arguments.

>  and is there anyway to make "a -> b" work? 
> 
The closest is probably using a function like:
realToFrac::(Real a, Fractional b) => a -> b
> 
then you can write sth like

data Foo a = Foo a 

class TwoPi a where
   div2pi :: (Floating b) => a -> b
  
instance (Real a, Floating a) => TwoPi (Foo a) where
    div2pi (Foo a) = a / (2*pi)


        Jürgen




------------------------------

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 26, Issue 52
*****************************************

Reply via email to