
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