[Haskell-beginners] Lions, Wolves and Goats

Elric elric at kiosa.org
Sun Jun 8 00:04:09 UTC 2014


Hi,
/
Disclaimer: I have been learning Haskell for a month and there are still 
several things about this wonderful language I know nothing of, so 
please bear with me. Also, I apologize for this (somewhat) long mail./

I came across this article: 
http://unriskinsight.blogspot.co.at/2014/06/fast-functional-goats-lions-and-wolves.html 
a couple of days ago. This compares performance of solving a problem 
(which I will get to) using the functional constructs alone in languages 
like C++11 and Java 8.
Since, Haskell is my first foray into FP, I thought I should try solving 
this in Haskell.

So the problem at hand is this: There is a magical forest which has only 
Lions, Wolves and Goats.
Lions are stronger than Wolves which are in turn stronger than Goats. 
Each strong animal is capable of eating a weaker animal, which also in 
turn transforms the '/eater/' into an animal which was not involved.
/i.e./ If a Lion eats a Wolf it gets transformed into a Goat. If a Wolf 
eats a Sheep it gets transformed into a Lion.

Below are the two versions of the code I came up with to solve this. 
Neither of them converge to the 'endStates' even after about 15 minutes. 
So there is definitely something wrong with what I have done. But after 
banging my head on the keyboard for more then a day with this, I would 
appreciate some pointers or help.

-- version 1
import Data.List

data Animal = Lion Int | Wolf Int | Goat Int
             deriving (Show, Eq)

type Forest = [Animal]

-- lions f = count 0 f
--   where
--     count acc [] = acc
--     count acc ((Lion a):as) = acc + a + (count acc as)
--     count acc (_:as) = acc + (count acc as)

-- wolfs f = count 0 f
--   where
--     count acc [] = acc
--     count acc ((Wolf a):as) = acc + a + (count acc as)
--     count acc (_:as) = acc + (count acc as)

-- goats f = count 0 f
--   where
--     count acc [] = acc
--     count acc ((Goat a):as) = acc + a + (count acc as)
--     count acc (_:as) = acc + (count acc as)

lions [Lion l, Wolf w, Goat g] = l
wolfs [Lion l, Wolf w, Goat g] = w
goats [Lion l, Wolf w, Goat g] = g

--Invalid eat calls are returned with [], to denote termination
eat :: Forest -> Animal -> Animal -> Forest
eat f (Lion _) (Goat le) =
   if (l >= le && g >= le) then [Lion (l-le), Wolf (w+le), Goat (g-le)] 
else []
   where
     l = lions f
     w = wolfs f
     g = goats f
eat f (Lion _) (Wolf le) =
   if (l >= le && w >= le) then [Lion (l-le), Wolf (w-le), Goat (g+le)] 
else []
   where
     l = lions f
     w = wolfs f
     g = goats f
eat f (Wolf _) (Goat we) =
   if (w >= we && g >= we) then [Lion (l+we), Wolf (w-we), Goat (g-we)] 
else []
   where
     l = lions f
     w = wolfs f
     g = goats f
eat _ _ _ = []

lionEatGoat :: Forest -> Forest
lionEatGoat f = eat f (Lion 0) (Goat 1)

lionEatWolf :: Forest -> Forest
lionEatWolf f = eat f (Lion 0) (Wolf 1)

wolfEatGoat :: Forest -> Forest
wolfEatGoat f = eat f (Wolf 0) (Goat 1)

meal :: Forest -> [Forest]
meal [] = []
meal f@[Lion l, Wolf w, Goat g]
   | endState f = []
   | l == 0 = [f] ++ weg
   | w == 0 = [f] ++ leg
   | g == 0 = [f] ++ lew
   | (l /= 0) && (w /= 0) && (g /= 0) = [f] ++ leg ++ lew ++ weg
   | otherwise = []
   where
     leg = meal $ lionEatGoat f
     lew = meal $ lionEatWolf f
     weg = meal $ wolfEatGoat f

endState :: Forest -> Bool
endState f = if ((l == 0 && g == 0) ||
                  (l == 0 && w == 0) ||
                  (w == 0 && g == 0)) then
                True
              else
                False
   where
     l = lions f
     w = wolfs f
     g = goats f

endStates = filter endState

main = do
   putStrLn $ show $ endStates $ meal [Lion 6, Wolf 55, Goat 17]

I thought using the ADT was causing the performance issue and reverted 
to using a plain 3-termed list which holds [Lion count, Wolf Count, 
Sheep Count] :: [Int]

-- version 2
import Data.List

lionEatGoat :: [Int] -> [Int]
lionEatGoat [l,w,g] = [l-1,w+1,g-1]

lionEatWolf :: [Int] -> [Int]
lionEatWolf [l,w,g] = [l-1,w-1,g+1]

wolfEatGoat :: [Int] -> [Int]
wolfEatGoat [l,w,g] = [l+1,w-1,g-1]

meal :: [Int] -> [[Int]]
meal [] = []
meal f@[l, w, g]
   | endState f = []
   | l == 0 = (f:weg:(meal weg))
   | w == 0 = (f:leg:(meal leg))
   | g == 0 = (f:lew:(meal lew))
   | (l /= 0) && (w /= 0) && (g /= 0) =
     (f:leg:lew:weg:(meal leg ++ meal lew ++ meal weg))
   | otherwise = []
   where
     leg = lionEatGoat f
     lew = lionEatWolf f
     weg = wolfEatGoat f

endState :: [Int] -> Bool
endState [l,w,g] = if ((l == 0 && g == 0) ||
                        (l == 0 && w == 0) ||
                        (w == 0 && g == 0)) then
                      True
                    else
                      False
endStates = filter endState

main = do
   putStrLn $ show $ endStates $ meal [Lion 6, Wolf 55, Goat 17]

This is still extremely slow, without the program ever terminating.

Can someone please tell me what I am doing wrong.

-Elric
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/beginners/attachments/20140607/eac8d220/attachment.html>


More information about the Beginners mailing list