Why not do something like this instead?

untab [] = []
untab xs = head : untab (drop 1 tail)
   where (head, tail) = break (== '\t') xs

BTW, going the extra step through unfoldr seems unnecessary to me - is
there any special reason to prefer unfolds over simple recursive
functions here? (Of course, you do get rid of the explicit recursive
call to untab - but in turn you have to run it all through unfoldr..)

Another, more pointless way is:

untab [] = []
untab xs = uncurry (:) $ second (untab . drop 1) $ break (== '\t') xs

(needs the additional import of Control.Arrow to get second)

On 6/11/07, Jules Bean <[EMAIL PROTECTED]> wrote:
Olivier Boudry wrote:
> Hi all,
>
> I'm trying to write a untab function that would split a string on tabs
> and return a list. Code is here.
>
> import Data.List (break, unfoldr)
> import Data.Char (String)
>
> untab :: String -> [String]
> untab s = unfoldr untab' s
>
> untab' :: String -> Maybe (String, String)
> untab' s | s == "" = Nothing
>         | otherwise = Just (h, ts)
>         where (h, t:ts) = break (== '\t') s
>
> This code raises an exception when handling the last portion of the
> string. Break returns a ("something", "") and t:ts cannot match on "".


untab' [] = Nothing
untab' s  = Just (h , drop 1 t)
   where (h,t) = break (== '\t') s
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

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

Reply via email to