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:  typeclass confusion (Isaac Dupree)
   2. Re:  typeclass confusion (Brandon S Allbery KF8NH)
   3. Re:  typeclass confusion (John Obbele)
   4.  type variables (Thomas)
   5. Re:  type variables (Daniel Fischer)
   6. Re:  type variables (Daniel Fischer)
   7. Re:  type variables (Brent Yorgey)


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

Message: 1
Date: Tue, 24 Aug 2010 01:53:00 -0400
From: Isaac Dupree <m...@isaac.cedarswampstudios.org>
Subject: Re: [Haskell-beginners] typeclass confusion
To: beginners@haskell.org
Message-ID: <4c735e3c.30...@isaac.cedarswampstudios.org>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

On 08/24/10 01:38, Greg Best wrote:
> My reservations were with needing to define sin for each angle type (which I 
> now think my method would force me to do anyway)

Yeah, the two methods are about equal in how much substantive code you 
have to write. -- each allows a certain amount of code-sharing (you can 
figure out how, with practice!), yet there's no "free lunch" (the code 
doesn't *all* write itself, and it shouldn't).


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

Message: 2
Date: Tue, 24 Aug 2010 01:56:52 -0400
From: Brandon S Allbery KF8NH <allb...@ece.cmu.edu>
Subject: Re: [Haskell-beginners] typeclass confusion
To: Greg Best <gregli...@me.com>
Cc: beginners@haskell.org
Message-ID: <4c735f24.5020...@ece.cmu.edu>
Content-Type: text/plain; charset=UTF-8

-----BEGIN PGP SIGNED MESSAGE-----
Hash: SHA1

On 8/24/10 01:38 , Greg Best wrote:
> The part I figured was impractical was the "Angular" class, but this is the 
> second feedback that suggested making both Degrees and Radians type 
> constructors rather than alternate value constructors.  Is that the right 
> approach?  I know the trig functions are already available and they all just 
> traffic in floats, but if this weren't the case, I'd imagine a structure 
> along the lines of

The point of typeclasses is to allow you to abstract operations over
multiple types.  If you have only one type...

> data Angle a = Radians a
>             | Degrees a
>             deriving (Eq, Show)

then a typeclass is just unnecessary complexity.  It's when you have
multiple types which share a group of operations that typeclasses become
useful.  So, for example, with the above type (sin) can be implemented as a
single function which pattern matches on the constructor; but if (Radians)
and (Degrees) need to be separate types instead of value constructors for a
single type, then you *must* use a typeclass to implement a single (sin)
instead of (sinRadians) or (sinDegrees).

- -- 
brandon s. allbery     [linux,solaris,freebsd,perl]      allb...@kf8nh.com
system administrator  [openafs,heimdal,too many hats]  allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university      KF8NH
-----BEGIN PGP SIGNATURE-----
Version: GnuPG v2.0.10 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkxzXyMACgkQIn7hlCsL25UfdgCgnx492P1aLyttxTsTQKBycSlf
KvQAnA/FkXYgPpJP37aF2hoJCMWUct+I
=aldW
-----END PGP SIGNATURE-----


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

Message: 3
Date: Tue, 24 Aug 2010 12:16:39 +0200
From: John Obbele <john.obb...@gmail.com>
Subject: Re: [Haskell-beginners] typeclass confusion
To: beginners@haskell.org
Message-ID: <20100824101638.ga3...@megabook.localdomain>
Content-Type: text/plain; charset=utf-8

On Tue, Aug 24, 2010 at 05:06:05AM +0200, Tobias Brandt wrote:
>    You don't need a type class, you can just define your functions with
>    pattern matching:
>    rad :: Angle a -> a
>    rad (Radians x) = x
>    rad (Degrees x) =*pi * (deg x) / 180
>    deg :: Angle a -> a
>    deg (Radians x) =*180 * (rad x) / pi
>    deg (Degrees x) = x

I may look like a nitpicker but the above function definitions
lose their type information. I'd have written it this way:

    data Angle a = Radians a | Degrees a deriving (Eq, Show)

    rad :: Floating a => Angle a -> Angle a
    rad (Radians x) = Radians x
    rad (Degrees x) = Radians (pi * x / 180)

    deg :: Floating a => Angle a -> Angle a
    deg (Radians x) = Degrees (180 * x / pi)
    deg (Degrees x) = Degrees x

On the other side, I am not particularly confident this approach
is the best. Other people may give you better solutions …

/‡ John


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

Message: 4
Date: Tue, 24 Aug 2010 13:09:56 +0200
From: Thomas <hask...@phirho.com>
Subject: [Haskell-beginners] type variables
To: beginners@haskell.org
Message-ID: <4c73a884.8080...@phirho.com>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Hello!

I have a question about type variables.
The following works:

type XMLCallback a = (XMLTreeNode -> a -> [Int] -> [XMLTreeNode] -> a)

xmlTreeFold :: XMLCallback a -> a -> Maybe XMLTreeNode -> Maybe a
xmlTreeFold _ _ Nothing = Nothing
xmlTreeFold func acc (Just tree) =
   Just (xmlTreeWalkerWithContext func acc tree [] [])

testFold :: XMLCallback [(XMLTreeNode, [Int], [XMLTreeNode])]
testFold node a is ns =
        if (length is) > 1 then ((node, is, ns):a) else a

=> xmlTreeFold testFold [] tree

But if I change the type declaration of 'testFold' to:
testFold :: XMLCallback a
it will not compile.

I thought that 'a' is a type /variable/ thus able to hold any type, for 
example, but not limited to '[(XMLTreeNode, [Int], [XMLTreeNode])]'. Why 
do I need to be that much more specific in the declaration for 'testFold'?
Especially since in the declaration of 'xmlTreeFold' the 'XMLCallback a' 
is well received.

Thanks for any insights,
Thomas






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

Message: 5
Date: Tue, 24 Aug 2010 13:45:10 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] type variables
To: beginners@haskell.org
Message-ID: <201008241345.10355.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-1"

On Tuesday 24 August 2010 13:09:56, Thomas wrote:
> Hello!
>
> I have a question about type variables.
> The following works:
>
> type XMLCallback a = (XMLTreeNode -> a -> [Int] -> [XMLTreeNode] -> a)
>
> xmlTreeFold :: XMLCallback a -> a -> Maybe XMLTreeNode -> Maybe a
> xmlTreeFold _ _ Nothing = Nothing
> xmlTreeFold func acc (Just tree) =
>    Just (xmlTreeWalkerWithContext func acc tree [] [])
>
> testFold :: XMLCallback [(XMLTreeNode, [Int], [XMLTreeNode])]
> testFold node a is ns =
>       if (length is) > 1 then ((node, is, ns):a) else a

Do not use `if length list > 1', if the list is long, that takes long too.
Use `if not (null $ drop 1 list)'.

>
> => xmlTreeFold testFold [] tree
>
> But if I change the type declaration of 'testFold' to:
> testFold :: XMLCallback a
> it will not compile.
>
> I thought that 'a' is a type /variable/ thus able to hold any type, for
> example, but not limited to '[(XMLTreeNode, [Int], [XMLTreeNode])]'.

Right. However, the definition of testFold says a can't be *any* type.
In the then-branch, the result is
(node, is, ns) : a,
which is a list, and forces a to be a list too, so the type of testFold 
cannot be more general than

XMLCallback [a]

(and that should compile).

> Why do I need to be that much more specific in the declaration for
> 'testFold'? Especially since in the declaration of 'xmlTreeFold' the
> 'XMLCallback a' is well received.

In the definition of xmlTreeFold, nothing restricts the type of the 
accumulator argument, so it can be anything.

>
> Thanks for any insights,
> Thomas



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

Message: 6
Date: Tue, 24 Aug 2010 14:03:56 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] type variables
To: beginners@haskell.org
Message-ID: <201008241403.56479.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-1"

On Tuesday 24 August 2010 13:45:10, Daniel Fischer wrote:
> On Tuesday 24 August 2010 13:09:56, Thomas wrote:
> > Hello!
> >
> > I have a question about type variables.
> > The following works:
> >
> > type XMLCallback a = (XMLTreeNode -> a -> [Int] -> [XMLTreeNode] -> a)
> >
> > xmlTreeFold :: XMLCallback a -> a -> Maybe XMLTreeNode -> Maybe a
> > xmlTreeFold _ _ Nothing = Nothing
> > xmlTreeFold func acc (Just tree) =
> >    Just (xmlTreeWalkerWithContext func acc tree [] [])
> >
> > testFold :: XMLCallback [(XMLTreeNode, [Int], [XMLTreeNode])]
> > testFold node a is ns =
> >     if (length is) > 1 then ((node, is, ns):a) else a
>
> Do not use `if length list > 1', if the list is long, that takes long
> too. Use `if not (null $ drop 1 list)'.
>
> > => xmlTreeFold testFold [] tree
> >
> > But if I change the type declaration of 'testFold' to:
> > testFold :: XMLCallback a
> > it will not compile.
> >
> > I thought that 'a' is a type /variable/ thus able to hold any type,
> > for example, but not limited to '[(XMLTreeNode, [Int],
> > [XMLTreeNode])]'.
>
> Right. However, the definition of testFold says a can't be *any* type.
> In the then-branch, the result is
> (node, is, ns) : a,
> which is a list, and forces a to be a list too, so the type of testFold
> cannot be more general than
>
> XMLCallback [a]
>
> (and that should compile).

Arrgh. Remember not to post before the third cup of tea.
Firstly, the fact that (node, is, ns) is consed to the front of a, forces 
the list type to be [(x,y,z)] for some x, y, z, with

node :: x
is :: y
ns :: z

Then use of length (or some other list function) forces y = [u].

So the type of testFold has to be

testFold :: x -> [(x,[u],z)] -> [u] -> z -> [(x,[u],z)]

If it is to be XMLCallback var, that has to be

testFold :: XMLTreeNode -> var -> [Int] -> [XMLTreeNode] -> var

So,

x = XMLTreeNode
[u] = [Int]
z = [XMLTreeNode]

var = [(x,[u],z)] = [(XMLTreeNode,[Int],[XMLTreeNode])]

>
> > Why do I need to be that much more specific in the declaration for
> > 'testFold'? Especially since in the declaration of 'xmlTreeFold' the
> > 'XMLCallback a' is well received.
>
> In the definition of xmlTreeFold, nothing restricts the type of the
> accumulator argument, so it can be anything.
>
> > Thanks for any insights,
> > Thomas


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

Message: 7
Date: Tue, 24 Aug 2010 13:47:25 +0100
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] type variables
To: beginners@haskell.org
Message-ID: <20100824124725.ga12...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

On Tue, Aug 24, 2010 at 01:09:56PM +0200, Thomas wrote:
> 
> But if I change the type declaration of 'testFold' to:
> testFold :: XMLCallback a
> it will not compile.
> 
> I thought that 'a' is a type /variable/ thus able to hold any type,
> for example, but not limited to '[(XMLTreeNode, [Int],
> [XMLTreeNode])]'. Why do I need to be that much more specific in the
> declaration for 'testFold'?

Daniel has already given a more detailed answer, but just to emphasize
the main point a bit more:

  testFold :: XMLCallback a

means that testFold *should work no matter what a is*.  But as Daniel
has explained, this is not the case; testFold only works for certain
specific types in place of a.  Type variables are not a shortcut used
when one can't be bothered to give the type in more detail; rather,
they are strong assertions that *any type will work*.

-Brent


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

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


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

Reply via email to