
Hi all, I've been working hard at trying to solve Einstein's problem (http://www.davar.net/MATH/PROBLEMS/EINSTEIN.HTM) if an efficient manner using Haskell. I have posted my solution here: http://haskell.pastebin.com/m3ff1973a This exercise has been a real eye opener for me, especially for learning to work with the Maybe and List monads. I'm looking for suggestions for making the "test" function nicer. In order to make my solution fast, I generate my test cases incrementally, thereby elimating most of the cases early on. However the function looks funny (deeply nested). I'm also open to any comments about making better use of the different Haskell idioms. Thanks a lot, Patrick -- ===================== Patrick LeBoutillier Rosemère, Québec, Canada

Am Mittwoch 23 Dezember 2009 20:46:51 schrieb Patrick LeBoutillier:
Hi all,
I've been working hard at trying to solve Einstein's problem (http://www.davar.net/MATH/PROBLEMS/EINSTEIN.HTM) if an efficient manner using Haskell.
I have posted my solution here: http://haskell.pastebin.com/m3ff1973a
This exercise has been a real eye opener for me, especially for learning to work with the Maybe and List monads.
I'm looking for suggestions for making the "test" function nicer. In order to make my solution fast, I generate my test cases incrementally, thereby elimating most of the cases early on. However the function looks funny (deeply nested).
Instead of if checkStreet s then ... else [], use Control.Monad.guard: test = do ds <- drinkPerms ns <- nationPerms let s = Street $ makeHouses ds ns [] [] [] guard (checkStreet s) ss <- smokePerms ...
I'm also open to any comments about making better use of the different Haskell idioms.
There is a function permutations in Data.List, you can use that instead of writing your own (except if you want the permutations in a different order). xxxPerms = permutationsOf [toEnum 0 .. toEnum 4] :: [[XXX]] isn't particularly nice, better give the first and last constructor of each type or define allPerms :: (Enum a, Bounded a) => [[a]] allPerms = permutationsOf [minBound .. maxBound] and derive also Bounded for your types. nationPerms = filter rule1 $ permutationsOf [toEnum 0 .. toEnum 4] :: [[Nation]] where rule1 ns = (ns !! 0) == Norway is very inefficient, make that nationPerms = map (Norway:) $ permutationsOf [England .. Denmark] (yes, it's not so terrible for only five items, still it made me wince). Similar for drinkPerms. checkCond (f,c) h = fmap (== c) (f h) ~> checkCond (f,c) = fmap (== c) . f
Thanks a lot,
Patrick

Daniel,
Instead of
if checkStreet s then ... else [], use Control.Monad.guard:
test = do ds <- drinkPerms ns <- nationPerms let s = Street $ makeHouses ds ns [] [] [] guard (checkStreet s) ss <- smokePerms ...
Excellent. That really cleans it up!
I'm also open to any comments about making better use of the different Haskell idioms.
There is a function permutations in Data.List, you can use that instead of writing your own (except if you want the permutations in a different order). xxxPerms = permutationsOf [toEnum 0 .. toEnum 4] :: [[XXX]] isn't particularly nice, better give the first and last constructor of each type or define allPerms :: (Enum a, Bounded a) => [[a]] allPerms = permutationsOf [minBound .. maxBound] and derive also Bounded for your types.
Great! I tried to do something a bit like that using typeclasses, but I got lost along the way.. :( I love how allPerms generates the correct permutations using type inference!
nationPerms = filter rule1 $ permutationsOf [toEnum 0 .. toEnum 4] :: [[Nation]] where rule1 ns = (ns !! 0) == Norway
is very inefficient, make that nationPerms = map (Norway:) $ permutationsOf [England .. Denmark] (yes, it's not so terrible for only five items, still it made me wince). Similar for drinkPerms.
How do you do it with drinkPerms? The constant element is in the middle (with Nations it seems easier since it's the first one).
checkCond (f,c) h = fmap (== c) (f h) ~> checkCond (f,c) = fmap (== c) . f
Ok. Hopefully someday these patterns will be obvious... Thanks a lot, Patrick -- ===================== Patrick LeBoutillier Rosemère, Québec, Canada

Am Donnerstag 24 Dezember 2009 03:30:54 schrieb Patrick LeBoutillier:
How do you do it with drinkPerms? The constant element is in the middle (with Nations it seems easier since it's the first one).
insertAt :: Int -> a -> [a] -> [a] insertAt k x xs = case splitAt k xs of (front,back) -> front ++ x:back drinkPerms = map (insertAt 2 Milk) $ permutations [Coffee, Tea, Water, Beer] Another possibility to have x inserted at a fixed position in all permutations of xs is to use do (fs,bs) <- picks k xs pf <- permutations fs pb <- permutations bs return (pf ++ x:pb) which has the advantage that the permutations of the front are shared (if the back is longer than the front, it might be better to swap lines 2 and 3 to share the permutations of the back) and avoids the many splits. picks :: Int -> [a] -> [([a],[a])] picks k xs | k == 0 = [([],xs)] | k == l = [(xs,[])] | k > l = [] | otherwise = pickHelper l k xs where l = length xs pickHelper s t yys@(y:ys) | s == t = [(yys,[])] | otherwise = [(y:zs,ws) | (zs,ws) <- pickHelper (s-1) (t-1) ys] ++ [(zs,y:ws) | (zs,ws) <- pickHelper (s-1) t ys] It's by far not as nice as keeping the first element fixed, but you can easily keep more than one position fixed. And when you have a couple more items, this approach is enormously faster than filtering.
participants (2)
-
Daniel Fischer
-
Patrick LeBoutillier