Swap two elements in a list by its indices
There are several working answers here, but I thought that a more idiomatic haskell example would be useful.
In essence, we zip an infinite sequence of natural numbers with the original list to include ordering information in the first element of the resulting pairs, and then we use a simple right fold (catamorphism) to consume the list from the right and create a new list, but this time with the correct elements swapped. We finally extract all the second elements, discarding the first element containing the ordering.
The indexing in this case is zero-based (congruent with Haskell's typical indexes) and the pointers must be in range or you'll get an exception (this can be easily prevented if you change the resulting type to Maybe [a]).
swapTwo :: Int -> Int -> [a] -> [a]
swapTwo f s xs = map snd . foldr (\x a ->
if fst x == f then ys !! s : a
else if fst x == s then ys !! f : a
else x : a) [] $ ys
where ys = zip [0..] xs
And a single liner, doing the swap in just one pass (combining the functionality of the foldr and map into a zipWith):
swapTwo' f s xs = zipWith (\x y ->
if x == f then xs !! s
else if x == s then xs !! f
else y) [0..] xs
Haskell doesn't have such a function, mainly because it is a little bit un-functional. What are you actually trying to achieve?
You can implement your own version of it (maybe there is a more idiomatic way to write this). Note that I assume that i < j
, but it would be trivial to extend the function to correctly handle the other cases:
swapElementsAt :: Int -> Int -> [a] -> [a]
swapElementsAt i j xs = let elemI = xs !! i
elemJ = xs !! j
left = take i xs
middle = take (j - i - 1) (drop (i + 1) xs)
right = drop (j + 1) xs
in left ++ [elemJ] ++ middle ++ [elemI] ++ right
Warning: differential calculus. I don't intend this answer entirely seriously, as it's rather a sledgehammer nutcracking. But it's a sledgehammer I keep handy, so why not have some sport? Apart from the fact that it's probably rather more than the questioner wanted to know, for which I apologize. It's an attempt to dig out the deeper structure behind the sensible answers which have already been suggested.
The class of differentiable functors offers at least the following bits and pieces.
class (Functor f, Functor (D f)) => Diff (f :: * -> *) where
type D f :: * -> *
up :: (I :*: D f) :-> f
down :: f :-> (f :.: (I :*: D f))
I suppose I'd better unpack some of those definitions. They're basic kit for combining functors. This thing
type (f :-> g) = forall a. f a -> g a
abbreviates polymorphic function types for operations on containers.
Here are constant, identity, composition, sum and product for containers.
newtype K a x = K a deriving (Functor, Foldable, Traversable, Show)
newtype I x = I x deriving (Functor, Foldable, Traversable, Show)
newtype (f :.: g) x = C {unC :: f (g x)} deriving (Functor, Foldable, Traversable, Show)
data (f :+: g) x = L (f x) | R (g x) deriving (Functor, Foldable, Traversable, Show)
data (f :*: g) x = f x :*: g x deriving (Functor, Foldable, Traversable, Show)
D
computes the derivative of a functor by the usual rules of calculus. It tells us how to represent a one-hole context for an element. Let's read the types of those operations again.
up :: (I :*: D f) :-> f
says we can make a whole f
from the pair of one element and a context for that element in an f
. It's "up", because we're navigating upward in a hierarchical structure, focusing on the whole rather than one element.
down :: f :-> (f :.: (I :*: D f))
Meanwhile, we can decorate every element in a differentiable functor structure with its context, computing all the ways to go "down" to one element in particular.
I'll leave the Diff
instances for the basic components to the end of this answer. For lists we get
instance Diff [] where
type D [] = [] :*: []
up (I x :*: (xs :*: ys)) = xs ++ x : ys
down [] = C []
down (x : xs) = C ((I x :*: ([] :*: xs)) :
fmap (id *:* ((x :) *:* id)) (unC (down xs)))
where
(*:*) :: (f a -> f' a) -> (g a -> g' a) -> (f :*: g) a -> (f' :*: g') a
(ff' *:* gg') (f :*: g) = ff' f :*: gg' g
So, for example,
> unC (down [0,1,2])
[I 0 :*: ([] :*: [1,2]),I 1 :*: ([0] :*: [2]),I 2 :*: ([0,1] :*: [])]
picks out each element-in-context in turn.
If f
is also Foldable
, we get a generalized !!
operator...
getN :: (Diff f, Foldable f) => f x -> Int -> (I :*: D f) x
getN f n = foldMap (: []) (unC (down f)) !! n
...with the added bonus that we get the element's context as well as the element itself.
> getN "abcd" 2
I 'c' :*: ("ab" :*: "d")
> getN ((I "a" :*: I "b") :*: (I "c" :*: I "d")) 2
I "c" :*: R ((I "a" :*: I "b") :*: L (K () :*: I "d"))
If we want a functor to offer swapping of two elements, it had better be twice differentiable, and its derivative had better be foldable too. Here goes.
swapN :: (Diff f, Diff (D f), Foldable f, Foldable (D f)) =>
Int -> Int -> f x -> f x
swapN i j f = case compare i j of
{ LT -> go i j ; EQ -> f ; GT -> go j i } where
go i j = up (I y :*: up (I x :*: f'')) where
I x :*: f' = getN f i -- grab the left thing
I y :*: f'' = getN f' (j - 1) -- grab the right thing
It's now easy to grab two elements out and plug them back in the other way around. If we're numbering the positions, we just need to be careful about the way removing elements renumbers the positions.
> swapN 1 3 "abcde"
"adcbe"
> swapN 1 2 ((I "a" :*: I "b") :*: (I "c" :*: I "d"))
(I "a" :*: I "c") :*: (I "b" :*: I "d")
As ever, you don't have do dig down too far below a funny editing operation to find some differential structure at work.
For completeness. Here are the other instances involved in the above.
instance Diff (K a) where -- constants have zero derivative
type D (K a) = K Void
up (_ :*: K z) = absurd z
down (K a) = C (K a)
instance Diff I where -- identity has unit derivative
type D I = K ()
up (I x :*: K ()) = I x
down (I x) = C (I (I x :*: K ()))
instance (Diff f, Diff g) => Diff (f :+: g) where -- commute with +
type D (f :+: g) = D f :+: D g
up (I x :*: L f') = L (up (I x :*: f'))
up (I x :*: R g') = R (up (I x :*: g'))
down (L f) = C (L (fmap (id *:* L) (unC (down f))))
down (R g) = C (R (fmap (id *:* R) (unC (down g))))
instance (Diff f, Diff g) => Diff (f :*: g) where -- product rule
type D (f :*: g) = (D f :*: g) :+: (f :*: D g)
up (I x :*: (L (f' :*: g))) = up (I x :*: f') :*: g
up (I x :*: (R (f :*: g'))) = f :*: up (I x :*: g')
down (f :*: g) = C (fmap (id *:* (L . (:*: g))) (unC (down f))
:*: fmap (id *:* (R . (f :*:))) (unC (down g)))
instance (Diff f, Diff g) => Diff (f :.: g) where -- chain rule
type D (f :.: g) = (D f :.: g) :*: D g
up (I x :*: (C f'g :*: g')) = C (up (I (up (I x :*: g')) :*: f'g))
down (C fg) = C (C (fmap inner (unC (down fg)))) where
inner (I g :*: f'g) = fmap wrap (unC (down g)) where
wrap (I x :*: g') = I x :*: (C f'g :*: g')
That's how I solved it:
swapElementsAt :: Int -> Int -> [a] -> [a]
swapElementsAt a b list = list1 ++ [list !! b] ++ list2 ++ [list !! a] ++ list3
where list1 = take a list;
list2 = drop (succ a) (take b list);
list3 = drop (succ b) list
Here I used the convention that position 0 is the first. My function expects a<=b.
What I like most in my program is the line take a list
.
Edit: If you want to get more such cool lines, look at this code:
swapElementsAt :: Int -> Int -> [a] -> [a]
swapElementsAt a another list = list1 ++ [list !! another] ++ list2 ++ [list !! a] ++ list3
where list1 = take a list;
list2 = drop (succ a) (take another list);
list3 = drop (succ another) list