
Multi-line regular expressions are indeed powerful. Rob Pike has a good
paper on it available at:
http://doc.cat-v.org/bell_labs/structural_regexps/se.pdfhttp://code.google.com/p/sregex/
http://code.google.com/p/sregex/Explains how line-based regular
expressions are limiting etc.
The Sam and Acme editors supported these.
Python does too now.
http://code.google.com/p/sregex/
On Wed, Nov 4, 2009 at 6:17 AM, kenny lu
Michael,
Here is how I do it.
module Main where
import Text.Regex.Posix.ByteString import Data.Maybe import qualified Data.ByteString.Char8 as S
text = S.pack "11\n abcd \n22" p = S.pack "11\n(.*)\n22"
main :: IO () main = do { (Right pat) <- compile compExtended execBlank p ; res <- regexec pat text ; case res of { (Right (Just (_,_,_,m))) -> putStrLn (show m) ; _ -> putStrLn "not matched." } }
You may swap out ByteString with String, PCRE should be similar, too.
Regards, Kenny
On Wed, Nov 4, 2009 at 2:04 PM, Michael Mossey
wrote: kenny lu wrote:
Hi Michael,
Could you give an example of what patterns you want to write?
Regards, Kenny
Something like
text = "11\n abcd \n22" answer = text =~ "11.*22" :: <various possibilities>
and have it find the entire string. The default behavior is to stop matching when it encounters a newline. There is mention in the Text.Regex.Posix docs of a flag to control this behavior, but it is not easy to figure out from the docs how to provide flags. The left-hand side of the =~ is a very complex type.
_______________________________________________ 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