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: Type Class Woes .. (Tim Attwood)
   2. Re:  Type Class Woes .. (Patrick LeBoutillier)
   3. Re:  Type Class Woes .. (Daniel Fischer)
   4. Re:  Type Class Woes .. (Chadda? Fouch?)
   5. Re:  Re: Type Class Woes .. (Tom Poliquin)
   6.  Utter Newbie - simple problems,  output - GHC vs GHCi
      (Nigel Rantor)
   7. Re:  Utter Newbie - simple problems, output - GHC         vs GHCi
      (Magnus Therning)


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

Message: 1
Date: Sun, 30 Aug 2009 03:57:47 -0700
From: "Tim Attwood" <timoth...@comcast.net>
Subject: [Haskell-beginners] Re: Type Class Woes ..
To: beginners@haskell.org
Message-ID: <h7dlve$fi...@ger.gmane.org>
Content-Type: text/plain; format=flowed; charset="iso-8859-1";
        reply-type=original

Orange, Apple etc are values of type FruitType, not types themselves.

module Main where

data FruitType = Orange | Apple | Banana | Watermelon deriving (Eq, Show)
data Fruit = Fruit {fruitRadius::Double, fruitLength::Double, 
fType::FruitType}

data VegType = Tomato | StringBean deriving (Eq, Show)
data Veg = Veg {vegRadius::Double, vegLength::Double, vType::VegType}

data GeoType = Sphere | Elipsoid deriving (Eq, Show)
data Geometric = Geo {radius1::Double, radius2::Double, radius3::Double, 
gType::GeoType}

class ObjectCalc a where
   volume :: a -> Double
   surfaceArea :: a -> Double

instance ObjectCalc Geometric where
   volume g | gType g == Sphere   = (4.0/3.0) * pi * ( (radius1 g) ** 3.0)
            | gType g == Elipsoid = (4.0/3.0) * pi * (radius1 g) * (radius2 
g) * (radius3 g)
            | otherwise = undefined
   surfaceArea g = undefined

instance ObjectCalc Fruit where
   volume f | fType f == Orange     = volume (Geo (fruitRadius f) undefined 
undefined Sphere)
            | fType f == Apple      = volume (Geo (fruitRadius f) undefined 
undefined Sphere)
            | fType f == Banana     = volume (Geo (fruitRadius f) 
(fruitRadius f) (fruitLength f) Elipsoid)
            | fType f == Watermelon = volume (Geo ((fruitRadius f)*2.0) 
((fruitLength f)*0.5) (fruitLength f) Elipsoid)
            | otherwise             = undefined
   surfaceArea f = undefined

instance ObjectCalc Veg where
   volume v = undefined
   surfaceArea v = undefined

initFruit :: [Fruit]
initFruit = [
              (Fruit  3.0  0.0 Orange),
              (Fruit  3.0  0.0 Apple),
              (Fruit  3.0  2.0 Banana),
              (Fruit 40.0 20.0 Watermelon)
            ]

main =
   let f = initFruit
       v = map volume f
       ft = map fType f
       s = zipWith (\a b -> putStrLn ("Volume -> " ++ (show a) ++ " = " ++ 
(show b))) ft v
   in sequence_ s 




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

Message: 2
Date: Sun, 30 Aug 2009 08:32:56 -0400
From: Patrick LeBoutillier <patrick.leboutill...@gmail.com>
Subject: Re: [Haskell-beginners] Type Class Woes ..
To: beginners <beginners@haskell.org>
Message-ID:
        <b217a64f0908300532y5b40f1as883963ce8e121...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Hi,

volume :: Fruit FruitType -> Double
> volume F{radius=r,len=l,fType=Orange} = (4.0/3.0) * pi * r * r * r
>

> volume F{radius=r,len=l,fType=Apple}  = (4.0/3.0) * pi * r * r * r
> volume F{radius=r,len=l,fType=Banana} = pi * (r * r) * l
> volume F{radius=r,len=l,fType=Watermelon} = (4.0/3.0) * pi * (2.0 * r)
>                                                         * l * (0.5 * l)


Can anyone explain the above pattern matching syntax? I've never seen it
before...


Thanks,

Patrick


-- 
=====================
Patrick LeBoutillier
Rosemère, Québec, Canada
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20090830/a967a563/attachment-0001.html

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

Message: 3
Date: Sun, 30 Aug 2009 15:06:02 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] Type Class Woes ..
To: beginners@haskell.org
Message-ID: <200908301506.02234.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-15"

Am Sonntag 30 August 2009 14:32:56 schrieb Patrick LeBoutillier:
> Hi,
>
> volume :: Fruit FruitType -> Double
>
> > volume F{radius=r,len=l,fType=Orange} = (4.0/3.0) * pi * r * r * r
> >
> >
> > volume F{radius=r,len=l,fType=Apple}  = (4.0/3.0) * pi * r * r * r
> > volume F{radius=r,len=l,fType=Banana} = pi * (r * r) * l
> > volume F{radius=r,len=l,fType=Watermelon} = (4.0/3.0) * pi * (2.0 * r)
> >                                                         * l * (0.5 * l)
>
> Can anyone explain the above pattern matching syntax? I've never seen it
> before...
>
>
> Thanks,
>
> Patrick

It's named-field syntax, cf.

http://haskell.org/onlinereport/exps.html#sect3.15

If you have a type with named fields, like

data FType
    = Con1 { field1 :: Int, field2 :: Bool }
    | Con2 { field1 :: Int, field3 :: Char }

you can pattern-match either by position:

fun (Con1 i b) = ...

or by named field syntax:

fun Con1{field2=True, field1=x} = ... -- corresponds to fun (Con1 x True)
fun Con2{field3='a'} = ... -- fun (Con2 _ 'a')

It's very convenient if you need only a few arguments of a multi-argument 
constructor:

fun C{fieldx=y}

vs.

fun (C _ _ _ _ _ y _ _ _ _)


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

Message: 4
Date: Sun, 30 Aug 2009 15:10:28 +0200
From: Chadda? Fouch? <chaddai.fou...@gmail.com>
Subject: Re: [Haskell-beginners] Type Class Woes ..
To: Patrick LeBoutillier <patrick.leboutill...@gmail.com>
Cc: beginners <beginners@haskell.org>
Message-ID:
        <e9350eaf0908300610g320d56c3g5025913cc89bc...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Sun, Aug 30, 2009 at 2:32 PM, Patrick
LeBoutillier<patrick.leboutill...@gmail.com> wrote:
>> volume :: Fruit FruitType -> Double
>> volume F{radius=r,len=l,fType=Orange} = (4.0/3.0) * pi * r * r * r
>>
>> volume F{radius=r,len=l,fType=Apple}  = (4.0/3.0) * pi * r * r * r
>> volume F{radius=r,len=l,fType=Banana} = pi * (r * r) * l
>> volume F{radius=r,len=l,fType=Watermelon} = (4.0/3.0) * pi * (2.0 * r)
>>                                                   
>>       * l * (0.5 * l)
>
> Can anyone explain the above pattern matching syntax? I've never seen it
> before...

It's part of what record syntax allows : record pattern.

record_pattern = data_constructor '{' (field_pattern ',')* '}'
field_pattern = field_name '=' pattern

You don't have to use all the fields of the datatype in a pattern if
you don't need them all. A special case is when you put zero
field_pattern in the {}, in this case you can even use this syntax for
regular datatype (no record syntax), to write thing like :

> isJust Just {} = True
> isJust _ = False

(especially interesting for constructors with plenty of parameters, of course)

-----------

To come back to the initial subject, if you use datatypes and
typeclass rather than dataconstructors and pattern matching to allow
extensibility of data, you can still have a list of different fruits
type, using existential types, though that is not without minus :

> data Fruit a = F { radius, length :: Double }
> data Orange; data Banana;
>
> class Volume a where
>   vol :: a -> Double
>
> instance Volume (Fruit Orange) where
>   vol (F r _) = (4/3) * pi * r * r * r
> instance Volume (Fruit Banana) where
>   vol (F r l) = pi * (r * r) * l
>
> data Volumic = Volume a => V a
>
> fruit_list :: [Volumic]
> fruit_list = [V (F 3 undefined :: Fruit Orange), V (F 1 6 :: Fruit Banana) ]

In this particular case it is really uninteresting since you could as
well stock a list of volumes (the only thing you can do with a Volumic
is get the volume of its content) but with more versatile typeclass,
it may be different.

-- 
Jedaï


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

Message: 5
Date: Sun, 30 Aug 2009 12:14:57 -0700
From: Tom Poliquin <poliq...@softcomp.com>
Subject: Re: [Haskell-beginners] Re: Type Class Woes ..
To: beginners@haskell.org
Message-ID: <200908301214.57658.poliq...@softcomp.com>
Content-Type: text/plain;  charset="iso-8859-1"


Thanks everyone for the replies!
Comments below ..

Tom Poliquin wrote:

> I chose the (contrived toy) problem of computing the volume
> of various fruits.

> First I wrote the code using algebraic data types ..
> ...then I 'converted' it to use type classes
> The type class version gives me the errors ..

> Main.hs:12:16: Not in scope: type constructor or class `Banana'
> Main.hs:15:16: Not in scope: type constructor or class `Watermelon'


On Sunday 30 August 2009 03:57, Tim Attwood wrote:

> Orange, Apple etc are values of type FruitType, not types themselves.
>
> module Main where
>
> data FruitType = Orange | Apple | Banana | Watermelon deriving (Eq, Show)
> data Fruit = Fruit {fruitRadius::Double, fruitLength::Double,
> fType::FruitType}
>
> data VegType = Tomato | StringBean deriving (Eq, Show)
> data Veg = Veg {vegRadius::Double, vegLength::Double, vType::VegType}
>
> data GeoType = Sphere | Elipsoid deriving (Eq, Show)
> data Geometric = Geo {radius1::Double, radius2::Double, radius3::Double,
> gType::GeoType}
>
> class ObjectCalc a where
>    volume :: a -> Double
>    surfaceArea :: a -> Double
>
> instance ObjectCalc Geometric where
>    volume g | gType g == Sphere   = (4.0/3.0) * pi * ( (radius1 g) ** 3.0)
>             | gType g == Elipsoid = (4.0/3.0) * pi * (radius1 g) * (radius2
> g) * (radius3 g)
>             | otherwise = undefined
>    surfaceArea g = undefined
>
> instance ObjectCalc Fruit where
>    volume f | fType f == Orange     = volume (Geo (fruitRadius f) undefined
> undefined Sphere)
>             | fType f == Apple      = volume (Geo (fruitRadius f) undefined
> undefined Sphere)
>             | fType f == Banana     = volume (Geo (fruitRadius f)
> (fruitRadius f) (fruitLength f) Elipsoid)
>             | fType f == Watermelon = volume (Geo ((fruitRadius f)*2.0)
> ((fruitLength f)*0.5) (fruitLength f) Elipsoid)
>             | otherwise             = undefined
>    surfaceArea f = undefined
>
> instance ObjectCalc Veg where
>    volume v = undefined
>    surfaceArea v = undefined
>
> initFruit :: [Fruit]
> initFruit = [
>               (Fruit  3.0  0.0 Orange),
>               (Fruit  3.0  0.0 Apple),
>               (Fruit  3.0  2.0 Banana),
>               (Fruit 40.0 20.0 Watermelon)
>             ]
>
> main =
>    let f = initFruit
>        v = map volume f
>        ft = map fType f
>        s = zipWith (\a b -> putStrLn ("Volume -> " ++ (show a) ++ " = " ++
> (show b))) ft v
>    in sequence_ s

This looks great .. it even added an extra idea ....
that different fruit/vegs have different geometric shapes .. Abstractly
then ..

'Grown Things' each have a geometric shape, then each geometric
shape has a method for computing volume and surface area ..


Javier M Mora wrote:

> THIRD IDEA. Make a wrapper volume function:
>
> -----
> module Main where
>
> data Fruit a = F {radius::Double, len::Double, fType::a}
>
> data FruitType = Orange | Apple | Banana | Watermelon
>    deriving Show
>
> class Volume a where
>    volume:: a -> Double -> Double -> Double
>
> instance Volume FruitType where
>    volume Banana r l = pi * (r * r) * l
>    volume Watermelon r l = (4.0/3.0) * pi * (2.0 * r) * l * (0.5 * l)
>    volume _ r l = (4.0/3.0) * pi * r * r * r
>
> volumeFruit F{radius=r,len=l,fType=f} = volume f r l
>
> initFruit :: [Fruit FruitType]
> initFruit = [
>                (F  3.0  0.0 Orange),
>                (F  3.0  0.0 Apple),
>                (F  3.0  2.0 Banana),
>                (F 40.0 20.0 Watermelon)
>              ]
>
> ----------
> -- Main --
> ----------
>
> main = do
>
>     let fruit = initFruit
>
>     mapM (\f@(F{fType=t}) -> putStrLn ("Volume -> " ++ show t ++
>                                      " = " ++ show (volumeFruit f))) fruit
> -----
>
>
> So. This problem is more interesting that I thought.
>
> Javier M Mora.

This has the flavor (no pun intended) of pattern matching
since there's only one instance ..


Chaddaï Fouché  wrote:

> To come back to the initial subject, if you use datatypes and
> typeclass rather than dataconstructors and pattern matching to allow
> extensibility of data, you can still have a list of different fruits
> type, using existential types, though that is not without minus :

> data Fruit a = F { radius, length :: Double }
> data Orange; data Banana;
>
> class Volume a where
>   vol :: a -> Double
>
> instance Volume (Fruit Orange) where
>   vol (F r _) = (4/3) * pi * r * r * r
> instance Volume (Fruit Banana) where
>   vol (F r l) = pi * (r * r) * l
>
> data Volumic = Volume a => V a
>
> fruit_list :: [Volumic]
> fruit_list = [V (F 3 undefined :: Fruit Orange), V (F 1 6 :: Fruit Banana) ]

> In this particular case it is really uninteresting since you could as
> well stock a list of volumes (the only thing you can do with a Volumic
> is get the volume of its content) but with more versatile typeclass,
> it may be different.

I've never used existentials .. but this seems like a powerful idea. 
Unfortunately I couldn't get this to compile ..
It was unhappy about 'data Volumic' so I changed it to
'data Volumic a' .. it was still unhappy and took me down
the road of compiler switch options .. until I had ..
ghc -XFlexibleInstances -XExistentialQuantification -XEmptyDataDecls --make 
Main.hs
which was also unsuccessful.


Philosophical Summary ...
All the examples of type classes examples I've seen in tutorials and
books look simple, beautiful and elegant. No disrespect intended
to the coding suggestions but they seem a little more difficult than
I had expected for my toy problem ..

So I'm wondering why that is ..

- I'm stupidly trying to shoehorn my toy problem
  into a type class example which is not the best approach.

- The problem is *not* a toy problem and is really
   complicated.

- Type classes are more appropriate at the 'system' level
   than the 'application' level. Applications are better off
   using algebraic data types.

- Tom (me) has expectations that are too high.
   I do have high expectations of Haskell. I've written
   several mid sized applications (obviously without
   using type classes :-) ) and found them easy to write
   and unbelievably easy to refactor!!!

Thoughts appreciated.

Thanks again to eveyone!

Tom
   






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

Message: 6
Date: Sun, 30 Aug 2009 23:09:41 +0100
From: Nigel Rantor <wig...@wiggly.org>
Subject: [Haskell-beginners] Utter Newbie - simple problems,    output -
        GHC vs GHCi
To: beginners@haskell.org
Message-ID: <4a9af8a5.3050...@wiggly.org>
Content-Type: text/plain; charset=ISO-8859-1


I am trying to get my head around Haskell but seem to keep butting
against problems that have nothing to do with FP yet, but are simply to
do with not understanding the tools.

I've been trying a lot of code from multiple tutorials but I keep
finding that the code simply does not work out of the box, and requires
some other setup I am unaware of.

I am currently on Debian, using GHC 6.8.2 installed using apt, so I
assume that the toolchain is installed and working correctly.

For example, the most recent tutorial I've been looking at is the "yet
another haskell tutorial", here -
http://www.cs.utah.edu/~hal/docs/daume02yaht.pdf

