This is a compact solution, but it produces multiple permutations of the same solution, which increases runtime. I let it run for 10 seconds, then ctrl-c'd.
Here's a solution that produces all 2 (or three, if you include Barbecue Sandwich) solutions instantly: Output: ===== *Xkcd287> go Menu 1 ****** Mixed Fruit ($2.15) x 7 Total: 15.05 Menu 2 ****** Hot Wings ($3.55) x 2 Mixed Fruit ($2.15) x 1 Sample Plate ($5.8) x 1 Total: 15.05 Menu 3 ****** Barbecue Sandwich ($6.55) x 1 Mixed Fruit ($2.15) x 2 Mozzarella Sticks ($4.2) x 1 Total: 15.05 *Xkcd287> Sourcecode: ========= module Xkcd287 where import Char import IO import GHC.Float import List import qualified Data.Map as Map import Control.Monad import Control.Monad.State import Control.Monad.Reader import Control.Monad.Writer menu :: [(String,Int)] menu = [("Mixed Fruit", 215), ("French Fries", 275), ("Side Salad", 335), ("Hot Wings", 355), ("Mozzarella Sticks", 420), ("Sample Plate", 580), ("Barbecue Sandwich", 655) ] cost:: Int cost = 1505 solutions :: [(String,Int)] -> Int -> [[(String,Int)]] solutions menu targetcost = [ solution | solution <- solutions' menu [] targetcost ] solutions' :: [(String,Int)] -> [(String,Int)] -> Int -> [[(String,Int)]] solutions' menu itemssofar targetcost | targetcost == 0 = [itemssofar] | otherwise = [ solution | item <- menu, (null itemssofar) || ((snd item) <= snd(head itemssofar)), (snd item) <= targetcost, solution <- solutions' menu (item:itemssofar) (targetcost - (snd item) ) ] synthesize :: [[(String,Int)]] -> [[(String,Int,Int)]] synthesize solutions = [ synthesize' solution | solution <- solutions ] synthesize' :: [(String,Int)] -> [(String,Int,Int)] synthesize' solution = [ (name,value,count) | (name,(value,count)) <- synthesize'' ] where synthesize'' :: [(String,(Int,Int))] synthesize'' = Map.toList $ foldr (\(name,value) thismap -> (process name value (Map.lookup name thismap) thismap) ) Map.empty solution process :: String -> Int -> Maybe (Int,Int) -> Map.Map String (Int,Int) -> Map.Map String (Int,Int) process name value Nothing thismap = Map.insert name (value,1 ) thismap process name value (Just(value',count)) thismap = Map.adjust(\(oldvalue,oldcount) -> (oldvalue,oldcount + 1)) name thismap createbilling :: [[(String,Int,Int)]] -> [String] createbilling solutions = [ line | (solution,i) <- (zip solutions [1..]), line <- ["Menu " ++ show(i), "******"] ++ createbilling' solution ++ ["Total: " ++ show( (int2Double $ foldr (\(name,value,count) total -> (total + (value * count)) ) 0 solution ) / 100) ] ++ [""] ] createbilling' :: [(String,Int,Int)] -> [String] createbilling' solution = [ name ++ " ($" ++ show((int2Double value) / 100.0) ++ ") x " ++ show(count) | (name,value,count) <- solution ] go' :: [[(String,Int,Int)]] go' = synthesize $ solutions menu cost go :: IO () go = mapM_ putStrLn (createbilling $ go' ) On 7/10/07, Henning Thielemann <[EMAIL PROTECTED]> wrote:
On Tue, 10 Jul 2007, Donald Bruce Stewart wrote: > These smaller NP problems really love the list monad. here's roconnor's > solution from #haskell: > > import Control.Monad > > menu = [("Mixed Fruit",215),("French Fries",275) > ,("Side Salad",335),("Hot Wings",355) > ,("Mozzarella Sticks",420),("Sampler Plate",580)] > > main = mapM_ print > [ map fst y > | i <- [0..] > , y <- replicateM i menu > , sum (map snd y) == 1505 ] Shouldn't we stay away from integer indices on lists? [ map fst y | y <- concat (iterate (liftM2 (:) menu) [[]]), sum (map snd y) == 1505] _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe