The whole point here is to evaluate
both lists inside the list comprehension only once. There is a
very simple way to accomplish this:
[q:qs | let qss = queens' (k-1), q <- [1..n], qs <- qss]
Here, queens' (k-1) is only evaluated once, and is shared for all
q.
(Note: If queens' (k-1) is polymorphic (which it is) and you use
-XNoMonomorphismRestriction, then you better add a type annotation
to qss to ensure sharing.)
Adrian
On 2013/01/30 1:51, Doaitse Swierstra wrote:
From the conclusion that both programs compute the same result it
can be concluded that the fact that you have made use of a list
comprehension has forced you to make a choice which should not
matter, i.e. the order in which to place the generators. This
should be apparent from your code.
My approach is such a situation is to "define your own
generator" (assuming here that isSafe needs both its
parameters):
pl `x` ql = [ (p,q) | p <-pl, q <- ql]
queens3 n = map reverse $ queens' n
where queens' 0 = [[]]
queens' k = [q:qs | (qs, q) <- queens'
(k-1) `x` [1..n], isSafe q qs]
isSafe try qs = not (try `elem` qs || sameDiag
try qs)
sameDiag try qs = any (\(colDist,q) -> abs (try
- q) == colDist) $ zip [1..] qs
Of course you can make more refined versions of `x`, which
perform all kinds of fair enumeration, but that is not the main
point here. It is the fact that the parameters to `x` are only
evaluated once which matters here.
Doaitse
Hi Cafe,
I have two programs for the same problem
"Eight queens problem",
My two grograms only has little
difference, but the performance, this is my solution:
-- solution
1------------------------------------------------------------
queens1 :: Int -> [[Int]]
queens1 n = map reverse $ queens' n
where queens' 0 = [[]]
queens' k = [q:qs | q <- [1..n],
qs <- queens' (k-1), isSafe q qs]
isSafe try qs = not (try `elem` qs ||
sameDiag try qs)
sameDiag try qs = any (λ(colDist, q)
-> abs (try - q) == colDist) $ zip [1..] qs
-- solution
2--------------------------------------------------------------
queens2 :: Int -> [[Int]]
queens2 n = map reverse $ queens' n
where queens' 0 = [[]]
queens' k = [q:qs | qs <-
queens' (k-1), q <- [1..n], isSafe q qs]
isSafe try qs = not (try `elem` qs ||
sameDiag try qs)
sameDiag try qs = any (λ(colDist,q)
-> abs (try - q) == colDist) $ zip [1..] qs
the performance difference is: (set :set
+s in ghci)
*Main> length (queens1 8)
92
(287.85 secs, 66177031160 bytes)
*Main> length (queens2 8)
92
(0.07 secs, 17047968 bytes)
*Main>
The only different in the two program
is in the first is "q <- [1..n], qs <-
queens' (k-1)," and the second is "qs <-
queens' (k-1), q <- [1..n]".
Does sequence in list comprehansion
matter? And why?
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe