[Haskell-cafe] String rewriting

2010-05-20 Thread Roly Perera
Hi,

I'm looking for a simple way to rewrite strings according to simple
composable rules like:

replace "_" by "\\(\\hole\\)"
replace "-n" where n matches an integer by "^{n}"

so that I can import some pretty-printed output into a LaTeX alltt
environment. I'm guessing that this nice functional stream
transformation problem has been solved thousands of times. Could
anyone point me to a simple package that would do this for me?

many thanks,
Roly
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] String rewriting

2010-05-20 Thread Daniel Fischer
On Thursday 20 May 2010 15:49:59, Roly Perera wrote:
> Hi,
>
> I'm looking for a simple way to rewrite strings according to simple
> composable rules like:
>
> replace "_" by "\\(\\hole\\)"
> replace "-n" where n matches an integer by "^{n}"
>
> so that I can import some pretty-printed output into a LaTeX alltt
> environment. I'm guessing that this nice functional stream
> transformation problem has been solved thousands of times. Could
> anyone point me to a simple package that would do this for me?
>
> many thanks,
> Roly

Hmm, I'm a little surprised that the Regex libraries don't seem to provide 
replacing functions (at least my short search didn't find any).

Still, shouldn't be too hard to use one of their matching functions to 
write a replacing function.

Or start from scratch:

repFun :: (String -> Maybe (String, String)) -> (String -> String)
   -> String -> String
repFun test repl str@(c:cs)
= case test str of
Nothing -> c : repFun test repl cs
Just (match, rest) -> repl match ++ repFun test repl rest
repFun _ _ [] = []

-- uses:

repFun uscore (const "\\(\\hole\\)")
where
uscore ('_':rest) = Just ("_",rest)
uscore _ = Nothing

repFun dashDigs expo
where
dashDigs ('-':rest@(d:_))
| isDigit d = Just (span isDigit rest)
dashDigs _ = Nothing
expo digs = '^':'{':digs ++ "}"
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] String rewriting

2010-05-20 Thread Stephen Tetley
Hello Roly

As Daniel Fischer says, there might not be a library to do this.

I would be tempted to start with a simple parser combinator library
and do something with the 'answer type' so it supports string
rewriting.

Dave Bayer was working with one in this thread on Beginners:
http://www.haskell.org/pipermail/beginners/2010-February/003399.html

See my comment here:
http://www.haskell.org/pipermail/beginners/2010-February/003433.html

Best wishes

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


Re: [Haskell-cafe] String rewriting

2010-05-21 Thread Uwe Schmidt
Hi Roly,

> I'm looking for a simple way to rewrite strings according to simple
> composable rules like:
>
> replace "_" by "\\(\\hole\\)"
> replace "-n" where n matches an integer by "^{n}"
>
> so that I can import some pretty-printed output into a LaTeX alltt
> environment. I'm guessing that this nice functional stream
> transformation problem has been solved thousands of times. Could
> anyone point me to a simple package that would do this for me?

you can try the regex-xmlschema package

on Hackage: http://hackage.haskell.org/package/regex-xmlschema-0.1.3

-- --

import Text.Regex.XMLSchema.String

replace1 :: String -> String
replace1 = sed (const "\\(\\hole\\)") "_"

replace1 :: String -> String
replace2 = sed (\ x -> "^{" ++ x ++ "}") "-[0-9]+"

-- ---

will solve your task

Regards,

  Uwe

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