how to define a user datatype consisting of instances of String?

How is it possible to define a user datatype consisting of instances of String? Suppose I am preparing a party for wine connoisseurs, and want to define the following data types: data Wine = Red | White data Red = "Merlot" data White = "Sauvignon Blanc" data Entree = "pork" | "chicken" | "tuna" data SideDish = "garlic bread" | "mozzarella sticks" | "caviar" Then, I want to write a Haskell function that takes two lists; e.g., ["pork", "chicken", "tuna"] and ["garlic bread", "mozzarella sticks", "caviar"] and that constructs a three-tuple of the following type: (Entree, SideDish, Wine) such that which Wine is chosen depends on the particular combination of Entree and SideDish, with respect to the following rules: ("pork", "garlic bread") -> ("pork", "garlic bread", "Merlot") ("pork", "mozzarella sticks") -> ("pork", "mozzarella sticks", "Merlot") ("pork", "caviar") -> ("pork", "Beluga", "Sauvignon Blanc") ("chicken", "garlic bread") -> ("chicken", "garlic bread", "Merlot") ("chicken", "mozzarella sticks") -> ("chicken", "mozzarella sticks", "Sauvignon Blanc") ("chicken", "caviar") -> ("chicken", "caviar", "Merlot") ("tuna", "garlic bread") -> ("tuna", "garlic bread", "Sauvignon Blanc") ("tuna", "mozzarella sticks") -> ("tuna", "mozzarella sticks", "Merlot") ("tuna", "caviar") -> ("tuna", "caviar", "Merlot") So far, I have written the following Haskell code: module Wine where data Wine = Red | White data Red = "Merlot" data White = "Sauvignon Blanc" data Entree = "pork" | "chicken" | "tuna" data SideDish = "garlic bread" | "mozzarella sticks" | "caviar" wine :: [Entree] -> [SideDish] -> [(Entree, SideDish, Wine)] wine entree sidedish | entree == "pork" = | sidedish == "garlic bread" = ("pork", "garlic bread", "Merlot") | sidedish == "mozzarella sticks" = ("pork", "mozzarella sticks", "Merlot") | sidedish == "caviar" = ("pork", "caviar", "Sauvignon Blanc") | entree == "chicken" = | sidedish == "garlic bread" = ("chicken", "garlic bread", "Merlot") | sidedish == "mozzarella sticks" = ("chicken", "mozzarella sticks", "Sauvignon Blanc") | sidedish == "caviar"= ("chicken", "caviar", "Merlot") | entree == "tuna" = | sidedish == "garlic bread" = ("tuna", "garlic bread", "Sauvignon Blanc") | sidedish == "mozzarella sticks" = ("tuna", "mozzarella sticks", "Merlot") | sidedish == "caviar"= ("tuna", "caviar", "Merlot") However, when I load this code into GHCi, I get the following error message: [1 of 1] Compiling Wine ( wine.hs, interpreted ) wine.hs:18:11: parse error on input `"' Failed, modules loaded: none. Prelude> I discovered the following seemingly relevant HaskellWiki page, but am not sure about how to apply the advice in it to this problem, because the advice does not seem sufficiently specific or detailed: List instance - HaskellWiki http://www.haskell.org/haskellwiki/List_instance What would be a good way to overcome this error? -- Benjamin L. Russell

On Thu, 23 Oct 2008 15:07:09 +0900, Benjamin L.Russell
module Wine where
data Wine = Red | White data Red = "Merlot" data White = "Sauvignon Blanc" data Entree = "pork" | "chicken" | "tuna" data SideDish = "garlic bread" | "mozzarella sticks" | "caviar"
wine :: [Entree] -> [SideDish] -> [(Entree, SideDish, Wine)] wine entree sidedish | entree == "pork" = | sidedish == "garlic bread" = ("pork", "garlic bread", "Merlot") | sidedish == "mozzarella sticks" = ("pork", "mozzarella sticks", "Merlot") | sidedish == "caviar" = ("pork", "caviar", "Sauvignon Blanc") | entree == "chicken" = | sidedish == "garlic bread" = ("chicken", "garlic bread", "Merlot") | sidedish == "mozzarella sticks" = ("chicken", "mozzarella sticks", "Sauvignon Blanc") | sidedish == "caviar"= ("chicken", "caviar", "Merlot") | entree == "tuna" = | sidedish == "garlic bread" = ("tuna", "garlic bread", "Sauvignon Blanc") | sidedish == "mozzarella sticks" = ("tuna", "mozzarella sticks", "Merlot") | sidedish == "caviar"= ("tuna", "caviar", "Merlot")
Sorry, I forgot to take care of list comprehension. I'm not quite sure how to extract elements of both lists at the same time in a nested guard. Here's a slight revision; would this work? module Wine where data Wine = Red | White data Red = "Merlot" data White = "Sauvignon Blanc" data Entree = "pork" | "chicken" | "tuna" data SideDish = "garlic bread" | "mozzarella sticks" | "caviar" wine :: [Entree] -> [SideDish] -> [(Entree, SideDish, Wine)] wine entrees sidedishes | entree <- entrees == "pork" = | sidedish <- sidedieshes == "garlic bread" = ("pork", "garlic bread", "Merlot") | sidedish <- sidedishes == "mozzarella sticks" = ("pork", "mozzarella sticks", "Merlot") | sidedish <- sidedishes == "caviar" = ("pork", "caviar", "Sauvignon Blanc") | entree <- entrees == "chicken" = | sidedish <- sidedieshes == "garlic bread" = ("chicken", "garlic bread", "Merlot") | sidedish <- sidedieshes == "mozzarella sticks" = ("chicken", "mozzarella sticks", "Sauvignon Blanc") | sidedish <- sidedieshes == "caviar"= ("chicken", "caviar", "Merlot") | entree <- entrees == "tuna" = | sidedish <- sidedieshes == "garlic bread" = ("tuna", "garlic bread", "Sauvignon Blanc") | sidedish <- sidedieshes == "mozzarella sticks" = ("tuna", "mozzarella sticks", "Merlot") | sidedish <- sidedieshes == "caviar"= ("tuna", "caviar", "Merlot") -- Benjamin L. Russell

On Thu, 23 Oct 2008 15:22:17 +0900, Benjamin L. Russell
Here's a slight revision; would this work?
module Wine where
data Wine = Red | White data Red = "Merlot" data White = "Sauvignon Blanc" data Entree = "pork" | "chicken" | "tuna" data SideDish = "garlic bread" | "mozzarella sticks" | "caviar"
wine :: [Entree] -> [SideDish] -> [(Entree, SideDish, Wine)] wine entrees sidedishes | entree <- entrees == "pork" = | sidedish <- sidedieshes == "garlic bread" = ("pork", "garlic bread", "Merlot") | sidedish <- sidedishes == "mozzarella sticks" = ("pork", "mozzarella sticks", "Merlot") | sidedish <- sidedishes == "caviar" = ("pork", "caviar", "Sauvignon Blanc") | entree <- entrees == "chicken" = | sidedish <- sidedieshes == "garlic bread" = ("chicken", "garlic bread", "Merlot") | sidedish <- sidedieshes == "mozzarella sticks" = ("chicken", "mozzarella sticks", "Sauvignon Blanc") | sidedish <- sidedieshes == "caviar"= ("chicken", "caviar", "Merlot") | entree <- entrees == "tuna" = | sidedish <- sidedieshes == "garlic bread" = ("tuna", "garlic bread", "Sauvignon Blanc") | sidedish <- sidedieshes == "mozzarella sticks" = ("tuna", "mozzarella sticks", "Merlot") | sidedish <- sidedieshes == "caviar"= ("tuna", "caviar", "Merlot")
Sorry; my earlier revision contained some typos where "sidedishes" was misspelled as "sidedieshes." Here is a corrected version: module Wine where data Wine = Red | White data Red = "Merlot" data White = "Sauvignon Blanc" data Entree = "pork" | "chicken" | "tuna" data SideDish = "garlic bread" | "mozzarella sticks" | "caviar" wine :: [Entree] -> [SideDish] -> [(Entree, SideDish, Wine)] wine entrees sidedishes | entree <- entrees == "pork" = | sidedish <- sidedishes == "garlic bread" = ("pork", "garlic bread", "Merlot") | sidedish <- sidedishes == "mozzarella sticks" = ("pork", "mozzarella sticks", "Merlot") | sidedish <- sidedishes == "caviar" = ("pork", "caviar", "Sauvignon Blanc") | entree <- entrees == "chicken" = | sidedish <- sidedishes == "garlic bread" = ("chicken", "garlic bread", "Merlot") | sidedish <- sidedishes == "mozzarella sticks" = ("chicken", "mozzarella sticks", "Sauvignon Blanc") | sidedish <- sidedishes == "caviar"= ("chicken", "caviar", "Merlot") | entree <- entrees == "tuna" = | sidedish <- sidedishes == "garlic bread" = ("tuna", "garlic bread", "Sauvignon Blanc") | sidedish <- sidedishes == "mozzarella sticks" = ("tuna", "mozzarella sticks", "Merlot") | sidedish <- sidedishes == "caviar"= ("tuna", "caviar", "Merlot") -- Benjamin L. Russell

On Thu, 23 Oct 2008 15:27:34 +0900, Benjamin L.Russell
module Wine where
data Wine = Red | White data Red = "Merlot" data White = "Sauvignon Blanc" data Entree = "pork" | "chicken" | "tuna" data SideDish = "garlic bread" | "mozzarella sticks" | "caviar"
wine :: [Entree] -> [SideDish] -> [(Entree, SideDish, Wine)] wine entrees sidedishes | entree <- entrees == "pork" = | sidedish <- sidedishes == "garlic bread" = ("pork", "garlic bread", "Merlot") | sidedish <- sidedishes == "mozzarella sticks" = ("pork", "mozzarella sticks", "Merlot") | sidedish <- sidedishes == "caviar" = ("pork", "caviar", "Sauvignon Blanc") | entree <- entrees == "chicken" = | sidedish <- sidedishes == "garlic bread" = ("chicken", "garlic bread", "Merlot") | sidedish <- sidedishes == "mozzarella sticks" = ("chicken", "mozzarella sticks", "Sauvignon Blanc") | sidedish <- sidedishes == "caviar"= ("chicken", "caviar", "Merlot") | entree <- entrees == "tuna" = | sidedish <- sidedishes == "garlic bread" = ("tuna", "garlic bread", "Sauvignon Blanc") | sidedish <- sidedishes == "mozzarella sticks" = ("tuna", "mozzarella sticks", "Merlot") | sidedish <- sidedishes == "caviar"= ("tuna", "caviar", "Merlot")
I just thought of a revision using the guards within an instance of unlines and map. This approach eliminates the need for the Wine, Red, and White datatypes. However, since two elements of type String need to be extracted at each step, I am not sure of the syntax. Would this approach a solution? module Wine where data Entree = "pork" | "chicken" | "tuna" data SideDish = "garlic bread" | "mozzarella sticks" | "caviar" wine :: Show a => [Entree] -> [SideDish] -> String wine entrees sidedishes = unlines (map entree entrees) (map sidedish sidedishes) where (entree Entree) (sidedish SideDish) = | entree == "pork" = | sidedish == "garlic bread" = "(" ++ show entree ++ ", " ++ show sidedish ++ ", Merlot)" | sidedish == "mozzarella sticks" = "(" ++ show entree ++ ", " ++ show sidedish ++ ", Merlot)" | sidedish == "caviar" = "(" ++ show entree ++ ", " ++ show sidedish ++ ", Sauvignon Blanc)" | entree == "chicken" = | sidedish == "garlic bread" = "(" ++ show entree ++ ", " ++ show sidedish ++ ", Merlot)" | sidedish == "mozzarella sticks" = "(" ++ show entree ++ ", " ++ show sidedish ++ ", Sauvignon Blanc)" | sidedish == "caviar"= "(" ++ show entree ++ ", " ++ show sidedish ++ ", Merlot)" | entree == "tuna" = | sidedish == "garlic bread" = "(" ++ show entree ++ ", " ++ show sidedish ++ ", Sauvignon Blanc)" | sidedish == "mozzarella sticks" = "(" ++ show entree ++ ", " ++ show sidedish ++ ", Merlot)" | sidedish == "caviar"= "(" ++ show entree ++ ", " ++ show sidedish ++ ", Merlot)" -- Benjamin L. Russell

Am Donnerstag, 23. Oktober 2008 08:07 schrieb Benjamin L.Russell:
How is it possible to define a user datatype consisting of instances of String?
Suppose I am preparing a party for wine connoisseurs, and want to define the following data types:
data Wine = Red | White data Red = "Merlot" data White = "Sauvignon Blanc" data Entree = "pork" | "chicken" | "tuna" data SideDish = "garlic bread" | "mozzarella sticks" | "caviar"
The syntax for data declarations does not allow such, you must have constructors applied to types. You could make it data Wine = Red Red | White White data Red = Merlot | Syrah data White = SauvignonBlanc | Riesling | PinotNoir data Entree = Pork | Chicken | Tuna deriving (Eq, Enum, Bounded) data SideDish = GarlicBread | MozzarellaSticks | Caviar deriving (Eq, Enum, Bounded) instance Show Wine where ... instance Show Red where ... ...
Then, I want to write a Haskell function that takes two lists; e.g.,
["pork", "chicken", "tuna"]
and
["garlic bread", "mozzarella sticks", "caviar"]
and that constructs a three-tuple of the following type:
(Entree, SideDish, Wine)
such that which Wine is chosen depends on the particular combination of Entree and SideDish, with respect to the following rules:
("pork", "garlic bread") -> ("pork", "garlic bread", "Merlot") ("pork", "mozzarella sticks") -> ("pork", "mozzarella sticks", "Merlot") ("pork", "caviar") -> ("pork", "Beluga", "Sauvignon Blanc") ("chicken", "garlic bread") -> ("chicken", "garlic bread", "Merlot") ("chicken", "mozzarella sticks") -> ("chicken", "mozzarella sticks", "Sauvignon Blanc") ("chicken", "caviar") -> ("chicken", "caviar", "Merlot") ("tuna", "garlic bread") -> ("tuna", "garlic bread", "Sauvignon Blanc") ("tuna", "mozzarella sticks") -> ("tuna", "mozzarella sticks", "Merlot") ("tuna", "caviar") -> ("tuna", "caviar", "Merlot")
selectWine :: Entree -> SideDish -> Wine selectWine Pork sd = case sd of Caviar -> White SauvignonBlanc _ -> Red Merlot selectWine Chicken sd = case sd of MozzarellaSticks -> White SauvignonBlanc _ -> Red Merlot selectWine Tuna sd = case sd of GarlicBread -> White SauvignonBlanc _ -> Red Merlot options :: [(Entree,SideDish,Wine)] options = [(e,s,selectWine e s) | e <- [minBound .. maxBound], s <- [minBound .. maxBound]]
So far, I have written the following Haskell code:
module Wine where
data Wine = Red | White data Red = "Merlot" data White = "Sauvignon Blanc" data Entree = "pork" | "chicken" | "tuna" data SideDish = "garlic bread" | "mozzarella sticks" | "caviar"
wine :: [Entree] -> [SideDish] -> [(Entree, SideDish, Wine)] wine entree sidedish
| entree == "pork" = | | sidedish == "garlic bread" = ("pork", "garlic bread",
"Merlot")
| sidedish == "mozzarella sticks" = ("pork", "mozzarella
sticks", "Merlot")
| sidedish == "caviar" = ("pork", "caviar", "Sauvignon Blanc") | | entree == "chicken" = | | sidedish == "garlic bread" = ("chicken", "garlic bread",
"Merlot")
| sidedish == "mozzarella sticks" = ("chicken", "mozzarella
sticks", "Sauvignon Blanc")
| sidedish == "caviar"= ("chicken", "caviar", "Merlot") | | entree == "tuna" = | | sidedish == "garlic bread" = ("tuna", "garlic bread",
"Sauvignon Blanc")
| sidedish == "mozzarella sticks" = ("tuna", "mozzarella
sticks", "Merlot")
| sidedish == "caviar"= ("tuna", "caviar", "Merlot")
However, when I load this code into GHCi, I get the following error message:
[1 of 1] Compiling Wine ( wine.hs, interpreted )
wine.hs:18:11: parse error on input `"' Failed, modules loaded: none. Prelude>
I discovered the following seemingly relevant HaskellWiki page, but am not sure about how to apply the advice in it to this problem, because the advice does not seem sufficiently specific or detailed:
List instance - HaskellWiki http://www.haskell.org/haskellwiki/List_instance
This isn't relevant here, you're not trying to create an instance of some typeclass for a list-type.
What would be a good way to overcome this error?
-- Benjamin L. Russell
See above, but I suggest rethinking your menu :)

On Thu, 23 Oct 2008 08:47:24 +0200, Daniel Fischer
[...]
The syntax for data declarations does not allow such, you must have constructors applied to types. You could make it
data Wine = Red Red | White White data Red = Merlot | Syrah data White = SauvignonBlanc | Riesling | PinotNoir data Entree = Pork | Chicken | Tuna deriving (Eq, Enum, Bounded) data SideDish = GarlicBread | MozzarellaSticks | Caviar deriving (Eq, Enum, Bounded)
instance Show Wine where ... instance Show Red where ... ...
[...]
selectWine :: Entree -> SideDish -> Wine selectWine Pork sd = case sd of Caviar -> White SauvignonBlanc _ -> Red Merlot selectWine Chicken sd = case sd of MozzarellaSticks -> White SauvignonBlanc _ -> Red Merlot selectWine Tuna sd = case sd of GarlicBread -> White SauvignonBlanc _ -> Red Merlot
options :: [(Entree,SideDish,Wine)] options = [(e,s,selectWine e s) | e <- [minBound .. maxBound], s <- [minBound .. maxBound]]
[...]
This isn't relevant here, you're not trying to create an instance of some typeclass for a list-type.
What would be a good way to overcome this error?
-- Benjamin L. Russell
See above, but I suggest rethinking your menu :)
After taking your advice into account, I have rewritten the wine.hs program as follows, but am unable to figure out what to write for the type constructor for Wine. In particular, I do not understand why the user type definition for Wine is "Red Red | White White" instead of just "Red | White." Should I fill out "instance Show Wine where ..." as something similar to instance Show Wine where show Red = ... show White = ... and then supply a conditional after "show Red = ..." and "show White = ...," or do I need to supply something else there? Here's my revised code so far (the "instance Show Wine where ..." part is unfinished): module Wine where data Wine = Red Red | White White data Red = Merlot | Syrah | Port data White = SauvignonBlanc | Riesling | PinotNoir data Entree = KobeBeef | LemonChicken | SteamedSalmon deriving (Eq, Enum, Bounded) data SideDish = ButteredPotatoes | BrieCheese | GreekSalad deriving (Eq, Enum, Bounded) instance Show Wine where ... instance Show Red where show Merlot = "Merlot" show Syrah = "Syrah" show Port = "Port" instance Show White where show SauvignonBlanc = "Sauvignon Blanc" show Riesling = "Riesling" show PinotNoir = "Pinot Noir" instance Show Entree where show KobeBeef = "Kobe Beef" show LemonChicken = "Lemon Chicken" show SteamedSalmon = "Steamed Salmon" instance Show SideDish where show ButteredPotatoes = "Buttered Potatoes" show BrieCheese = "Brie Cheese" show GreekSalad = "Greek Salad" selectWine :: Entree -> SideDish -> Wine selectWine KobeBeef sd = case sd of GreekSalad -> White SauvignonBlanc _ -> Red Merlot selectWine LemonChicken sd = case sd of BrieCheese -> White Riesling _ -> Red Syrah selectWine SteamedSalmon sd = case sd of ButteredPotatoes -> White PinotNoir _ -> Red Port options :: [(Entree,SideDish,Wine)] options = [(e,s,selectWine e s) | e <- [minBound .. maxBound], s <- [minBound .. maxBound]] -- Benjamin L. Russell

On Thu, 23 Oct 2008 17:51:59 +0900, Benjamin L.Russell
[...]
After taking your advice into account, I have rewritten the wine.hs program as follows, but am unable to figure out what to write for the type constructor for Wine. In particular, I do not understand why the user type definition for Wine is "Red Red | White White" instead of just "Red | White."
Should I fill out "instance Show Wine where ..." as something similar to
instance Show Wine where show Red = ... show White = ...
and then supply a conditional after "show Red = ..." and "show White = ...," or do I need to supply something else there?
[...]
After researching type classes somewhat, I discovered that in "data Wine = Red Red | White White," the second terms "Red" and "White" were arguments to their respective first terms of the same name. With this information, I then rewrote the type definition and type constructor for Wine as follows: data Wine = Red Red | White White instance Show Wine where show (Red Merlot) = "Merlot" show (Red Syrah) = "Syrah" show (Red Port) = "Port" show (White SauvignonBlanc) = "Sauvignon Blanc" show (White Riesling) = "Riesling" show (White PinotNoir) = "Pinot Noir" Here is my revised program, which seems to work fine this time: module Wine where data Wine = Red Red | White White data Red = Merlot | Syrah | Port data White = SauvignonBlanc | Riesling | PinotNoir data Entree = KobeBeef | LemonChicken | SteamedSalmon deriving (Eq, Enum, Bounded) data SideDish = ButteredPotatoes | BrieCheese | GreekSalad deriving (Eq, Enum, Bounded) instance Show Wine where show (Red Merlot) = "Merlot" show (Red Syrah) = "Syrah" show (Red Port) = "Port" show (White SauvignonBlanc) = "Sauvignon Blanc" show (White Riesling) = "Riesling" show (White PinotNoir) = "Pinot Noir" instance Show Red where show Merlot = "Merlot" show Syrah = "Syrah" show Port = "Port" instance Show White where show SauvignonBlanc = "Sauvignon Blanc" show Riesling = "Riesling" show PinotNoir = "Pinot Noir" instance Show Entree where show KobeBeef = "Kobe Beef" show LemonChicken = "Lemon Chicken" show SteamedSalmon = "Steamed Salmon" instance Show SideDish where show ButteredPotatoes = "Buttered Potatoes" show BrieCheese = "Brie Cheese" show GreekSalad = "Greek Salad" selectWine :: Entree -> SideDish -> Wine selectWine KobeBeef sd = case sd of GreekSalad -> White SauvignonBlanc _ -> Red Merlot selectWine LemonChicken sd = case sd of BrieCheese -> White Riesling _ -> Red Syrah selectWine SteamedSalmon sd = case sd of ButteredPotatoes -> White PinotNoir _ -> Red Port options :: [(Entree,SideDish,Wine)] options = [(e,s,selectWine e s) | e <- [minBound .. maxBound], s <- [minBound .. maxBound]] When I run it in GHCi (with my Haskell program file renamed as wine2.hs), these are the results: Prelude> :l wine2.hs [1 of 1] Compiling Wine ( wine2.hs, interpreted ) Ok, modules loaded: Wine. *Wine> options [(Kobe Beef,Buttered Potatoes,Merlot),(Kobe Beef,Brie Cheese,Merlot),(Kobe Beef, Greek Salad,Sauvignon Blanc),(Lemon Chicken,Buttered Potatoes,Syrah),(Lemon Chic ken,Brie Cheese,Riesling),(Lemon Chicken,Greek Salad,Syrah),(Steamed Salmon,Butt ered Potatoes,Pinot Noir),(Steamed Salmon,Brie Cheese,Port),(Steamed Salmon,Gree k Salad,Port)] *Wine> These results seem correct. Thank you for your help! -- Benjamin L. Russell

On Thu, 23 Oct 2008 18:39:52 +0900, Benjamin L. Russell
instance Show Wine where show (Red Merlot) = "Merlot" show (Red Syrah) = "Syrah" show (Red Port) = "Port" show (White SauvignonBlanc) = "Sauvignon Blanc" show (White Riesling) = "Riesling" show (White PinotNoir) = "Pinot Noir"
instance Show Red where show Merlot = "Merlot" show Syrah = "Syrah" show Port = "Port"
instance Show White where show SauvignonBlanc = "Sauvignon Blanc" show Riesling = "Riesling" show PinotNoir = "Pinot Noir"
The only remaining issue is whether there is a way to define the type constructor for Wine without pre-defining parts that are later defined in the type constructors for Red and White. In the above code, for example,
instance Show Wine where show (Red Merlot) = "Merlot"
essentially pre-defines the following definition later given in the type constructor for Red:
instance Show Red where show Merlot = "Merlot"
This seems redundant. Since the type definition for Wine is data Wine = Red Red | White White the type constructors for Red and White both require an argument, so show (Red Merlot) = ... seems reasonable. This would seem to imply that if I need to reduce redundancy, I should probably rewrite the RHS of the above line. Is there a way to refer to the type constructors for Red and White in the type constructor for Wine? -- Benjamin L. Russell

Am Donnerstag, 23. Oktober 2008 11:48 schrieb Benjamin L.Russell:
On Thu, 23 Oct 2008 18:39:52 +0900, Benjamin L. Russell
wrote: instance Show Wine where show (Red Merlot) = "Merlot" show (Red Syrah) = "Syrah" show (Red Port) = "Port" show (White SauvignonBlanc) = "Sauvignon Blanc" show (White Riesling) = "Riesling" show (White PinotNoir) = "Pinot Noir"
instance Show Red where show Merlot = "Merlot" show Syrah = "Syrah" show Port = "Port"
instance Show White where show SauvignonBlanc = "Sauvignon Blanc" show Riesling = "Riesling" show PinotNoir = "Pinot Noir"
The only remaining issue is whether there is a way to define the type constructor for Wine without pre-defining parts that are later defined in the type constructors for Red and White.
You could make it type Grape = String type Colour = String data Wine = Wine { grape :: Grape, colour :: Colour } but you'd face the possibility of (Wine "" "petillant") - bad. To have only real wines, you have to do it more or less as it is or leave out the Red and White types and make Wine an enumeration without colour tag.
In the above code, for example,
instance Show Wine where show (Red Merlot) = "Merlot"
essentially pre-defines the following definition later given in the
type constructor for Red:
instance Show Red where show Merlot = "Merlot"
with the below Show instance of Wine, instance Show Red where show = show . Red instance Show White where show = show . White would save a bit of typing. But the other way round, instance Show Wine where show (Red w) = show w show (White w) = show w seems cleaner.
This seems redundant.
Since the type definition for Wine is
data Wine = Red Red | White White
the type constructors for Red and White both require an argument, so
show (Red Merlot) = ...
seems reasonable.
This would seem to imply that if I need to reduce redundancy, I should probably rewrite the RHS of the above line.
Is there a way to refer to the type constructors for Red and White in the type constructor for Wine?
I don't understand what you mean, certainly not data Wine a = W a and W Merlot :: Wine Red ?
-- Benjamin L. Russell
Cheers, Daniel

