
On 火, 2007-6月-05, at 02:54, Greg Fitzgerald wrote:
rotating the fourth element 2 positions would result in: [1, 2, 4, 3, 5] Seems odd. Should that be [4,1,2,3,5]?
Yes, I meant to use the 5 element in my second example. Sorry for the confusion.
Is there an idomatic way to handle both of these cases in a function? Generally people like to see your attempt at a solution before giving the idomatic one so that they are sure it's not a homework question. What do you have so far?
Yeah, I only wish I had gone to a school that would be forward thinking enough to each FP. ;-) Here is my version: rotate :: Array Integer Card -> Integer -> Integer -> Array Integer Card rotate a i n | i <= u - n = a // [(i, a ! (i + 1)), (i + 1, a ! (i + 2)), (i + 2, a ! i)] | otherwise = a // zip [l..u] (h ++ [a ! i] ++ filter (not . (== (a ! i))) t) where (l, u) = bounds a (h, t) = splitAt (fromInteger ((i - u) + n)) $ elems a This function is part of my implementation of the Solitaire encryption algorithm, so that is why I have the reference to a Card data type. This does what I want, and seems basically idiomatic, but perhaps it could be better. Thanks, Kevin

Kevin,
Below is my attempt, which hopefully is bad enough to get this thread
rolling for you. :)
It rotates the 'i'th element 'n' times by swapping the 'i'th element with
the element to its right 'n' times. It looks horribly inefficient to me,
but is fairly simple and only depends on the prelude. I think it ought to
be possible to reduce this to a very simple function with no recursion and
one strategic splitAt, but I've run out of time to work more on it. :(
rotate :: [a] -> Int -> Int -> [a]
rotate xs i n = snd (iterate swap (i,xs) !! n)
swap :: (Int, [a]) -> (Int, [a])
swap (i,xs)
| i == length xs - 1 = (0, last xs : init (tail xs) ++ [head xs])
| otherwise = (i + 1, start ++ [right,left] ++ end)
where
(start, left:right:end) = splitAt i xs
-Greg
On 6/4/07, kevin birch
On 火, 2007-6月-05, at 02:54, Greg Fitzgerald wrote:
rotating the fourth element 2 positions would result in: [1, 2, 4, 3, 5]
Seems odd. Should that be [4,1,2,3,5]?
Yes, I meant to use the 5 element in my second example. Sorry for the confusion.
Is there an idomatic way to handle both of these cases in a function? Generally people like to see your attempt at a solution before giving the idomatic one so that they are sure it's not a homework question. What do you have so far?
Yeah, I only wish I had gone to a school that would be forward thinking enough to each FP. ;-)
Here is my version:
rotate :: Array Integer Card -> Integer -> Integer -> Array Integer Card rotate a i n | i <= u - n = a // [(i, a ! (i + 1)), (i + 1, a ! (i + 2)), (i + 2, a ! i)] | otherwise = a // zip [l..u] (h ++ [a ! i] ++ filter (not . (== (a ! i))) t) where (l, u) = bounds a (h, t) = splitAt (fromInteger ((i - u) + n)) $ elems a
This function is part of my implementation of the Solitaire encryption algorithm, so that is why I have the reference to a Card data type. This does what I want, and seems basically idiomatic, but perhaps it could be better.
Thanks, Kevin

Here is my list-based version. There are redundant calls to get the length of the same list, but I didn't feel like factoring them out (call it an exercise for the reader). The key to its simplicity is that shifting an element is a similarity transform of shifting the first element, with pre- and post list rotation. The shift just maps (h:xs++ys) to xs++(h:ys). Rotating a list is easy with the drop . cycle pattern, and shares the list up to the point of rotation (when brought in from cycle 2 to end the list). Dan module RotateList where import Control.Arrow((&&&)) rotateList :: Int -> [a] -> [a] rotateList offset = uncurry take . (length &&& uncurry drop . (mod offset . length &&& cycle)) shiftElem :: Int -> [a] -> [a] shiftElem _ [] = [] shiftElem offset (h:t) = a ++ (h:b) where (a,b) = splitAt ((offset-1) `mod` (length t) + 1) t -- rotateElem is a similarity transform of shiftElem rotateElem :: Int -> Int -> [a] -> [a] rotateElem start offset = rotateList (negate start) . shiftElem offset . rotateList start kevin birch wrote:
On 火, 2007-6月-05, at 02:54, Greg Fitzgerald wrote:
rotating the fourth element 2 positions would result in: [1, 2, 4, 3, 5] Seems odd. Should that be [4,1,2,3,5]?
Yes, I meant to use the 5 element in my second example. Sorry for the confusion.
Is there an idomatic way to handle both of these cases in a function? Generally people like to see your attempt at a solution before giving the idomatic one so that they are sure it's not a homework question. What do you have so far?
Yeah, I only wish I had gone to a school that would be forward thinking enough to each FP. ;-)
Here is my version:
rotate :: Array Integer Card -> Integer -> Integer -> Array Integer Card rotate a i n | i <= u - n = a // [(i, a ! (i + 1)), (i + 1, a ! (i + 2)), (i + 2, a ! i)] | otherwise = a // zip [l..u] (h ++ [a ! i] ++ filter (not . (== (a ! i))) t) where (l, u) = bounds a (h, t) = splitAt (fromInteger ((i - u) + n)) $ elems a
This function is part of my implementation of the Solitaire encryption algorithm, so that is why I have the reference to a Card data type. This does what I want, and seems basically idiomatic, but perhaps it could be better.
Thanks, Kevin
------------------------------------------------------------------------
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (3)
-
Dan Weston
-
Greg Fitzgerald
-
kevin birch