Skip to content

Instantly share code, notes, and snippets.

Created June 16, 2014 23:15
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save anonymous/99bc650c41e07364764c to your computer and use it in GitHub Desktop.
Save anonymous/99bc650c41e07364764c to your computer and use it in GitHub Desktop.
A slow solution to the goat, wolf, lion problem.
{-# LANGUAGE BangPatterns #-}
-- tdp93422 over in yahoo.com land.
import qualified Data.Set as S
import Data.List (foldl')
import System.Environment (getArgs)
main :: IO ()
main = do
args <- getArgs
putStrLn $ "goats: " ++ (args !! 0)
putStrLn $ "wolves: " ++ (args !! 1)
putStrLn $ "lions: " ++ (args !! 2)
let animalCount = map read args :: [Int]
doIt $ GWL (animalCount !! 0) (animalCount !! 1) (animalCount !! 2)
data GWL = GWL { goat :: !Int
, wolf :: !Int
, lion :: !Int} deriving (Eq, Ord, Show)
doIt :: GWL -> IO ()
doIt m = doIt' (S.singleton m)
where
doIt' :: S.Set GWL -> IO()
doIt' ms = do
let newGWLs = eatAll ms
if S.foldl' setSuccess False newGWLs
then mapM_ print $ S.toList $ S.filter success $ newGWLs
else doIt' newGWLs
setSuccess :: Bool -> GWL -> Bool
setSuccess True _ = True
setSuccess False m = success m
success :: GWL -> Bool
success (GWL g w l) = (g == 0 && (w == 0 || l == 0)) || (w == 0 && l == 0)
eatAll :: S.Set GWL -> S.Set GWL
eatAll roundGWLs = S.foldl' eat S.empty roundGWLs
eat :: S.Set GWL -> GWL -> S.Set GWL
eat newEatSet (GWL g w l) = lionEatGoat
where
wolfEatGoat = if w > 0 && g > 0
then S.insert (GWL (g-1) (w-1) (l+1)) newEatSet
else newEatSet
lionEatWolf = if w > 0 && l > 0
then S.insert (GWL (g+1) (w-1) (l-1)) wolfEatGoat
else wolfEatGoat
lionEatGoat = if g > 0 && l > 0
then S.insert (GWL (g-1) (w+1) (l-1)) lionEatWolf
else lionEatWolf
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment