
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

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

On Mon, Nov 3, 2008 at 2:55 PM, Daniel Fischer
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

Am Dienstag, 4. November 2008 00:26 schrieb Michael Snoyman:
On Mon, Nov 3, 2008 at 2:55 PM, Daniel Fischer
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

On Mon, Nov 3, 2008 at 3:53 PM, Daniel Fischer
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!

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
participants (3)
-
apfelmus
-
Daniel Fischer
-
Michael Snoyman