Skip to content

Instantly share code, notes, and snippets.

@pacak
Last active August 29, 2015 14:21
Show Gist options
  • Save pacak/ffcf9761ecfa55d642af to your computer and use it in GitHub Desktop.
Save pacak/ffcf9761ecfa55d642af to your computer and use it in GitHub Desktop.
1/0 knapsack using various stuff
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS -Wall #-}
module Main where
import Data.Functor.Foldable
import Control.Comonad.Cofree
type Item = (String, Int, Double)
ss :: [Item]
ss = [("A", 5, 10), ("B", 4, 40), ("C", 6, 30), ("D", 3, 50)]
getVal :: Item -> Double
getVal (_, _, val) = val
getWgt :: Item -> Int
getWgt (_, wgt, _) = wgt
knapsack :: forall a. (a -> Double) -> (a -> Int) -> [a] -> [(Double, [a])]
knapsack valuate measure = histo phi where
phi :: Prim [a] (Cofree (Prim [a]) [(Double, [a])]) -> [(Double, [a])]
phi Nil = repeat nothing
phi (Cons a@(measure -> w) (prevSol :< _)) =
zipWith bestSol prevSol (replicate w nothing ++ map (pick a) prevSol)
nothing = (0, [])
pick item (val, items) = (val + valuate item, item:items)
bestSol a b = if fst a > fst b then a else b
main :: IO ()
main = print $ knapsack getVal getWgt ss !! 10
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment