Why is there no splitBy in the list module?

Donald Bruce Stewart dons at cse.unsw.edu.au
Wed Jul 12 08:12:39 EDT 2006


maeder:
> Simon Marlow schrieb:
> > Would someone like to make a concrete proposal (with code!) for 2-3
> > functions we could reasonably add to Data.List?
> 
> Here is my proposal that is consistent with Data.PackedString and
> "lines" (i.e a final delimiter is ignored -- by extra code)

I was thinking of Data.ByteString, but no matter.

I'ved added some QuickChecks, and suggest changing splitWith to splitBy,
following the other List functions with explicit predicates, sortBy,
groupBy, minimumBy, ...

Looks like a nice, simple minimal change that could be done.


-- | The 'splitBy' function takes a predicate and splits the input
-- list at each element which satisfies the predicate.
splitBy :: (a -> Bool) -> [a] -> [[a]]
splitBy p s =
    case s of
      [] -> []
      _  -> let (l, r) = break p s in
            case r of
                _ : t@(_:_) -> l : splitBy p t
                _             -> [l]

-- | The 'split' function splits the input list on each occurrence of
-- the given element.
split :: Eq a => a -> [a] -> [[a]]
split c = splitBy (== c)


------------------------------------------------------------------------
--
-- QuickChecks

module Data.Split where

import Data.List
import Data.Char
import Test.QuickCheck
import Test.QuickCheck.Batch

prop_lines_split xs = 
    lines xs == split '\n' xs

prop_words_split xs = 
    words xs == split ' ' xs

test_split = runTests "split" defOpt
        [ run prop_lines_split
        , run prop_words_split
        ]

instance Arbitrary Char where
    arbitrary     = choose (minBound, maxBound)
    coarbitrary c = variant (ord c `rem` 4)


More information about the Libraries mailing list