regex-posix-0.96.0.2: POSIX Backend for "Text.Regex" (regex-base)
Copyright(c) Chris Kuklewicz 2006
LicenseBSD-3-Clause
MaintainerAndreas Abel
Stabilitystable
Portabilitynon-portable (regex-base needs MPTC+FD)
Safe HaskellNone
LanguageHaskell2010

Text.Regex.Posix.String

Description

This provides String instances for RegexMaker and RegexLike based on Text.Regex.Posix.Wrap, and a (RegexContext Regex String String) instance.

To use these instance, you would normally import Text.Regex.Posix. You only need to import this module to use the medium level API of the compile, regexec, and execute functions. All of these report error by returning Left values instead of undefined or error or fail.

Synopsis

Types

data Regex Source #

A compiled regular expression.

Instances

Instances details
RegexLike Regex ByteString Source # 
Instance details

Defined in Text.Regex.Posix.ByteString

Methods

matchOnce :: Regex -> ByteString -> Maybe MatchArray #

matchAll :: Regex -> ByteString -> [MatchArray] #

matchCount :: Regex -> ByteString -> Int #

matchTest :: Regex -> ByteString -> Bool #

matchAllText :: Regex -> ByteString -> [MatchText ByteString] #

matchOnceText :: Regex -> ByteString -> Maybe (ByteString, MatchText ByteString, ByteString) #

RegexLike Regex ByteString Source # 
Instance details

Defined in Text.Regex.Posix.ByteString.Lazy

Methods

matchOnce :: Regex -> ByteString -> Maybe MatchArray #

matchAll :: Regex -> ByteString -> [MatchArray] #

matchCount :: Regex -> ByteString -> Int #

matchTest :: Regex -> ByteString -> Bool #

matchAllText :: Regex -> ByteString -> [MatchText ByteString] #

matchOnceText :: Regex -> ByteString -> Maybe (ByteString, MatchText ByteString, ByteString) #

RegexLike Regex String Source # 
Instance details

Defined in Text.Regex.Posix.String

Methods

matchOnce :: Regex -> String -> Maybe MatchArray #

matchAll :: Regex -> String -> [MatchArray] #

matchCount :: Regex -> String -> Int #

matchTest :: Regex -> String -> Bool #

matchAllText :: Regex -> String -> [MatchText String] #

matchOnceText :: Regex -> String -> Maybe (String, MatchText String, String) #

RegexContext Regex ByteString ByteString Source # 
Instance details

Defined in Text.Regex.Posix.ByteString

Methods

match :: Regex -> ByteString -> ByteString #

matchM :: MonadFail m => Regex -> ByteString -> m ByteString #

RegexContext Regex ByteString ByteString Source # 
Instance details

Defined in Text.Regex.Posix.ByteString.Lazy

Methods

match :: Regex -> ByteString -> ByteString #

matchM :: MonadFail m => Regex -> ByteString -> m ByteString #

RegexContext Regex String String Source # 
Instance details

Defined in Text.Regex.Posix.String

Methods

match :: Regex -> String -> String #

matchM :: MonadFail m => Regex -> String -> m String #

RegexOptions Regex CompOption ExecOption Source # 
Instance details

Defined in Text.Regex.Posix.Wrap

RegexMaker Regex CompOption ExecOption ByteString Source # 
Instance details

Defined in Text.Regex.Posix.ByteString

Methods

makeRegex :: ByteString -> Regex #

makeRegexOpts :: CompOption -> ExecOption -> ByteString -> Regex #

makeRegexM :: MonadFail m => ByteString -> m Regex #

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> ByteString -> m Regex #

RegexMaker Regex CompOption ExecOption ByteString Source # 
Instance details

Defined in Text.Regex.Posix.ByteString.Lazy

Methods

makeRegex :: ByteString -> Regex #

makeRegexOpts :: CompOption -> ExecOption -> ByteString -> Regex #

makeRegexM :: MonadFail m => ByteString -> m Regex #

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> ByteString -> m Regex #

RegexMaker Regex CompOption ExecOption String Source # 
Instance details

Defined in Text.Regex.Posix.String

Methods

makeRegex :: String -> Regex #

makeRegexOpts :: CompOption -> ExecOption -> String -> Regex #

makeRegexM :: MonadFail m => String -> m Regex #

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> String -> m Regex #

RegexMaker Regex CompOption ExecOption (Seq Char) Source # 
Instance details

Defined in Text.Regex.Posix.Sequence

Methods

makeRegex :: Seq Char -> Regex #

makeRegexOpts :: CompOption -> ExecOption -> Seq Char -> Regex #

makeRegexM :: MonadFail m => Seq Char -> m Regex #

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> Seq Char -> m Regex #

RegexLike Regex (Seq Char) Source # 
Instance details

Defined in Text.Regex.Posix.Sequence

Methods

matchOnce :: Regex -> Seq Char -> Maybe MatchArray #

matchAll :: Regex -> Seq Char -> [MatchArray] #

matchCount :: Regex -> Seq Char -> Int #

