99 questions/Solutions/19

From HaskellWiki
< 99 questions‎ | Solutions
Revision as of 20:35, 23 May 2021 by Anphung (talk | contribs) (Remove solution that doesn't work)
(diff) ← Older revision | Latest revision (diff) | Newer revision → (diff)
Jump to navigation Jump to search
The printable version is no longer supported and may have rendering errors. Please update your browser bookmarks and please use the default browser print function instead.

(**) Rotate a list N places to the left.

Hint: Use the predefined functions length and (++).

rotate [] _ = []
rotate xs 0 = xs
rotate (x:xs) (n+1) = rotate (xs ++ [x]) n
rotate xs n = rotate xs (length xs + n)

(Note that this solution uses n+k-patterns which are removed from Haskell 2010.)

There are two separate cases:

  • If n > 0, move the first element to the end of the list n times.
  • If n < 0, convert the problem to the equivalent problem for n > 0 by adding the list's length to n.

or using cycle:

rotate xs n = take len . drop (n `mod` len) . cycle $ xs
    where len = length xs

or using list comprehension (only works for sequential increasing elements):

rotate :: (Enum a) => [a] -> Int -> [a]
rotate xs n = [(f n) .. last xs] ++ [head xs .. (f (n-1))]
              where f k = xs !! (k `mod` length xs)

or without mod:

rotate xs n = take (length xs) $ drop (length xs + n) $ cycle xs

or

rotate xs n = if n >= 0 then
                  drop n xs ++ take n xs
              else let l = ((length xs) + n) in
                  drop l xs ++ take l xs

or

rotate xs n | n >= 0 = drop n xs ++ take n xs
            | n < 0 = drop len xs ++ take len xs
                      where len = n+length xs

or calculate the position at first:

rotate xs n = let i = if n < 0 then length xs + n else n
              in drop i xs ++ take i xs

or

rotate xs n = drop nn xs ++ take nn xs
    where 
      nn = n `mod` length xs

Using a simple splitAt trick

rotate xs n
    | n < 0 = rotate xs (n+len)
    | n > len = rotate xs (n-len)
    | otherwise = let (f,s) = splitAt n xs in s ++ f
    where len = length xs

A much simpler solution without using length that is very similar to the first solution:

rotate :: [a] -> Int -> [a]
rotate [] _ = []
rotate x 0 = x
rotate x y
  | y > 0 = rotate (tail x ++ [head x]) (y-1)
  | otherwise = rotate (last x : init x) (y+1)

Here's another solution without using length. If the order of the arguments is reversed so that the integer comes before the list, then it is possible to define rotation by n as rotation by (n-1) followed by rotation by 1 recursively (with suitable modifications to support negative rotations). This leads to the following solution:

rotate :: [a] -> Int -> [a]
rotate xs n = rot n xs
    where rot 0 = id
          rot 1 = \xs -> case xs of [] -> []; xs -> tail xs ++ [head xs]
          rot (-1) = \xs -> case xs of [] -> []; xs -> (last xs):init xs
          rot n
              | n > 0 = (rot (n-1)).(rot 1)
              | n < 0 = (rot (n+1)).(rot (-1))