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
        [EMAIL PROTECTED]

You can reach the person managing the list at
        [EMAIL PROTECTED]

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


Today's Topics:

   1. Re:  Control.Monad.State: State CTOR unneeded     to create a
      State? (Brent Yorgey)
   2.  Weighted average (Michael Snoyman)
   3. Re:  Weighted average (Daniel Fischer)
   4. Re:  Weighted average (Michael Snoyman)
   5. Re:  Weighted average (Daniel Fischer)
   6. Re:  Weighted average (Michael Snoyman)
   7.  Re: Weighted average (apfelmus)
   8.  Tab complement (gerry xiao)


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

Message: 1
Date: Sat, 1 Nov 2008 15:43:55 -0400
From: Brent Yorgey <[EMAIL PROTECTED]>
Subject: Re: [Haskell-beginners] Control.Monad.State: State CTOR
        unneeded        to create a State?
To: beginners@haskell.org
Message-ID: <[EMAIL PROTECTED]>
Content-Type: text/plain; charset=us-ascii

On Sat, Nov 01, 2008 at 11:23:38AM -0500, Larry Evans wrote:
>
>  put (n+1)
> AFAICT, with the preceding |n <- get|, this means:
>
>  put (get+1)
> and since the get has type, |State Int Int|, and there's
> not + operator defined on that type (because the following:
>

Others have explained in more detail, let me just state this simply to
hopefully clear up the main point of confusion:

  let x = y

    and

  x <- y

are *not* the same.  In the first case, x is just a name for y, and x
and y can be used interchangeably.  In the second case, x is bound to
*the result of* the action y.  So x and y cannot be used
interchangeably.

-Brent


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

Message: 2
Date: Mon, 3 Nov 2008 13:41:26 -0800
From: "Michael Snoyman" <[EMAIL PROTECTED]>
Subject: [Haskell-beginners] Weighted average
To: beginners@haskell.org
Message-ID:
        <[EMAIL PROTECTED]>
Content-Type: text/plain; charset="utf-8"

Hi everyone,

I'm trying to set up some type safe functions for doing weighted averages
and sum of products. The example I give below is to try and calculate the
average miles per gallon for a collections of vehicles. Unfortunately, I am
unable to get my weightedAverage function to work, seemingly due to an
ambiguity for which instance to use. I think that the issue is that my
"class Multiplicable" should only have two parameters, as opposed to the
three it currently has. However, I can't figure out how to get that to work.

Any help is greatly appreciated. Thank you,
Michael

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

{-# LANGUAGE MultiParamTypeClasses #-}

import Prelude hiding (sum, product)

class Addable a where
    add :: a -> a -> a
    zero :: a

    sum :: [a] -> a
    sum = foldr add zero

class Multiplicable a b c where
    mult :: a -> b -> c

    product :: [a] -> [b] -> [c]
    product x y = map (\(x1, y1) -> x1 `mult` y1) $ zip x y

sumProduct :: (Addable c, Multiplicable a b c) => [a] -> [b] -> c
sumProduct x y = sum $ product x y

weightedAverage x y = (sumProduct y x) `divide` (sum y)

class Dividable a b c where
    divide :: c -> a -> b

newtype MilesPerGallon = MilesPerGallon Double deriving Show
newtype Gallon = Gallon Double deriving Show
newtype Mile = Mile Double deriving Show

instance Addable Gallon where
    add (Gallon x) (Gallon y) = Gallon $ x + y
    zero = Gallon 0

instance Addable Mile where
    add (Mile x) (Mile y) = Mile $ x + y
    zero = Mile 0

instance Multiplicable Gallon MilesPerGallon Mile where
    mult (Gallon x) (MilesPerGallon y) = Mile $ x * y

instance Dividable Gallon MilesPerGallon Mile where
    divide (Mile x) (Gallon y) = MilesPerGallon $ x / y

milesPerGallon :: [MilesPerGallon]
milesPerGallon = map MilesPerGallon [35, 25, 29, 20, 52]

gallons :: [Gallon]
gallons = map Gallon [500, 190, 240, 100, 600]

totalGallons :: Gallon
totalGallons = sum gallons

totalMiles :: Mile
totalMiles = sumProduct gallons milesPerGallon

totalMilesPerGallon :: MilesPerGallon
totalMilesPerGallon = totalMiles `divide` totalGallons
-- I would like some way to get the following line to replace the previous
--totalMilesPerGallon = weightedAverage milesPerGallon gallons

main = do
    putStrLn $ "Total gallons of gas used: " ++ show totalGallons
    putStrLn $ "Total miles traveled: " ++ show totalMiles
    putStrLn $ "Average miles per gallon: " ++ show totalMilesPerGallon
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20081103/9bf23093/attachment-0001.htm

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

Message: 3
Date: Mon, 3 Nov 2008 23:55:37 +0100
From: Daniel Fischer <[EMAIL PROTECTED]>
Subject: Re: [Haskell-beginners] Weighted average
To: "Michael Snoyman" <[EMAIL PROTECTED]>, beginners@haskell.org
Message-ID: <[EMAIL PROTECTED]>
Content-Type: text/plain;  charset="utf-8"

Am Montag, 3. November 2008 22:41 schrieb Michael Snoyman:
> Hi everyone,
>
> I'm trying to set up some type safe functions for doing weighted averages
> and sum of products. The example I give below is to try and calculate the
> average miles per gallon for a collections of vehicles. Unfortunately, I am
> unable to get my weightedAverage function to work, seemingly due to an
> ambiguity for which instance to use. I think that the issue is that my
> "class Multiplicable" should only have two parameters, as opposed to the
> three it currently has. However, I can't figure out how to get that to
> work.
>
> Any help is greatly appreciated. Thank you,
> Michael
>
> ----------------------------------
>
> {-# LANGUAGE MultiParamTypeClasses #-}
>
> import Prelude hiding (sum, product)
>
> class Addable a where
>     add :: a -> a -> a
>     zero :: a
>
>     sum :: [a] -> a
>     sum = foldr add zero
>
> class Multiplicable a b c where
>     mult :: a -> b -> c

Use functional dependencies {-# LANGUAGE FunctionalDependencies #-},

class Multiplicable a b c | a b -> c where ...

which states that the result type of multiplication is determined by the 
argument types

or type families

>
>     product :: [a] -> [b] -> [c]
>     product x y = map (\(x1, y1) -> x1 `mult` y1) $ zip x y

product = zipWith mult

>
> sumProduct :: (Addable c, Multiplicable a b c) => [a] -> [b] -> c
> sumProduct x y = sum $ product x y
>
> weightedAverage x y = (sumProduct y x) `divide` (sum y)
>
> class Dividable a b c where
>     divide :: c -> a -> b

FunDep here, too, but which one?

>
> newtype MilesPerGallon = MilesPerGallon Double deriving Show
> newtype Gallon = Gallon Double deriving Show
> newtype Mile = Mile Double deriving Show
>
> instance Addable Gallon where
>     add (Gallon x) (Gallon y) = Gallon $ x + y
>     zero = Gallon 0
>
> instance Addable Mile where
>     add (Mile x) (Mile y) = Mile $ x + y
>     zero = Mile 0
>
> instance Multiplicable Gallon MilesPerGallon Mile where
>     mult (Gallon x) (MilesPerGallon y) = Mile $ x * y
>
> instance Dividable Gallon MilesPerGallon Mile where
>     divide (Mile x) (Gallon y) = MilesPerGallon $ x / y
>
> milesPerGallon :: [MilesPerGallon]
> milesPerGallon = map MilesPerGallon [35, 25, 29, 20, 52]
>
> gallons :: [Gallon]
> gallons = map Gallon [500, 190, 240, 100, 600]
>
> totalGallons :: Gallon
> totalGallons = sum gallons
>
> totalMiles :: Mile
> totalMiles = sumProduct gallons milesPerGallon
>
> totalMilesPerGallon :: MilesPerGallon
> totalMilesPerGallon = totalMiles `divide` totalGallons
> -- I would like some way to get the following line to replace the previous
> --totalMilesPerGallon = weightedAverage milesPerGallon gallons
>
> main = do
>     putStrLn $ "Total gallons of gas used: " ++ show totalGallons
>     putStrLn $ "Total miles traveled: " ++ show totalMiles
>     putStrLn $ "Average miles per gallon: " ++ show totalMilesPerGallon



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

Message: 4
Date: Mon, 3 Nov 2008 15:26:12 -0800
From: "Michael Snoyman" <[EMAIL PROTECTED]>
Subject: Re: [Haskell-beginners] Weighted average
To: "Daniel Fischer" <[EMAIL PROTECTED]>
Cc: beginners@haskell.org
Message-ID:
        <[EMAIL PROTECTED]>
Content-Type: text/plain; charset="utf-8"

On Mon, Nov 3, 2008 at 2:55 PM, Daniel Fischer <[EMAIL PROTECTED]>wrote:

>
>
> > class Multiplicable a b c where
> >     mult :: a -> b -> c
>
> Use functional dependencies {-# LANGUAGE FunctionalDependencies #-},
>
> class Multiplicable a b c | a b -> c where ...
>
> which states that the result type of multiplication is determined by the
> argument types
>
> or type families


That's exactly what I was looking for, thank you. Now that I got that
working, I've noticed that it can be tedious making sure the arguments to
sumProduct are in the correct order. Since multiplication is commutative, is
there any way of automatically having the Multiplicable instances generate a
"flip" mult?

> sumProduct :: (Addable c, Multiplicable a b c) => [a] -> [b] -> c
> > sumProduct x y = sum $ product x y
> >
> > weightedAverage x y = (sumProduct y x) `divide` (sum y)
> >
> > class Dividable a b c where
> >     divide :: c -> a -> b
>
> FunDep here, too, but which one?


I did class Dividable a b c | c a -> b where...

Michael
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20081103/5f554cea/attachment-0001.htm

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

Message: 5
Date: Tue, 4 Nov 2008 00:53:05 +0100
From: Daniel Fischer <[EMAIL PROTECTED]>
Subject: Re: [Haskell-beginners] Weighted average
To: "Michael Snoyman" <[EMAIL PROTECTED]>
Cc: beginners@haskell.org
Message-ID: <[EMAIL PROTECTED]>
Content-Type: text/plain;  charset="utf-8"

Am Dienstag, 4. November 2008 00:26 schrieb Michael Snoyman:
> On Mon, Nov 3, 2008 at 2:55 PM, Daniel Fischer 
<[EMAIL PROTECTED]>wrote:
> > > class Multiplicable a b c where
> > >     mult :: a -> b -> c
> >
> > Use functional dependencies {-# LANGUAGE FunctionalDependencies #-},
> >
> > class Multiplicable a b c | a b -> c where ...
> >
> > which states that the result type of multiplication is determined by the
> > argument types
> >
> > or type families
>
> That's exactly what I was looking for, thank you. Now that I got that
> working, I've noticed that it can be tedious making sure the arguments to
> sumProduct are in the correct order. Since multiplication is commutative,
> is there any way of automatically having the Multiplicable instances
> generate a "flip" mult?

Beware! Multiplication is usually not commutative, think about matrices. If 
(a `mult` b) and (b `mult` a) are both defined (need not be if they have 
different types), the products may have different types, so in general it is 
not desirable to have both defined automatically in a way that doesn't force 
you to supply the arguments in the correct order.

In your case, you could provide
instance Multiplicable MilesPerGallon Gallon Mile where
        mult = flip mult
-- or write the implementation out
and it should work whichever order the arguments are passed.

>
> > sumProduct :: (Addable c, Multiplicable a b c) => [a] -> [b] -> c
> >
> > > sumProduct x y = sum $ product x y
> > >
> > > weightedAverage x y = (sumProduct y x) `divide` (sum y)
> > >
> > > class Dividable a b c where
> > >     divide :: c -> a -> b
> >
> > FunDep here, too, but which one?
>
> I did class Dividable a b c | c a -> b where...
>
> Michael



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

Message: 6
Date: Tue, 4 Nov 2008 07:22:11 -0800
From: "Michael Snoyman" <[EMAIL PROTECTED]>
Subject: Re: [Haskell-beginners] Weighted average
To: "Daniel Fischer" <[EMAIL PROTECTED]>
Cc: beginners@haskell.org
Message-ID:
        <[EMAIL PROTECTED]>
Content-Type: text/plain; charset="utf-8"

On Mon, Nov 3, 2008 at 3:53 PM, Daniel Fischer <[EMAIL PROTECTED]>wrote:

> Am Dienstag, 4. November 2008 00:26 schrieb Michael Snoyman:
>
> Beware! Multiplication is usually not commutative, think about matrices. If
> (a `mult` b) and (b `mult` a) are both defined (need not be if they have
> different types), the products may have different types, so in general it
> is
> not desirable to have both defined automatically in a way that doesn't
> force
> you to supply the arguments in the correct order.
>
> In your case, you could provide
> instance Multiplicable MilesPerGallon Gallon Mile where
>        mult = flip mult
> -- or write the implementation out
> and it should work whichever order the arguments are passed.


Good point. Thanks for all the help!
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20081104/994dd9eb/attachment-0001.htm

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

Message: 7
Date: Tue, 04 Nov 2008 16:42:05 +0100
From: apfelmus <[EMAIL PROTECTED]>
Subject: [Haskell-beginners] Re: Weighted average
To: beginners@haskell.org
Message-ID: <[EMAIL PROTECTED]>
Content-Type: text/plain; charset=UTF-8

Michael Snoyman wrote:
> 
> newtype MilesPerGallon = MilesPerGallon Double deriving Show
> newtype Gallon = Gallon Double deriving Show
> newtype Mile = Mile Double deriving Show
> 

You may want to have a look at Björn Buckwalter's  dimensional  library

  http://hackage.haskell.org/cgi-bin/hackage-scripts/package/dimensional


Regards,
apfelmus



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

Message: 8
Date: Thu, 6 Nov 2008 18:38:55 +0800
From: "gerry xiao" <[EMAIL PROTECTED]>
Subject: [Haskell-beginners] Tab complement
To: beginners@haskell.org
Message-ID:
        <[EMAIL PROTECTED]>
Content-Type: text/plain; charset="iso-8859-1"

Hello,i'm gerry,new to haskell

Why i can't do tab complement in GHCI?



Best Regards



gerry
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20081106/e8241551/attachment.htm

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

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


End of Beginners Digest, Vol 5, Issue 2
***************************************

Reply via email to