Proposal (Trac ticket #3671): Add takeRec, genericTakeRec and spanRec to Data.List

Christian Maeder Christian.Maeder at dfki.de
Fri Nov 20 12:45:09 EST 2009


My proposal would be to add a function like

\begin{code}
replaceBy :: ([a] -> (b, [a])) -> [a] -> [b]
replaceBy splt l = case l of
  [] -> []
  _ -> let (ft, rt) = splt l in
    ft : replaceBy splt rt
\end{code}

that takes a function "splt" that splits a non-empty list and returns a
shorter list as second component (to ensure termination).

I've used this function to implement a replace function (below), but the
simplest application is:

\begin{code}
splitAts :: Int -> [a] -> [[a]]
splitAts n | n > 0 = replaceBy (splitAt n)
\end{code}

or with Control.Applicative:

\begin{code}
breaks :: (a -> Bool) -> [a] -> [[a]]
breaks p = replaceBy $ second (drop 1) .  break p
\end{code}

This "breaks" function ignores a final separator!

breaks (',' ==) "123,456,,78" == ["123","456","","78"]
breaks (',' ==) "123,456,78," == ["123","456","78"]

groupBy could be implemented as follows:

\begin{code}
groupBy eq = replaceBy $ \ (h : r) -> first (h :) $ span (eq h) r
\end{code}

And given a function to split of a single "run", "runs" (with the same
type as groupBy) is simply:

\begin{code}
runs :: (a -> a -> Bool) -> [a] -> [[a]]
runs eq = replaceBy (run eq)

run :: (a -> a -> Bool) -> [a] -> ([a], [a])
run eq l = case l of
  x : r@(y : s) | eq x y -> first (x :) $ run eq r
  x : r -> ([x], r)
  [] -> ([], [])
\end{code}

My original application for replacing a substring by a special character
is defined by:

\begin{code}
replace :: Eq a => [a] -> a -> [a] -> [a]
replace sl@(_ : _) r = replaceBy $ \ l@(hd : tl) ->
  case stripPrefix sl l of
    Nothing -> (hd, tl)
    Just rt -> (r, rt)
\end{code}

Cheers Christian




More information about the Libraries mailing list