[Haskell-cafe] multi-line regex

kenny lu haskellmail at gmail.com
Wed Nov 4 09:17:30 EST 2009


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 <mpm at alumni.caltech.edu>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 at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20091104/9554dc36/attachment.html


More information about the Haskell-Cafe mailing list