Thank You Bob,

I learnt quite a bit from your solution. I have been restricting myself to Lists so far. I think I will have to start exploring other data structures like Sets in Haskell as well. :)

Thank You,
Elric

On 06/08/2014 03:41 PM, Bob Ippolito wrote:
Here's another approach that more closely models what's going on in the C++ version. I defined an ordNub rather than using nub as nub is O(n^2) as it only requires Eq.

https://gist.github.com/etrepum/5bfedc8bbe576f89fe09

import qualified Data.Set as S
import Data.List (partition)
import System.Environment (getArgs)

data LWG = LWG { _lion, _wolf, _goat :: {-# UNPACK #-} !Int }
     deriving (Show, Ord, Eq)

lionEatGoat, lionEatWolf, wolfEatGoat :: LWG -> LWG
lionEatGoat (LWG l w g) = LWG (l - 1) (w + 1) (g - 1)
lionEatWolf (LWG l w g) = LWG (l - 1) (w - 1) (g + 1)
wolfEatGoat (LWG l w g) = LWG (l + 1) (w - 1) (g - 1)

stableState :: LWG -> Bool
stableState (LWG l w g) = length (filter (==0) [l, w, g]) >= 2

validState :: LWG -> Bool
validState (LWG l w g) = all (>=0) [l, w, g]

possibleMeals :: LWG -> [LWG]
possibleMeals state =
  filter validState .
  map ($ state) $ [lionEatGoat, lionEatWolf, wolfEatGoat]

ordNub :: Ord a => [a] -> [a]
ordNub = S.toList . S.fromList

endStates :: [LWG] -> [LWG]
endStates states
  | not (null stable)   = stable
  | not (null unstable) = endStates (concatMap possibleMeals unstable)
  | otherwise           = []
  where (stable, unstable) = partition stableState (ordNub states)
  
main :: IO ()
main = do
  [l, w, g] <- map read `fmap` getArgs
  mapM_ print . endStates $ [LWG l w g]



On Sat, Jun 7, 2014 at 11:33 PM, Francesco Ariis <fa-ml@ariis.it> wrote:
On Sat, Jun 07, 2014 at 08:04:09PM -0400, Elric wrote:
> Hi,
>
> 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.
>

Hello Elric,
    I gave a go at the problem, managed to get a result (23).
I attach the .hs file (not my best Haskell, but hopefully clear enough).

The crucial point in my solution lies in this lines:

    carnage :: [Forest] -> [Forest]
    let wodup = nub aa in
    -- etc. etc.

Which means after every iteration I call |nub| on my list of possible
states; nub is a function from |Data.List| and removes duplicate
elements from a list.

If I omit that nub call, the program doesn't reach a solution (as it
is computationally quite inefficient). I think that's the problem
with your versions.

Let me know if this helps







_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners




_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners