Lions, Wolves and Goats

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-... 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

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-... 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

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
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-... 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

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
mailto: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-... > 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 mailto:Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

I tried a set-based solution and it can process ~1600 items in 25 seconds
on this i7. Seems really slow compared to the times posted here:
http://unriskinsight.blogspot.co.at/2014/06/fast-functional-goats-lions-and-...
I'm curious if anyone spots any major flaw. If not, I'll profile it tonight
-- I can't afford to spend more time on this at work
Tim
On Fri, Jun 13, 2014 at 8:54 AM, Elric
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
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-... 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 listBeginners@haskell.orghttp://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Oops, I forgot the gist location.
https://gist.github.com/anonymous/99bc650c41e07364764c
I tried a set-based solution and it can process ~1600 items in 25 seconds
on this i7. Seems really slow compared to the times posted here:
http://unriskinsight.blogspot.co.at/2014/06/fast-functional-goats-lions-and-...
I'm curious if anyone spots any major flaw. If not, I'll profile it tonight
-- I can't afford to spend more time on this at work
On Mon, Jun 16, 2014 at 4:15 PM, Tim Perry
I tried a set-based solution and it can process ~1600 items in 25 seconds on this i7. Seems really slow compared to the times posted here:
http://unriskinsight.blogspot.co.at/2014/06/fast-functional-goats-lions-and-...
I'm curious if anyone spots any major flaw. If not, I'll profile it tonight -- I can't afford to spend more time on this at work
Tim
On Fri, Jun 13, 2014 at 8:54 AM, Elric
wrote: 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
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-... 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 listBeginners@haskell.orghttp://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Thank You Ariis, I was using nub in a wrong way, like so: 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 = nub $ meal $ ionEatGoat f lew = nub $ meal $ lionEatWolf f weg = nub $ meal $ wolfEatGoat f After looking at your solution, I realized I was essentially generating every possible state, and THEN trying to remove the duplicates, whereas in your solution at each step you remove possible duplicates states of the forest and propagate to the next step only from there. Thank You, Praveen On 06/08/2014 02:33 AM, Francesco Ariis 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-... 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

Elric
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./
...
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.
For one, you don't appear to be removing duplicates from the search set resulting in a blow-up in your search space.
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]
Your problem here isn't the use of ADTs, it's the use of lists. Why not instead define a forest as follows? data Forest = Forest { wolfs, lions, goats :: !Int } Note how I used a strictness annotation !Int here to ensure that the compiler unboxes these members (at least with GHC >= 7.8), which is almost certainly what you want in this case. Anyways, I took a quick stab at the problem myself. My approach can be found here[1]. Performance isn't great (a bit better than Javascript) but then again the code is pretty much as naive as one could get. I'm sure things could be improved. Cheers, - Ben [1] https://gist.github.com/anonymous/e4a2ccd8df05255d5ed5

Are there any good tutorials on understanding space complexity for haskell programs? My current approach of "waiting for it to crash" by being out of memory, doesn't really seem like good engineering practice. However, I have not found a source that gives me any proactive insight into what should be avoided. Most of what I have read only helps to solve the problem "after the fact". How do we design programs that avoid those problems from the beginning? Any pointers? Thanks, Dimitri

I found the beginning of Parallel and Concurrent Programming in Haskell particularly enlightening: http://chimera.labs.oreilly.com/books/1230000000929/ch02.html#sec_par-eval-w... After reading that, Haskell's evaluation strategy finally clicked for me. Now I can much more easily spot and fix these sorts of errors before even running them for the most part. On Mon, Jun 9, 2014 at 10:01 PM, Dimitri DeFigueiredo < defigueiredo@ucdavis.edu> wrote:
Are there any good tutorials on understanding space complexity for haskell programs?
My current approach of "waiting for it to crash" by being out of memory, doesn't really seem like good engineering practice. However, I have not found a source that gives me any proactive insight into what should be avoided. Most of what I have read only helps to solve the problem "after the fact". How do we design programs that avoid those problems from the beginning? Any pointers?
Thanks,
Dimitri _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Thanks Bob. Following your previous comment on this list, I read chapter 2 and really liked it, but I feel it was only scratching the surface. The example bug of implementing 'sum' using 'foldl' was insightful, but I'm sure 'foldl (+)' is not the only circumstance where laziness builds up large data structures unnecessarily and I'm afraid of recursion now. Are there more insights peppered throughout the book? Or other good pointers you know? Thanks again! Dimitri Em 09/06/14 23:21, Bob Ippolito escreveu:
I found the beginning of Parallel and Concurrent Programming in Haskell particularly enlightening: http://chimera.labs.oreilly.com/books/1230000000929/ch02.html#sec_par-eval-w...
After reading that, Haskell's evaluation strategy finally clicked for me. Now I can much more easily spot and fix these sorts of errors before even running them for the most part.
On Mon, Jun 9, 2014 at 10:01 PM, Dimitri DeFigueiredo
mailto:defigueiredo@ucdavis.edu> wrote: Are there any good tutorials on understanding space complexity for haskell programs?
My current approach of "waiting for it to crash" by being out of memory, doesn't really seem like good engineering practice. However, I have not found a source that gives me any proactive insight into what should be avoided. Most of what I have read only helps to solve the problem "after the fact". How do we design programs that avoid those problems from the beginning? Any pointers?
Thanks,
Dimitri _______________________________________________ Beginners mailing list Beginners@haskell.org mailto:Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

I don't recall too much more in the book about strictness, but it's a great read nonetheless. The one thing it could do a better job of covering is how types defined with data and newtype differ, and how to use strict fields in data types. It does give an explanation of how to implement NFData in terms of seq, but you can often get away with simply defining strict data types. Some of that is in here, but there isn't a lot of explanation: http://www.haskell.org/haskellwiki/Performance/Data_types I honestly don't recall where I picked up all that, it might've just been from reading parts of the Haskell Report or RWH. https://www.haskell.org/onlinereport/haskell2010/haskellch4.html#x10-680004.... http://book.realworldhaskell.org/read/profiling-and-optimization.html I would recommend trying to understand the general case, not to look for specific examples of what not to do because you'll never find them all :) Ultimately it all boils down to following the pattern matching of constructors (since that's what forces evaluation to happen) and you should assume that Haskell is going to be as lazy as it possibly can (ignore what the optimizer *might* do). The special cases are seq, newtype, and strict fields. On Mon, Jun 9, 2014 at 10:32 PM, Dimitri DeFigueiredo < defigueiredo@ucdavis.edu> wrote:
Thanks Bob.
Following your previous comment on this list, I read chapter 2 and really liked it, but I feel it was only scratching the surface. The example bug of implementing 'sum' using 'foldl' was insightful, but I'm sure 'foldl (+)' is not the only circumstance where laziness builds up large data structures unnecessarily and I'm afraid of recursion now. Are there more insights peppered throughout the book? Or other good pointers you know?
Thanks again!
Dimitri
Em 09/06/14 23:21, Bob Ippolito escreveu:
I found the beginning of Parallel and Concurrent Programming in Haskell particularly enlightening:
http://chimera.labs.oreilly.com/books/1230000000929/ch02.html#sec_par-eval-w...
After reading that, Haskell's evaluation strategy finally clicked for me. Now I can much more easily spot and fix these sorts of errors before even running them for the most part.
On Mon, Jun 9, 2014 at 10:01 PM, Dimitri DeFigueiredo < defigueiredo@ucdavis.edu> wrote:
Are there any good tutorials on understanding space complexity for haskell programs?
My current approach of "waiting for it to crash" by being out of memory, doesn't really seem like good engineering practice. However, I have not found a source that gives me any proactive insight into what should be avoided. Most of what I have read only helps to solve the problem "after the fact". How do we design programs that avoid those problems from the beginning? Any pointers?
Thanks,
Dimitri _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing listBeginners@haskell.orghttp://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Tue, Jun 10, 2014 at 12:01 PM, Dimitri DeFigueiredo < defigueiredo@ucdavis.edu> wrote:
My current approach of "waiting for it to crash" by being out of memory, doesn't really seem like good engineering practice
Have you tried the graphical profiling tools? And looked up RWH's chapter on profiling and optimization? Don's answer here is a widely cited resource: http://stackoverflow.com/questions/3276240/tools-for-analyzing-performance-o... -- Kim-Ee

Dimitri DeFigueiredo wrote:
Are there any good tutorials on understanding space complexity for haskell programs?
My current approach of "waiting for it to crash" by being out of memory, doesn't really seem like good engineering practice. However, I have not found a source that gives me any proactive insight into what should be avoided. Most of what I have read only helps to solve the problem "after the fact". How do we design programs that avoid those problems from the beginning? Any pointers?
Lazy evaluation makes it difficult to reason about space usage -- it's not compositional anymore. However, I have found the following technique, dubbed "space invariants", to be very helpful: http://apfelmus.nfshost.com/blog/2013/08/21-space-invariants.html The main idea is that because it is impossible to trace lazy evaluation in detail, we have to use invariants. In particular, we can attach bounds on space usage to semantic meaning. Example: "If this container with 5 elements is in WHNF, then it will use only as much space as the 5 elements." (This invariant seems banal, but the point is that lazy evaluation does not preserve it.) (WHNF means "weak head normal form", i.e. the expression has been evaluated to the outermost constructor.) Best regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

Thanks for the links. The guidance on your blog post is exactly the kind of analysis I was looking for. Dimitri Em 10/06/14 06:20, Heinrich Apfelmus escreveu:
Dimitri DeFigueiredo wrote:
Are there any good tutorials on understanding space complexity for haskell programs?
My current approach of "waiting for it to crash" by being out of memory, doesn't really seem like good engineering practice. However, I have not found a source that gives me any proactive insight into what should be avoided. Most of what I have read only helps to solve the problem "after the fact". How do we design programs that avoid those problems from the beginning? Any pointers?
Lazy evaluation makes it difficult to reason about space usage -- it's not compositional anymore. However, I have found the following technique, dubbed "space invariants", to be very helpful:
http://apfelmus.nfshost.com/blog/2013/08/21-space-invariants.html
The main idea is that because it is impossible to trace lazy evaluation in detail, we have to use invariants. In particular, we can attach bounds on space usage to semantic meaning. Example:
"If this container with 5 elements is in WHNF, then it will use only as much space as the 5 elements."
(This invariant seems banal, but the point is that lazy evaluation does not preserve it.)
(WHNF means "weak head normal form", i.e. the expression has been evaluated to the outermost constructor.)
Best regards, Heinrich Apfelmus
-- http://apfelmus.nfshost.com
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Thank You Ben, Your solution is really neat. I was trying to create the infix 'eat' function when I was thinking of implementing this in Haskell. But I completely forgot about being able to use the Record syntax to do this. I am not sure about the purpose of !Int, but that is something for me to read more and learn :) Thank You, Elric On 06/08/2014 04:52 PM, Ben Gamari wrote:
Elric
writes: 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./
...
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.
For one, you don't appear to be removing duplicates from the search set resulting in a blow-up in your search space.
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]
Your problem here isn't the use of ADTs, it's the use of lists. Why not instead define a forest as follows?
data Forest = Forest { wolfs, lions, goats :: !Int }
Note how I used a strictness annotation !Int here to ensure that the compiler unboxes these members (at least with GHC >= 7.8), which is almost certainly what you want in this case.
Anyways, I took a quick stab at the problem myself. My approach can be found here[1]. Performance isn't great (a bit better than Javascript) but then again the code is pretty much as naive as one could get. I'm sure things could be improved.
Cheers,
- Ben
participants (8)
-
Ben Gamari
-
Bob Ippolito
-
Dimitri DeFigueiredo
-
Elric
-
Francesco Ariis
-
Heinrich Apfelmus
-
Kim-Ee Yeoh
-
Tim Perry