How to reorder a sublist efficiently?

This is for work (so a realworld problem) I have a few idea how tackle it but I though it make an interesting puzzle.

The problem is how given a list and a sublist of it given in a different order update the whole list so that the element of the sublsiy appear in the new order but the other elements stay in place.

Example f [1 2 3 45 6 7 8] [8 4 3] == [1 2 8 4 5 6 7 3] ?

Alternativley it can be (Eq a, Ord a) => [a] -> (a -> Bool) -> ([a] -> [a]) -> [a].

import Control.Monad.State.Strict
import Data.Set qualified as Set
import Data.Traversable

f xs ys0 = (`evalState` ys0) $ for xs $ \x -> do
  if x `Set.member` ysSet
     then do
       ~(y:ys) <- get
       put $! ys
       pure y
     else pure x
  where
    ysSet = Set.fromList ys0
2 Likes

That was quick. It took you less time to answer me than me to unserstand it. :slight_smile: .
That is a really interesting approach (even though it copies the tail if there is one).

Picking element in order (your ys state) works really well indeed. I rewrote using simple recursion (so I don’t have to import anything :wink: )

freezeOrder boxesInOrder boxes  =
  let inOrderSet = Set.fromList boxesInOrder
      go [] bs = bs
      go _ [] = []
      go (o:os) (b:bs) = 
                -- replace the current box with the first in boxesInOrder  if current
                -- box is part of the boxesInOrder
                if b `member` inOrderSet
                then o : go os bs
                else b : go os bs
  in go boxesInOrder boxes

(I could factorize the go os bs …)

1 Like