matchTest :: Regex -> Seq Char -> Bool #

matchAllText :: Regex -> Seq Char -> [MatchText (Seq Char)] #

matchOnceText :: Regex -> Seq Char -> Maybe (Seq Char, MatchText (Seq Char), Seq Char) #

RegexContext Regex (Seq Char) (Seq Char) Source # 
Instance details

Defined in Text.Regex.Posix.Sequence

Methods

match :: Regex -> Seq Char -> Seq Char #

matchM :: MonadFail m => Regex -> Seq Char -> m (Seq Char) #

type MatchOffset = Int #

type MatchLength = Int #

data ReturnCode Source #

ReturnCode is an enumerated CInt, corresponding to the error codes from man 3 regex:

  • retBadbr (REG_BADBR) invalid repetition count(s) in { }
  • retBadpat (REG_BADPAT) invalid regular expression
  • retBadrpt (REG_BADRPT) ?, *, or + operand invalid
  • retEcollate (REG_ECOLLATE) invalid collating element
  • retEctype (REG_ECTYPE) invalid character class
  • retEescape (REG_EESCAPE) \ applied to unescapable character
  • retEsubreg (REG_ESUBREG) invalid backreference number
  • retEbrack (REG_EBRACK) brackets [ ] not balanced
  • retEparen (REG_EPAREN) parentheses ( ) not balanced
  • retEbrace (REG_EBRACE) braces { } not balanced
  • retErange (REG_ERANGE) invalid character range in [ ]
  • retEspace (REG_ESPACE) ran out of memory
  • retNoMatch (REG_NOMATCH) The regexec() function failed to match

Instances

Instances details
Show ReturnCode Source # 
Instance details

Defined in Text.Regex.Posix.Wrap

Methods

showsPrec :: Int -> ReturnCode -> ShowS

show :: ReturnCode -> String

showList :: [ReturnCode] -> ShowS

Eq ReturnCode Source # 
Instance details

Defined in Text.Regex.Posix.Wrap

Methods

(==) :: ReturnCode -> ReturnCode -> Bool

(/=) :: ReturnCode -> ReturnCode -> Bool

type WrapError = (ReturnCode, String) Source #

The return code will be retOk when it is the Haskell wrapper and not the underlying library generating the error message.

Miscellaneous

Medium level API functions

compile Source #

Arguments

:: CompOption

Flags (summed together)

-> ExecOption

Flags (summed together)

-> String

The regular expression to compile (ASCII only, no null bytes)

-> IO (Either WrapError Regex)

Returns: the compiled regular expression

regexec Source #

Arguments

:: Regex

Compiled regular expression

-> String

String to match against

-> IO (Either WrapError (Maybe (String, String, String, [String])))

Returns: Nothing if the regex did not match the string, or:

  Just (everything before match,
        matched portion,
        everything after match,
        subexpression matches)

Matches a regular expression against a string

execute Source #

Arguments

:: Regex

Compiled regular expression

-> String

String to match against

-> IO (Either WrapError (Maybe (Array Int (MatchOffset, MatchLength))))

Returns: Nothing if the regex did not match the string, or:

  Just (array of offset length pairs)

Matches a regular expression against a string

Compilation options

newtype CompOption Source #

A bitmapped CInt containing options for compilation of regular expressions. Option values (and their man 3 regcomp names) are

  • compBlank which is a completely zero value for all the flags. This is also the blankCompOpt value.
  • compExtended (REG_EXTENDED) which can be set to use extended instead of basic regular expressions. This is set in the defaultCompOpt value.
  • compNewline (REG_NEWLINE) turns on newline sensitivity: The dot (.) and inverted set [^ ] never match newline, and ^ and $ anchors do match after and before newlines. This is set in the defaultCompOpt value.
  • compIgnoreCase (REG_ICASE) which can be set to match ignoring upper and lower distinctions.
  • compNoSub (REG_NOSUB) which turns off all information from matching except whether a match exists.

Constructors

CompOption CInt 

Instances

Instances details
Bits CompOption Source # 
Instance details

Defined in Text.Regex.Posix.Wrap

Num CompOption Source # 
Instance details

Defined in Text.Regex.Posix.Wrap

Show CompOption Source # 
Instance details

Defined in Text.Regex.Posix.Wrap

Methods

showsPrec :: Int -> CompOption -> ShowS

show :: CompOption -> String

showList :: [CompOption] -> ShowS

Eq CompOption Source # 
Instance details

Defined in Text.Regex.Posix.Wrap

Methods

(==) :: CompOption -> CompOption -> Bool

(/=) :: CompOption -> CompOption -> Bool

RegexOptions Regex CompOption ExecOption Source # 
Instance details

Defined in Text.Regex.Posix.Wrap

RegexMaker Regex CompOption ExecOption ByteString Source # 
Instance details

Defined in Text.Regex.Posix.ByteString

Methods

makeRegex :: ByteString -> Regex #

makeRegexOpts :: CompOption -> ExecOption -> ByteString -> Regex #

makeRegexM :: MonadFail m => ByteString -> m Regex #

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> ByteString -> m Regex #

RegexMaker Regex CompOption ExecOption ByteString Source # 
Instance details

Defined in Text.Regex.Posix.ByteString.Lazy

Methods

makeRegex :: ByteString -> Regex #

makeRegexOpts :: CompOption -> ExecOption -> ByteString -> Regex #

makeRegexM :: MonadFail m => ByteString -> m Regex #

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> ByteString -> m Regex #

RegexMaker Regex CompOption ExecOption String Source # 
Instance details

Defined in Text.Regex.Posix.String

Methods

makeRegex :: String -> Regex #

makeRegexOpts :: CompOption -> ExecOption -> String -> Regex #

makeRegexM :: MonadFail m => String -> m Regex #

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> String -> m Regex #

RegexMaker Regex CompOption ExecOption (Seq Char) Source # 
Instance details

Defined in Text.Regex.Posix.Sequence

Methods

makeRegex :: Seq Char -> Regex #

makeRegexOpts :: CompOption -> ExecOption -> Seq Char -> Regex #

makeRegexM :: MonadFail m => Seq Char -> m Regex #

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> Seq Char -> m Regex #

compBlank :: CompOption Source #

A completely zero value for all the flags. This is also the blankCompOpt value.

Execution options

newtype ExecOption Source #

A bitmapped CInt containing options for execution of compiled regular expressions. Option values (and their man 3 regexec names) are

  • execBlank which is a complete zero value for all the flags. This is the blankExecOpt value.
  • execNotBOL (REG_NOTBOL) can be set to prevent ^ from matching at the start of the input.
  • execNotEOL (REG_NOTEOL) can be set to prevent $ from matching at the end of the input (before the terminating NUL).

Constructors

ExecOption CInt 

Instances

Instances details
Bits ExecOption Source # 
Instance details

Defined in Text.Regex.Posix.Wrap

Num ExecOption Source # 
Instance details

Defined in Text.Regex.Posix.Wrap

Show ExecOption Source # 
Instance details

Defined in Text.Regex.Posix.Wrap

Methods

showsPrec :: Int -> ExecOption -> ShowS

show :: ExecOption -> String

showList :: [ExecOption] -> ShowS

Eq ExecOption Source # 
Instance details

Defined in Text.Regex.Posix.Wrap

Methods

(==) :: ExecOption -> ExecOption -> Bool

(/=) :: ExecOption -> ExecOption -> Bool

RegexOptions Regex CompOption ExecOption Source # 
Instance details

Defined in Text.Regex.Posix.Wrap

RegexMaker Regex CompOption ExecOption ByteString Source # 
Instance details

Defined in Text.Regex.Posix.ByteString

Methods

makeRegex :: ByteString -> Regex #

makeRegexOpts :: CompOption -> ExecOption -> ByteString -> Regex #

makeRegexM :: MonadFail m => ByteString -> m Regex #

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> ByteString -> m Regex #

RegexMaker Regex CompOption ExecOption ByteString Source # 
Instance details

Defined in Text.Regex.Posix.ByteString.Lazy

Methods

makeRegex :: ByteString -> Regex #

makeRegexOpts :: CompOption -> ExecOption -> ByteString -> Regex #

makeRegexM :: MonadFail m => ByteString -> m Regex #

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> ByteString -> m Regex #

RegexMaker Regex CompOption ExecOption String Source # 
Instance details

Defined in Text.Regex.Posix.String

Methods

makeRegex :: String -> Regex #

makeRegexOpts :: CompOption -> ExecOption -> String -> Regex #

makeRegexM :: MonadFail m => String -> m Regex #

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> String -> m Regex #

RegexMaker Regex CompOption ExecOption (Seq Char) Source # 
Instance details

Defined in Text.Regex.Posix.Sequence

Methods

makeRegex :: Seq Char -> Regex #

makeRegexOpts :: CompOption -> ExecOption -> Seq Char -> Regex #

makeRegexM :: MonadFail m => Seq Char -> m Regex #

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> Seq Char -> m Regex #

execBlank :: ExecOption Source #

A completely zero value for all the flags. This is also the blankExecOpt value.

Orphan instances

RegexLike Regex String Source # 
Instance details

Methods

matchOnce :: Regex -> String -> Maybe MatchArray #

matchAll :: Regex -> String -> [MatchArray] #

matchCount :: Regex -> String -> Int #

matchTest :: Regex -> String -> Bool #

matchAllText :: Regex -> String -> [MatchText String] #

matchOnceText :: Regex -> String -> Maybe (String, MatchText String, String) #

RegexContext Regex String String Source # 
Instance details

Methods

match :: Regex -> String -> String #

matchM :: MonadFail m => Regex -> String -> m String #

RegexMaker Regex CompOption ExecOption String Source # 
Instance details

Methods

makeRegex :: String -> Regex #

makeRegexOpts :: CompOption -> ExecOption -> String -> Regex #

makeRegexM :: MonadFail m => String -> m Regex #

makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> String -> m Regex #