Am Donnerstag, 23. Oktober 2008 10:51 schrieb Benjamin L.Russell:
After taking your advice into account, I have rewritten the wine.hs program as follows, but am unable to figure out what to write for the type constructor for Wine. In particular, I do not understand why the user type definition for Wine is "Red Red | White White" instead of just "Red | White."
Okay, that was a bit mean, but not intentionally. In GADT syntax: data Wine where Red :: Red -> Wine White :: White -> Wine So there is a dataconstructor called Red and also a datatype (I was tempted to write typeconstructor) called Red and the dataconstructor Red takes an argument of type Red, similarly for White. The type Wine is isomorphic to Either Red White, but since that wouldn't give a good Show instance, we roll our own type. If we had just data Wine = Red | White , the type Wine would have just the two members Red and White (and _|_) and not have any connection with the types Red and White which give the details (grape/origin). We need a means to transform a value of type Red into a value of type Wine, that is a function of type Red -> Wine, the application demands that that function doesn't lose information, that is best achieved by a dataconstructor of type Red -> Wine. Would probably have been less confusing if I called the dataconstructors RedWine resp. WhiteWine.
Should I fill out "instance Show Wine where ..." as something similar to
instance Show Wine where show Red = ... show White = ...
and then supply a conditional after "show Red = ..." and "show White = ...," or do I need to supply something else there?
You have basically two choices, you can say everybody knows which colour the wines have and use instance Show Wine where show (Red w) = show w show (White w) = show w or include the colour in the rendered String, for example via deriving Show, or by declaring your own instance (if you want White PinotNoir rendered as "White (Pinot Noir)", you would have to do that or write a more complicated Show instance for White). If you want to parse values of type Wine in the future, it will be slightly easier with the dataconstructors included.
Here's my revised code so far (the "instance Show Wine where ..." part is unfinished):
module Wine where
data Wine = Red Red | White White data Red = Merlot | Syrah | Port data White = SauvignonBlanc | Riesling | PinotNoir data Entree = KobeBeef | LemonChicken | SteamedSalmon deriving (Eq, Enum, Bounded) data SideDish = ButteredPotatoes | BrieCheese | GreekSalad deriving (Eq, Enum, Bounded)
instance Show Wine where ...
instance Show Red where show Merlot = "Merlot" show Syrah = "Syrah" show Port = "Port"
instance Show White where show SauvignonBlanc = "Sauvignon Blanc" show Riesling = "Riesling" show PinotNoir = "Pinot Noir"
instance Show Entree where show KobeBeef = "Kobe Beef" show LemonChicken = "Lemon Chicken" show SteamedSalmon = "Steamed Salmon"
instance Show SideDish where show ButteredPotatoes = "Buttered Potatoes" show BrieCheese = "Brie Cheese" show GreekSalad = "Greek Salad"
selectWine :: Entree -> SideDish -> Wine selectWine KobeBeef sd = case sd of GreekSalad -> White SauvignonBlanc _ -> Red Merlot selectWine LemonChicken sd = case sd of BrieCheese -> White Riesling _ -> Red Syrah selectWine SteamedSalmon sd = case sd of ButteredPotatoes -> White PinotNoir _ -> Red Port
options :: [(Entree,SideDish,Wine)] options = [(e,s,selectWine e s) | e <- [minBound .. maxBound], s <- [minBound .. maxBound]]
-- Benjamin L. Russell
Bon Appetit, Daniel P.S.: Could I have a Syrah with my beef and potatoes?

