How to double iterator in FP style: pairing list into (n, n + k)

I thought I was decent enough at FP… until I met this problem.
While skimming through an algorithmic problem repo, I found an interesting one.
The crux of the problem was “pairing a list into (n, n + k) without duplicates”. (assumed to be possible for given inputs)

For example, given a list [1, 3, 4, 6, 7, 10, 12, 15] and k = 3,
we’d obtain [(1, 4), (3, 6), (7, 10), (12, 15)]. Quite a tricky one.

In an imperative paradigm, you might sort the list,
and then maintain a secondary index for right-found along with the main index.
To illustrate,

  • encounter 1, put it in. [(1, 4)], right-found at 0
  • encounter 3, put it in. [(1, 4), (3, 6)], right-found at 0
  • encounter 4. 0th left is 1, 4 = 1 + 3. 1’s right-counterpart found, right-found at 1
  • encounter 6. 1th left is 3, 6 = 3 + 3. 3’s right-counterpart found, right-found at 2
  • encounter 7. not a right-counterpart, so put it in.
    [(1, 4), (3, 6), (7, 10)], right-found at 3
  • (goes on like this)

I feel ashamed of incapability to come up with a functional solution for this one. How should I solve this problem in functional paradigm?

Can you explain the problem a bit more?

I don’t understand how [1, 3, 4, 6, 7, 10, 12, 15] can yield [(1, 4), (3, 6), (7, 10), (12, 15)]. Are the n and n+k indices in the list or actual values?

If it is the latter, then I would expect (1,3) to be the first element of the result as that fits the pattern (n, n + k) where n = 1 and k = 2. But that seems too simple and doesn’t really fit the description “pairing a list into …”.

If it is the former, then I would expect the last two elements of the result to be (7,12) and (10,15).

Sorry, I am bad at explaining this. (n, n+k) are actual values.
Notice that 4 = 1 + 3, 6 = 3 + 3, 10 = 7 + 3, 15 = 12 + 3. So these are the disjoint pairs with difference 3.

Ah, but then k = 3 right?

Wait. So it was a typo :stuck_out_tongue: Let me fix that real quick! EDIT: Fixed into k = 3

Here’s my first stab at this problem:

f k xs = map (\x -> (x, x + k)) (filter (\x -> (x + k) `elem` xs) xs)

Although that is probably not very efficient and it silently gives a wrong answer if the precondition is not satisfied, e.g. f 3 [1,4,7] = [(1,4),(4,7)].

Edit: Oh wait, does it need to be able to solve inputs like this: f 3 [1,4,7,10]? That will also fail with this implementation.

Yep, [1, 4, 7, 10] is definitely one of the possible inputs.

Here’s my second stab:

