[Haskell-beginners] Einstein's Problem

Daniel Fischer daniel.is.fischer at web.de
Wed Dec 23 22:09:26 EST 2009


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.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/beginners/attachments/20091223/b0ef4b6b/attachment-0001.html


More information about the Beginners mailing list