Put adjacent elements in List into Tuples

会有一股神秘感。 提交于 2021-02-16 15:23:16

问题


Given a List of elements:

xs = [a, b, c, d, ... z]

where a, b, c etc are placeholders for arbitrary values. I want to implement a function adjacents :: [a] -> [(a, a)] that produces

adjacentValues = [(a, b), (b, c), (c, d), ... (y, z)]

In Haskell, a recursive definition is reasonably concise:

adjacents :: [a] -> [(a, a)]
adjacents (x:xs) = (x, head xs) : adjacents xs
adjacents [] = []

Purescript is a little more verbose:

adjacents :: forall a. List a -> List (Tuple a a)
adjacents list = case uncons list of 
    Nothing -> []
    Just {head: x, tail: xs} -> case head xs of
                                     Just next -> Tuple x next : adjacents xs
                                     Nothing -> []

Is there a way to express adjacents without explicit recursion (using a fold)?


Disclaimer: This question has both Purescript and Haskell tags because I want to open it to a broader audience. I reckon an answer not to depend on haskells lazy-evaluation semantics, and therefore to be valid in both languages.


回答1:


In Haskell, without explicit recursion, you can zip a list with its tail.

   let a = [1,2,3,4,5,6,7,8,9,0]

   a `zip` tail a

   => [(1,2),(2,3),(3,4),(4,5),(5,6),(6,7),(7,8),(8,9),(9,0)]



回答2:


Purescript solution for completeness sake:

adjacent :: forall n. List n -> List (Tuple n n)
adjacent list = zip list $ fromMaybe empty $ tail list

can be expressed more elegantly as:

adjacent :: forall n. List n -> List (Tuple n n)
adjacent list = zip list $ drop 1 list



回答3:


For the sake of illustration (the zip-based solutions are definitely nicer), here is your explicitly recursive Haskell solution written as an unfold. I have golfed it into an one-liner for no particular reason.

{-# LANGUAGE LambdaCase #-}

import Data.List (unfoldr)

adjacent :: [a] -> [(a, a)]
adjacent = unfoldr (\case { x:y:ys -> Just ((x, y), ys); _ -> Nothing })

(Note that the pattern matches here handle lists with an odd number of elements without crashing.)




回答4:


Since we've seen zip and unfoldr, we should have one using foldr:

adjacent :: [a] -> [(a,a)]
adjacent xs = foldr go (const []) xs Nothing
  where
    go a r Nothing = r (Just a)
    go a r (Just prev) = (prev, a) : r (Just a)

And now, because every toy problem deserves an over-engineered solution, here's what you could use to get double-sided list fusion:

import GHC.Exts (build)

adjacent :: [a] -> [(a,a)]
adjacent xs = build $ \c nil ->
  let
    go a r Nothing = r (Just a)
    go a r (Just prev) = (prev, a) `c` r (Just a)
  in foldr go (const nil) xs Nothing
{-# INLINE adjacent #-}



回答5:


folding with state, where the state is the last paired item:

in Haskell:

import Data.List (mapAccumL)

adjacents :: [a] -> [(a, a)]
adjacents [] = []
adjacents (x:xs) = snd $ mapAccumL op x xs
    where
        op x y = (y, (x,y))


来源:https://stackoverflow.com/questions/49360890/put-adjacent-elements-in-list-into-tuples

易学教程内所有资源均来自网络或用户发布的内容,如有违反法律规定的内容欢迎反馈
该文章没有解决你所遇到的问题?点击提问,说说你的问题,让更多的人一起探讨吧!