99 questions/Solutions/9
< 99 questions | Solutions
Jump to navigation
Jump to search
(**) Pack consecutive duplicates of list elements into sublists.
If a list contains repeated elements they should be placed in separate sublists.
pack (x:xs) = let (first,rest) = span (==x) xs
in (x:first) : pack rest
pack [] = []
This is implemented as group
in Data.List
.
A more verbose solution is
pack :: Eq a => [a] -> [[a]]
pack [] = []
pack (x:xs) = (x:first) : pack rest
where
getReps [] = ([], [])
getReps (y:ys)
| y == x = let (f,r) = getReps ys in (y:f, r)
| otherwise = ([], (y:ys))
(first,rest) = getReps xs
Similarly, using splitAt
and findIndex
:
pack :: Eq a => [a] -> [[a]]
pack [] = []
pack (x:xs) = (x:reps) : (pack rest)
where
(reps, rest) = maybe (xs,[]) (\i -> splitAt i xs) (findIndex (/=x) xs)
Another solution using takeWhile
and dropWhile
:
pack :: (Eq a) => [a] -> [[a]]
pack [] = []
pack (x:xs) = (x : takeWhile (==x) xs) : pack (dropWhile (==x) xs)
Or we can use foldr
to implement this:
pack :: (Eq a) => [a] -> [[a]]
pack = foldr func []
where func x [] = [[x]]
func x (y:xs) =
if x == (head y) then ((x:y):xs) else ([x]:y:xs)
A simple solution:
pack :: (Eq a) => [a] -> [[a]]
pack [] = []
pack [x] = [[x]]
pack (x:xs) = if x `elem` (head (pack xs))
then (x:(head (pack xs))):(tail (pack xs))
else [x]:(pack xs)
A simpler solution which is similar to the takeWhile/dropWhile solution, but in one step.
pack :: (Eq a) => [a] -> [[a]]
pack (x:xs) = (x:xs') : (pack ys)
where (xs',ys) = break (/=x) xs
pack [] = []