One of the exercises after talking about functions that act on lists is
to determine the number of lowercase letters in a string.

Fine, that makes complete sense to me. I figure something along the
lines of:

length( filter( Char.isLower "LoweR" ) )

should return the value 3

If I attempt this at the interactive GHC prompt I get the following:

------------------------------------------------------------------------------------------
wig...@mink:~/src/ht$ ghci
GHCi, version 6.8.2: http://www.haskell.org/ghc/  :? for help
Loading package base ... linking ... done.
Prelude> show( length( filter( Char.isLower "LoweR" ) ) )

<interactive>:1:35:
    Couldn't match expected type `Char' against inferred type `[Char]'
    In the first argument of `GHC.Unicode.isLower', namely `"LoweR"'
    In the first argument of `filter', namely
        `(GHC.Unicode.isLower "LoweR")'
    In the first argument of `length', namely
        `(filter (GHC.Unicode.isLower "LoweR"))'
Prelude>
------------------------------------------------------------------------------------------

If I attempt to put the code into a file and compile it I get the following:

[Code]
------------------------------------------------------------------------------------------
module Main where
import Char
main = show( length( filter( Char.isLower "LoweR" ) ) )
------------------------------------------------------------------------------------------

[Terminal]
------------------------------------------------------------------------------------------
wig...@mink:~/src/ht$ ghc -o test ex3.hs

ex3.hs:3:42:
    Couldn't match expected type `Char' against inferred type `[Char]'
    In the first argument of `isLower', namely `"LoweR"'
    In the first argument of `filter', namely `(isLower "LoweR")'
    In the first argument of `length', namely
        `(filter (isLower "LoweR"))'
wig...@mink:~/src/ht$
------------------------------------------------------------------------------------------

This is one of the smallest examples I can think of posting for some
help, and quite frankly, I'm feeling a bit dim because I just cannot
understand why this doesn't work...I've tried in vain to mess with the
code (I won't attempt to describe it, I'm not au fait enough with
Haskell terminology yet, it would sound like gibberish *and* be incorrect)

Any help would be awesome, equally, any ready-to-run examples/tutorials
that people could recommend would likewise be awesome and beer-worthy[0].

Cheers,

  n

[0] offer only applies to those in the London area or those environs
where I find myself randomly


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

Message: 7
Date: Sun, 30 Aug 2009 23:13:14 +0100
From: Magnus Therning <mag...@therning.org>
Subject: Re: [Haskell-beginners] Utter Newbie - simple problems,
        output - GHC    vs GHCi
To: Nigel Rantor <wig...@wiggly.org>
Cc: beginners@haskell.org
Message-ID:
        <e040b520908301513i30343e70la7a9fd8eba228...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Sun, Aug 30, 2009 at 11:09 PM, Nigel Rantor<wig...@wiggly.org> wrote:
>
> I am trying to get my head around Haskell but seem to keep butting
> against problems that have nothing to do with FP yet, but are simply to
> do with not understanding the tools.
>
> I've been trying a lot of code from multiple tutorials but I keep
> finding that the code simply does not work out of the box, and requires
> some other setup I am unaware of.
>
> I am currently on Debian, using GHC 6.8.2 installed using apt, so I
> assume that the toolchain is installed and working correctly.
>
> For example, the most recent tutorial I've been looking at is the "yet
> another haskell tutorial", here -
> http://www.cs.utah.edu/~hal/docs/daume02yaht.pdf
>
> One of the exercises after talking about functions that act on lists is
> to determine the number of lowercase letters in a string.
>
> Fine, that makes complete sense to me. I figure something along the
> lines of:
>
> length( filter( Char.isLower "LoweR" ) )

try this instead

length (filter Char.isLower "LoweR")

`filter` takes two arguments.

/M

-- 
Magnus Therning                        (OpenPGP: 0xAB4DFBA4)
magnus@therning.org          Jabber: magnus@therning.org
http://therning.org/magnus         identi.ca|twitter: magthe


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

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


End of Beginners Digest, Vol 14, Issue 14
*****************************************

Reply via email to