Am 05.01.2012 11:57, schrieb Steve Horne:
[...]
groupCut :: (x -> x -> Bool) -> [x] -> [[x]]
[...]

How about a break function that respects an escape character (1. arg) (and drops the delimiter - 2. arg) and use this function for unfolding?

import Data.List

break' :: (a -> Bool) -> (a -> Bool) -> [a] -> ([a], [a])
break' e p l = case l of
  [] -> (l, [])
  c : r
    | p c -> ([], r)
    | e c -> case r of
      [] -> (l, [])
      d : t -> let (f, s) = break' e p t in
        (c : d : f, s)
    | otherwise -> let (f, s) = break' e p r in
        (c : f, s)

split' :: (a -> Bool) -> (a -> Bool) -> [a] -> [[a]]
split' e p = unfoldr $ \ l -> if null l then Nothing else
  Just $ break' e p l

*Main> split' (== '\r') (== '\n') "string1\nstring2\r\nstring3\nstring4"
["string1","string2\r\nstring3","string4"]

C.

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to