Find two items in the list, order them in their place

I am writing a function that takes a list and two elements that the list can contain. The function should return two elements in a structure that sorts them according to their occurrence in the list.

So, for the number, we'll have something like this:

xs = [4,6,3,2,1,8]
f (3,1) --> (Just 3, Just 1)
f (1,3) --> (Just 3, Just 1)
f (9,1) --> (Just 1, Nothing)
f (9,9) --> (Nothing, Nothing)

      

etc.

I used tuples there, as I'm really only interested in these two values ​​instead of an arbitrary number. But if there are reasons, modeling it as a list would be fine as well.

Anyway, here I used the function:

f :: Eq a => [a] -> (a, a) -> (Maybe a, Maybe a) 
f xs (a, b) = foldl g (Nothing, Nothing) xs  where
  g (Nothing, Nothing) x | x == a            = (Just a, Nothing)
  g (Nothing, Nothing) x | x == b            = (Just b, Nothing)
  g (Just a', Nothing) x | a' == a && x == b = (Just a, Just b)
  g (Just b', Nothing) x | b' == b && x == a = (Just b, Just a)
  g m x = m

      

Its a job, but I think there are quite a few templates out there, it seems to be error prone. So, does anyone have a better abstraction for the problem?

+3


source to share


3 answers


If you want to reduce the number of pattern matches, then it's best to never pass a pair (Maybe a, Maybe a)

recursively and a pattern match on it. You can simply split your function into two recursive functions where the first functions detect the first element and call the second function on the other. This can be done as follows:

f :: Eq a => (a, a) -> [a] -> (Maybe a, Maybe a)
f (a, b) = goFirst
  where
    goFirst []    = (Nothing, Nothing)
    goFirst (x:xs)
      | x == a    = (Just a, goSecond b xs)
      | x == b    = (Just b, goSecond a xs)
      | otherwise = goFirst xs

    goSecond _ [] = Nothing
    goSecond y (x:xs)
      | x == y    = Just y
      | otherwise = goSecond y xs

      

It's not as short and sleek as you might wish, but it's readable, fast (I want to add that you should never use a function foldl

), and less error prone.

If you're looking for some abstraction, you might look at a First

monoid with a pair of monoids. Using a monoid instance for a datatype First

, you can start with something like this:

import Data.Bifunctor (bimap)
import Data.Monoid    (First (..), mconcat)

g :: Eq a => (a, a) -> [a] -> (Maybe a, Maybe a)
g (a, b) = bimap getFirst getFirst . mconcat . map fMapper
  where
    fMapper x
      | x == a    = (First (Just a), mempty)
      | x == b    = (mempty, First (Just b))
      | otherwise = mempty

      



While this function doesn't do exactly what you want:

ghci> let xs = [4,6,3,2,1,8]
ghci> g (3, 1) xs
(Just 3,Just 1)
ghci> g (1, 3) xs
(Just 1,Just 3)

      

To achieve the original goal with this approach, you can add indices to each element and then sort the pairs under the index First

by the indices, but this solution is scary and ugly. Using a First

monoid is tempting, but I don't know how it can be used elegantly here.

But you can combine ideas from the first and second solutions:

import Data.Bool   (bool)
import Data.Monoid (First (..))

h :: Eq a => (a, a) -> [a] -> (Maybe a, Maybe a)
h (a, b) = goFirst
  where
    goFirst []    = (Nothing, Nothing)
    goFirst (x:xs)
      | x == a    = (Just a, goSecond b xs)
      | x == b    = (Just b, goSecond a xs)
      | otherwise = goFirst xs

    goSecond y = getFirst . foldMap (bool mempty (First (Just y)) . (== y))

      

+1


source


Here is one possible solution with the following type of lists:

f :: Eq a => [a] -> [a] -> [Maybe a]

      

Name the list to search haystack

and items to search needles

. First, we can search haystack

for each needle

and return a pair of values ​​and the index where it was found, if any, using findIndex

:

findIndices needles haystack =
  [ (needle, findIndex (== needle) haystack)
  | needle <- needles
  ]

findIndices [1, 3] xs == [(1, Just 4), (3, Just 2)]

      

(Note that this always uses the index of the first occurrence - I'm not sure if this is what you want. You can expand this to a warehouse that removes each occurrence as it finds it.)

Then sort this list by index:

sortBy (comparing snd) [(1, Just 4), (3, Just 2)]
==
[(3, Just 2), (1, Just 4)]

      

And finally, extract the value for each index present using (<$) :: Functor f => a -> f b -> f a

:

[value <$ mIndex | (value, mIndex) <- [(3, Just 2), (1, Just 4)]]
==
[Just 3, Just 1]

      

( x <$ f

equivalent const x <$> f

.)

But when we try this on the input where some elements aren't found, we get the wrong result where Nothing

comes at the beginning and not at the end:

findIndices [9, 1] xs == [(9, Nothing), (1, Just 4)]

sortBy (comparing snd) [(9, Nothing), (1, Just 4)]
==
[(9, Nothing), (1, Just 4)]

      



This is due to the fact that it Nothing

is considered less than any value Just

. Since we want the opposite, we can reverse the sort order Maybe

using Down

newtype from Data.Ord

by passing Down . snd

instead snd

as a comparator:

sortBy (comparing (Down . snd)) [(9, Nothing), (1, Just 4)]
==
[(1, Just 4), (9, Nothing)]

      

But this also reverses the sort order of the indices themselves, which we don't want:

sortBy (comparing (Down . snd)) [(1, Just 4), (3, Just 2)]
==
[(1, Just 4), (3, Just 2)]

      

So we can just add more Down

around the indices:

findIndices needles haystack =
  [ (needle, Down <$> findIndex (== needle) haystack)
  | needle <- needles
  ]

sortBy (comparing Down) [Just (Down 2), Nothing, Just (Down 1)]
==
[Just (Down 1), Just (Down 2), Nothing]

sortBy (comparing (Down . snd))
  [(1, Down (Just 4)), (3, Down (Just 2))]
==
[(3, Down (Just 2)), (1, Down (Just 4))]

      

And finally, all together:

f :: (Eq a) => [a] -> [a] -> [Maybe a]
f needles haystack =
  [ value <$ index
  | (value, index) <- sortBy (comparing (Down . snd))
    [ (needle, Down <$> findIndex (== needle) haystack)
    | needle <- needles
    ]
  ]

f [1, 3] xs == [Just 3, Just 1]
f [3, 1] xs == [Just 3, Just 1]
f [1, 9] xs == [Just 1, Nothing]
f [9, 9] xs == [Nothing, Nothing]

      

Or, excluding lists and with shorter names:

f :: (Eq a) => [a] -> [a] -> [Maybe a]
f ns hs
  = map (\ (v, i) -> v <$ i)
  $ sortBy (comparing (Down . snd))
  $ map (\ n -> (n, Down <$> findIndex (== n) hs)) ns

      

\ (v, i) -> v <$ i

can also be written as uncurry (<$)

, but it can be a little cryptic if you're not used to the dotless style. Also, if you don't care about Nothing

s, you can use mapMaybe

instead map

by changing the return type from [Maybe a]

to [a]

.

+1


source


I don't know how much better you think this, but you can do some things that make more use of the list functions.

At first I thought about filtering out unnecessary items first and grouping:

f :: Eq a => [a] -> (a,a) -> (Maybe a, Maybe a)
f xs (a, b) =
  case (map head . group . filter (`elem` [a,b])) xs of
    [] -> (Nothing, Nothing)
    [c] -> (Just c, Nothing)
    (c:d:_) -> (Just c, Just d)

      

But this is not the same as your implementation, for example f [8,9,9] (9,9)

, so you need a special case if that's a case you care about.

Another way dropWhile

::

f' :: Eq a => [a] -> (a,a) -> (Maybe a, Maybe a)
f' xs (a, b) =
  case dropWhile (`notElem` [a, b]) xs of
    [] -> (Nothing, Nothing)
    (y:ys) -> (Just y, next)
      where
        next = case dropWhile (/=other) ys of
                 [] -> Nothing
                 (z:_) -> Just z
        other = if y == a then b else a

      

And the inner case is really simple find

, so it can be simplified a little more:

f'' :: Eq a => [a] -> (a,a) -> (Maybe a, Maybe a)
f'' xs (a, b) =
  case dropWhile (`notElem` [a, b]) xs of
    [] -> (Nothing, Nothing)
    (y:ys) -> (Just y, find (==other) ys)
      where
        other = if y == a then b else a

      

Note: these functions never return a form result (Nothing, Just _)

. This suggests that the return type Maybe (a, Maybe a)

could be better. Or a custom type of type None | One a | Two a a

.

Alternatively, we could generalize to a list version that allows as many target values ​​as you like. This makes it nice to unwrap:

f''' :: Eq a => [a] -> [a] -> [a]
f''' xs ts = unfoldr g (xs, ts)
  where
    g (ys, us) = case dropWhile (`notElem` us) ys of
                   [] -> Nothing
                   (z:zs) -> Just (z, (zs, delete z us))

      

Which works like this:

λ> f''' [4,2,5,3,1] [1,2,3]
[2,3,1]
λ> f''' [4,2,5,3,1] [1,2,6]
[2,1]
λ> f''' [7,9,8,9] [9,9]
[9,9]

      

I'm almost reinventing intersect

here, but not quite. This has a behavior that we want to keep the order from the first list, but this is not the same on duplicates - eg. intersect [4,2,2,5] [1,2]

is [2,2]

.

0


source







All Articles