[Haskell-cafe] Separate a string into a list of strings

Jared Updike jupdike at gmail.com
Mon Jun 12 19:34:15 EDT 2006


Funny. I have a module called Useful.hs with some of these same sorts
of functions. (coming from Python where I used .split(',') and
.replace('\r', '') and such a lot):

------------------
module Useful where

import List ( intersperse, tails )
import Numeric ( readHex )

hex2num :: (Num a) => String -> a
hex2num s = let (result, _):_ = readHex s in result

toEnv s = map tuple (split ';' s)

tuple :: String -> (String, String)
tuple line = case split '=' line of
   a:b:_ -> (a,b)
   a:_   -> (a,"")
   _     -> ("","") -- not good, probably won't happen for my typical usage...

split       :: Char -> String -> [String]
split _ ""  =  []
split c s   =  let (l, s') = break (== c) s
                 in  l : case s' of
                           []      -> []
                           (_:s'') -> split c s''

beginsWith []       []     = True
beginsWith _        []     = True
beginsWith []       _      = False
beginsWith (a:aa)   (b:bb)
    | a == b               = aa `beginsWith` bb
    | otherwise            = False

dropping []     []     = []
dropping []     _      = []
dropping x      []     = x
dropping s@(a:aa) (b:bb) | a == b    = dropping aa bb
                         | otherwise = s

-- replace all occurrences of 'this' with 'that' in the string 'str'
-- like Python replace
replace _    _    []  = []
replace this that str
    | str `beginsWith` this = let after = (str `dropping` this)
                               in  that ++ replace this that after
    | otherwise             =
        let x:xs = str
          in x : replace this that xs

eat s = replace s ""

-- sometimes newlines get out of hand on the end of form POST submissions,
-- so trim all the end newlines and add a single newline
fixEndingNewlines = reverse . ('\n':) . dropWhile (=='\n') . reverse .
filter (/= '\r')

endsWith a b = beginsWith (reverse a) (reverse b)

a `contains` b = any (`beginsWith` b) $ tails a
------------------

  Jared.

On 6/12/06, Neil Mitchell <ndmitchell at gmail.com> wrote:
> Hi,
>
> I tend to use the module TextUtil (or Util.Text) from Yhc for these
> kind of string manipulations:
>
> http://www-users.cs.york.ac.uk/~malcolm/cgi-bin/darcsweb.cgi?r=yhc;a=headblob;f=/src/compiler98/Util/Text.hs
>
> separate = splitList ","
>
> I am currently thinking about making this module into a standalone
> library with some other useful functions, if people have any opinions
> on this then please let me know.
>
> Thanks
>
> Neil
>
>
> On 6/12/06, Sara Kenedy <sarakenedy at gmail.com> wrote:
> > Hi all,
> >
> > I want to write a function to separate a string into a list of strings
> > separated by commas.
> >
> > Example:
> > separate :: String -> [String]
> >
> > separate "Haskell, Haskell, and Haskell" = ["Haskell", "Haskell", "and Haskell"]
> >
> > If anyone has some ideas, please share with me. Thanks.
> >
> > S.
> > _______________________________________________
> > Haskell-Cafe mailing list
> > Haskell-Cafe at haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


-- 
http://www.updike.org/~jared/
reverse ")-:"


More information about the Haskell-Cafe mailing list