Factory methods in Haskell

Hello, I was reading about the "Factory Method Pattern" on wikipedia, and noticed that the very first example was written in Haskell. Sweet! http://en.wikipedia.org/wiki/Factory_method_pattern#Haskell Unfortunately, it looks to me like it is missing the 'factory' part. I have attempted to implement something more factory like (see attached). I am wonder what other people think. Is the code on wikipedia really demoing a factory method? Is the code attached any better? Is there an even better what to write this in Haskell? Thanks! - j {-# LANGUAGE ExistentialQuantification #-} import Numeric (showFFloat) -- * A type which can hold different types of pizzas data Pizza = forall a. (PizzaMethods a) => Pizza a -- * A type class with functions common to different types of pizza class (Show a) => PizzaMethods a where price' :: a -> Double -- * Getter functions for the pizza type price :: Pizza -> Double price (Pizza p) = price' p pizzaType :: Pizza -> String pizzaType (Pizza p) = show p -- * Some types of pizza data HamAndMushroom = HamAndMushroom deriving (Read, Show) data Deluxe = Deluxe deriving (Read, Show) data Hawaiin = Hawaiin deriving (Read, Show) -- * Prices of various pizzas instance PizzaMethods HamAndMushroom where price' _ = 8.50 instance PizzaMethods Deluxe where price' _ = 10.50 instance PizzaMethods Hawaiin where price' _ = 11.50 -- * A pizza factory pizzaFactory :: String -> Pizza pizzaFactory pizzaType | pizzaType == "HamAndMushroom" = Pizza HamAndMushroom | pizzaType == "Deluxe" = Pizza Deluxe | pizzaType == "Hawaiin" = Pizza Hawaiin | otherwise = error "We don't serve your kind here." -- * An order at the pizza factory main = let pizza = pizzaFactory "HamAndMushroom" in putStrLn $ "You can get a " ++ pizzaType pizza ++ " for $" ++ showFFloat (Just 2) (price pizza) "."

On Sat, 2009-01-24 at 15:43 -0600, Jeremy Shaw wrote:
Hello,
I was reading about the "Factory Method Pattern" on wikipedia, and noticed that the very first example was written in Haskell. Sweet!
http://en.wikipedia.org/wiki/Factory_method_pattern#Haskell
Unfortunately, it looks to me like it is missing the 'factory' part.
It is.
I have attempted to implement something more factory like (see attached). I am wonder what other people think. Is the code on wikipedia really demoing a factory method? Is the code attached any better? Is there an even better what to write this in Haskell?
Answering your questions in order: no, yes, yes but the essence is right (there are other ways as well) However since dynamic dispatch is rare in Haskell, the factory method does not really come up. It does occur but not in a way that most people think of as "the factory method."
plain text document attachment (Pizza.hs) {-# LANGUAGE ExistentialQuantification #-} import Numeric (showFFloat)
-- * A type which can hold different types of pizzas
data Pizza = forall a. (PizzaMethods a) => Pizza a
-- * A type class with functions common to different types of pizza
class (Show a) => PizzaMethods a where price' :: a -> Double
-- * Getter functions for the pizza type
price :: Pizza -> Double price (Pizza p) = price' p
pizzaType :: Pizza -> String pizzaType (Pizza p) = show p
Get rid of these functions and get rid of the ' in price' and simply make Pizza an instance of PizzaMethods.
-- * Some types of pizza
data HamAndMushroom = HamAndMushroom deriving (Read, Show) data Deluxe = Deluxe deriving (Read, Show) data Hawaiin = Hawaiin deriving (Read, Show)
-- * Prices of various pizzas
instance PizzaMethods HamAndMushroom where price' _ = 8.50
instance PizzaMethods Deluxe where price' _ = 10.50
instance PizzaMethods Hawaiin where price' _ = 11.50
-- * A pizza factory
pizzaFactory :: String -> Pizza pizzaFactory pizzaType | pizzaType == "HamAndMushroom" = Pizza HamAndMushroom | pizzaType == "Deluxe" = Pizza Deluxe | pizzaType == "Hawaiin" = Pizza Hawaiin | otherwise = error "We don't serve your kind here."
-- * An order at the pizza factory
main = let pizza = pizzaFactory "HamAndMushroom" in putStrLn $ "You can get a " ++ pizzaType pizza ++ " for $" ++ showFFloat (Just 2) (price pizza) "." _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (2)
-
Derek Elkins
-
Jeremy Shaw