On Thu, 23 Oct 2008 11:48:46 +0200, Daniel Fischer
Am Donnerstag, 23. Oktober 2008 10:51 schrieb Benjamin L.Russell:
After taking your advice into account, I have rewritten the wine.hs program as follows, but am unable to figure out what to write for the type constructor for Wine. In particular, I do not understand why the user type definition for Wine is "Red Red | White White" instead of just "Red | White."
Okay, that was a bit mean, but not intentionally.
In GADT syntax: data Wine where Red :: Red -> Wine White :: White -> Wine
So there is a dataconstructor called Red and also a datatype (I was tempted to write typeconstructor) called Red and the dataconstructor Red takes an argument of type Red, similarly for White. The type Wine is isomorphic to Either Red White, but since that wouldn't give a good Show instance, we roll our own type.
If we had just data Wine = Red | White , the type Wine would have just the two members Red and White (and _|_) and not have any connection with the types Red and White which give the details (grape/origin). We need a means to transform a value of type Red into a value of type Wine, that is a function of type Red -> Wine, the application demands that that function doesn't lose information, that is best achieved by a dataconstructor of type Red -> Wine. Would probably have been less confusing if I called the dataconstructors RedWine resp. WhiteWine.
Thank you. That makes the Wine much clearer ;-) .
[...]
You have basically two choices, you can say everybody knows which colour the wines have and use
instance Show Wine where show (Red w) = show w show (White w) = show w
or include the colour in the rendered String, for example via deriving Show, or by declaring your own instance (if you want White PinotNoir rendered as "White (Pinot Noir)", you would have to do that or write a more complicated Show instance for White). If you want to parse values of type Wine in the future, it will be slightly easier with the dataconstructors included.
So perhaps I should rewrite the type definitions for Red and White as follows? data Red = Syrah | Merlot | Port deriving (Eq, Show) data White = SauvignonBlanc | Riesling | PinotNoir deriving (Eq, Show) Alternatively (adapted from an example provided by Dirk Thierbach in the thread "seeking helpful links," dated "Tue, 21 Oct 2008 16:33:41 -0700 (PDT)," on comp.lang.haskell), perhaps the following? type Entree = String type SideDish = String type Wine = String wine :: Entree -> SideDish -> Wine wine "Kobe Beef" "Buttered Potatoes" = "Syrah" wine "Kobe Beef" "Brie Cheese" = "Syrah" wine "Kobe Beef" "Greek Salad" = "Sauvignon Blanc" wine "Lemon Chicken" "Buttered Potatoes" = "Merlot" wine "Lemon Chicken" "Brie Cheese" = "Sauvignon Blanc" wine "Lemon Chicken" "Greek Salad" = "Merlot" wine "Steamed Salmon" "Buttered Potatoes" = "Sauvignon Blanc" wine "Steamed Salmon" "Brie Cheese" = "Port" wine "Steamed Salmon" "Greek Salad" = "Port" wines :: [Entree] -> [SideDish] -> [(Entree, SideDish, Wine)] wines entrees sideDishes = [(e, s, wine e s) | e <- entrees, s <- sideDishes]
[...]
Bon Appetit, Daniel
P.S.: Could I have a Syrah with my beef and potatoes?
Certainly; here is your Syrah with your beef and potatoes. Bon appetit ;-) : module Wine where data Wine = Red Red | White White data Red = Syrah | Merlot | Port data White = SauvignonBlanc | Riesling | PinotNoir data Entree = KobeBeef | LemonChicken | SteamedSalmon deriving (Eq, Enum, Bounded) data SideDish = ButteredPotatoes | BrieCheese | GreekSalad deriving (Eq, Enum, Bounded) instance Show Wine where show (Red w) = show w show (White w) = show w instance Show Red where show Syrah = "Syrah" show Merlot = "Merlot" show Port = "Port" instance Show White where show SauvignonBlanc = "Sauvignon Blanc" show Riesling = "Riesling" show PinotNoir = "Pinot Noir" instance Show Entree where show KobeBeef = "Kobe Beef" show LemonChicken = "Lemon Chicken" show SteamedSalmon = "Steamed Salmon" instance Show SideDish where show ButteredPotatoes = "Buttered Potatoes" show BrieCheese = "Brie Cheese" show GreekSalad = "Greek Salad" selectWine :: Entree -> SideDish -> Wine selectWine KobeBeef sd = case sd of GreekSalad -> White SauvignonBlanc _ -> Red Syrah selectWine LemonChicken sd = case sd of BrieCheese -> White Riesling _ -> Red Merlot selectWine SteamedSalmon sd = case sd of ButteredPotatoes -> White PinotNoir _ -> Red Port options :: [(Entree,SideDish,Wine)] options = [(e,s,selectWine e s) | e <- [minBound .. maxBound], s <- [minBound .. maxBound]] Here's your new menu: *Wine> :l wine2.hs [1 of 1] Compiling Wine ( wine2.hs, interpreted ) Ok, modules loaded: Wine. *Wine> options [(Kobe Beef,Buttered Potatoes,Syrah),(Kobe Beef,Brie Cheese,Syrah),(Kobe Beef,Gr eek Salad,Sauvignon Blanc),(Lemon Chicken,Buttered Potatoes,Merlot),(Lemon Chick en,Brie Cheese,Riesling),(Lemon Chicken,Greek Salad,Merlot),(Steamed Salmon,Butt ered Potatoes,Pinot Noir),(Steamed Salmon,Brie Cheese,Port),(Steamed Salmon,Gree k Salad,Port)] *Wine> -- Benjamin L. Russell

Am Donnerstag, 23. Oktober 2008 12:19 schrieb Benjamin L.Russell:
You have basically two choices, you can say everybody knows which colour the wines have and use
instance Show Wine where show (Red w) = show w show (White w) = show w
or include the colour in the rendered String, for example via deriving Show, or by declaring your own instance (if you want White PinotNoir rendered as "White (Pinot Noir)", you would have to do that or write a more complicated Show instance for White). If you want to parse values of type Wine in the future, it will be slightly easier with the dataconstructors included.
So perhaps I should rewrite the type definitions for Red and White as follows?
data Red = Syrah | Merlot | Port deriving (Eq, Show) data White = SauvignonBlanc | Riesling | PinotNoir deriving (Eq, Show)
That would be the easiest, but of course having the two Whites displayed with a space is aesthetically superior.
Alternatively (adapted from an example provided by Dirk Thierbach in the thread "seeking helpful links," dated "Tue, 21 Oct 2008 16:33:41 -0700 (PDT)," on comp.lang.haskell), perhaps the following?
type Entree = String type SideDish = String type Wine = String
wine :: Entree -> SideDish -> Wine wine "Kobe Beef" "Buttered Potatoes" = "Syrah" wine "Kobe Beef" "Brie Cheese" = "Syrah" wine "Kobe Beef" "Greek Salad" = "Sauvignon Blanc" wine "Lemon Chicken" "Buttered Potatoes" = "Merlot" wine "Lemon Chicken" "Brie Cheese" = "Sauvignon Blanc" wine "Lemon Chicken" "Greek Salad" = "Merlot" wine "Steamed Salmon" "Buttered Potatoes" = "Sauvignon Blanc" wine "Steamed Salmon" "Brie Cheese" = "Port" wine "Steamed Salmon" "Greek Salad" = "Port"
wines :: [Entree] -> [SideDish] -> [(Entree, SideDish, Wine)] wines entrees sideDishes = [(e, s, wine e s) | e <- entrees, s <- sideDishes]
The downside of that is that a typo in the entrees or sideDishes will explode with a pattern match failure. Otherwise it's concise and clean.
[...]
Bon Appetit, Daniel
P.S.: Could I have a Syrah with my beef and potatoes?
Certainly; here is your Syrah with your beef and potatoes. Bon appetit ;-) :
Merci, c'était délicieux.
-- Benjamin L. Russell
participants (2)
-
Benjamin L.Russell
-
Daniel Fischer