f k = go [] where
  go _ [] = []
  go [] (x:xs) = go [x] xs
  go ys@(y:ys') (x:xs)
    | x == y + k = (y, x) : go ys' xs
    | otherwise = go (ys ++ [x]) xs

You can speed this up by using a Data.Sequence for ys and especially that ys ++ [x] part.

Edit: (this assumes that the input is sorted)

Oh. I roughly thought of this way, but I was not acknowledging it as a FP solution. It looked too imperative to me. (Observe how y here acts like a state, I think it is never duplicated)
However, now I see that this counts as a FP solution.

I totally agree that this isn’t really very declarative. It is definitely still functional, but I also would prefer a higher level solution.

1 Like

Any idea on a nice declarative solution?

Here’s a higher level solution, but it is a lot slower:

import Data.List (nubBy)
import Data.Function (on)

tupleToList (x, y) = [x, y]

f k xs = withoutDuplicates [(x,y) | x <- xs, y <- xs, y == x + k]
  where
    withoutDuplicates = nubBy ((\xs ys -> hasDuplicates (xs ++ ys)) `on` tupleToList)
    hasDuplicates xs = nub xs /= xs

I’d say this is almost a direct formalization of your “pairing a list into (n, n + k) without duplicates” description.

2 Likes

Personally I think that non-mutating “imperative” solutions are perfectly functional. I like using Haskell as a better imperative language.

3 Likes

Even after the edit to k = 3, I don’t think the problem is well-defined:

Why does the solution prefer (3, 6) in the answer, as opposed to rejecting that in favour of (6, 9) to avoid duplicate 6 somewhere?

Is there something about preferring the lower of a clashing pair? Is there something about expecting the given list to be in ascending sequence, and preferring pairs generated from elements more to the left?

1 Like

Well, 9 is not in the input list, so that is not available for pairing. And in general I think it is impossible for an ambiguity to occur due to this. E.g. if you have [1,4,7,10] and k = 3 you are forced to return [(1,4),(7,10)], because there is no solution that has the element (4,7). And the input [1,4,7] does not satisfy the precondition.

Maybe the piece of info you’re missing is that every element in the input must be used exactly once and no extra numbers may be added?

1 Like

I hate making assumptions about the validity of input data. Especially input in Lists (which are not sets, and are not guaranteed ascending): really it’s a shame there are so many beginners’ exercise using only Lists; Haskell is no longer Lisp with bells on; early in an intro you should be introduced to more appropriate data structures (Data.Set would be my go-to here).

However, I’ve assumed for the exercise:

  • the input list is not necessarily ascending;
  • it is not necessarily a set (duplicate elements allowed);
  • it is not necessarily possible to pair up all the elements exhaustively

See the deviant tests.

inList = [1, 3, 4, 6, 7, 10, 12, 15]

rawPairs k xs@(_: ys@(_:_)) = [(x, y) | x <- xs, y <- ys, x+k == y]

filterDups _ [] = []
filterDups xy@(_,y) xys@(xy'@(x',_): xys')
               | y == x'    = filterTail
--             | y <  x'    = xys               -- optimisation, assumes ascending
               | otherwise  = xy' : filterTail
           where filterTail = filterDups xy xys'


nonDupPairs k xs = go $ rawPairs k xs
    where go []         = []
          go (xy : xys) = xy : go (filterDups xy xys)


{-  -- tests
nonDupPairs 3 inList
===> [(1,4),(3,6),(7,10),(12,15)]

nonDupPairs 3 [1,4,7]
===> [(1,4)]

nonDupPairs 3 [4,1,4,7]
===> [(4,7),(1,4)]

nonDupPairs 3 [4,1]
===> []
nonDupPairs 3 [7,4,1]
===> [(1,4)]

nonDupPairs 3 [1,5,8,10,14]
===> [(5,8)]
nonDupPairs 3 [1,5,6,7,8,11,15]
===> [(5,8)]
nonDupPairs 3 [1,5,9,10,14]
===> []

-}

The test with [4,1] produces nothing, because of the y <- ys optimisation in the List comprehension. Changing that to y <- xs, as @jaror’s List comprehension, does then yield [(1,4)].

“You sort the list, and then …”

Can’t speak to efficiency, but this is quite readable.

f _ [] = []
f n (x:xs)
  | v `elem` xs = (x, v) : f n (filter (/= v) xs)
  | otherwise = f n xs
  where v = n + x

I expect there’s a really clean recursion scheme formulation, but I’d have to go stare at the docs for an hour to produce it. :smiley: There’s probably some easy performance wins to wring out of some of the existing solutions with a little discrimination or witherable.

2 Likes

Yeah: both your elem and filter are scanning the tail looking for the same condition – and filter scans the whole tail even after finding v. Similarly, the approaches generating the Cartesian product (via List comprehension) “and then” filtering, are scanning by multiple passes and appending. But we know that for element x there is at most one k+x; and it’s at most k positions beyond x in the list; and if we’ve found it, there’s no need to scan beyond that point in the List. (Assuming the List is indeed a set in ascending sequence.)

import Data.Set as Set

viaSetPairs k xs = go $ Set.fromList xs        -- could be 'fromDistinctAscList', if we're sure it is
       where  go s
                | size s <= 1                 =             [] 
                | otherwise = case Set.deleteFindMin s of
                    (x, s') | member x_k s'   -> (x, x_k) : go (delete x_k s')
                            | otherwise       ->            go s'
                        where x_k = x+k

Set.member goes straight to x+k by binary chop (if it’s there); similarly Set.delete. (We could do better: deleteMemberMaybe :: Ord a => a -> Set a -> Maybe (Set a) (if it existed) could return in one pass Just s'' with the member deleted, or Nothing if it’s not there.)

I guess the o.p. won’t like the smell of imperativism, especially the nasty stench of destructive update.

Oh, that’s quite good. Do you think it could be done in one pass with alterF? I was trying to work out something nicer that leaned on Maybe to do the hard work and avoid the double scan, but I exhausted my before-bed nerd snipe time. :smiley: