| Copyright | (c) Chris Kuklewicz 2007 | 
|---|---|
| License | BSD-3-Clause | 
| Maintainer | hvr@gnu.org | 
| Stability | experimental | 
| Portability | non-portable (regex-base needs MPTC+FD) | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Text.Regex.Posix.ByteString.Lazy
Contents
Description
This provides Lazy instances for RegexMaker and RegexLike
 based on Text.Regex.Posix.Wrap, and a (RegexContext Regex
 ByteString ByteString) 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.
A Lazy ByteString with more than one chunk cannot be be passed to the library efficiently (as a pointer). It will have to converted via a full copy to a temporary normal bytestring (with a null byte appended if necessary).
Synopsis
- data Regex
- type MatchOffset = Int
- type MatchLength = Int
- data ReturnCode
- type WrapError = (ReturnCode, String)
- unusedOffset :: Int
- compile :: CompOption -> ExecOption -> ByteString -> IO (Either WrapError Regex)
- execute :: Regex -> ByteString -> IO (Either WrapError (Maybe (Array Int (MatchOffset, MatchLength))))
- regexec :: Regex -> ByteString -> IO (Either WrapError (Maybe (ByteString, ByteString, ByteString, [ByteString])))
- newtype CompOption = CompOption CInt
- compBlank :: CompOption
- compExtended :: CompOption
- compIgnoreCase :: CompOption
- compNoSub :: CompOption
- compNewline :: CompOption
- newtype ExecOption = ExecOption CInt
- execBlank :: ExecOption
- execNotBOL :: ExecOption
- execNotEOL :: ExecOption
Types
A compiled regular expression.
Instances
type MatchOffset = Int #
0 based index from start of source, or (-1) for unused
type MatchLength = Int #
non-negative length of a match
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
| Eq ReturnCode Source # | |
| Defined in Text.Regex.Posix.Wrap | |
| Show ReturnCode Source # | |
| Defined in Text.Regex.Posix.Wrap Methods showsPrec :: Int -> ReturnCode -> ShowS # show :: ReturnCode -> String # showList :: [ReturnCode] -> ShowS # | |
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
unusedOffset :: Int Source #
Medium level API functions
Arguments
| :: CompOption | Flags (summed together) | 
| -> ExecOption | Flags (summed together) | 
| -> ByteString | The regular expression to compile | 
| -> IO (Either WrapError Regex) | Returns: the compiled regular expression | 
Compiles a regular expression
Arguments
| :: Regex | Compiled regular expression | 
| -> ByteString | String to match against | 
| -> IO (Either WrapError (Maybe (Array Int (MatchOffset, MatchLength)))) | Returns:  | 
Matches a regular expression against a buffer, returning the buffer indicies of the match, and any submatches
| Matches a regular expression against a string
Arguments
| :: Regex | Compiled regular expression | 
| -> ByteString | String to match against | 
| -> IO (Either WrapError (Maybe (ByteString, ByteString, ByteString, [ByteString]))) | 
Compilation options
newtype CompOption Source #
A bitmapped CInt containing options for compilation of regular
 expressions.  Option values (and their man 3 regcomp names) are
- compBlankwhich is a completely zero value for all the flags. This is also the- blankCompOptvalue.
- compExtended(REG_EXTENDED) which can be set to use extended instead of basic regular expressions. This is set in the- defaultCompOptvalue.
- 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- defaultCompOptvalue.
- 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
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
- execBlankwhich 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
execBlank :: ExecOption Source #
A completely zero value for all the flags.
 This is also the blankExecOpt value.
Orphan instances
| RegexLike Regex ByteString Source # | |
| 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) # | |
| RegexContext Regex ByteString ByteString Source # | |
| Methods match :: Regex -> ByteString -> ByteString # matchM :: MonadFail m => Regex -> ByteString -> m ByteString # | |
| RegexMaker Regex CompOption ExecOption ByteString Source # | |
| Methods makeRegex :: ByteString -> Regex # makeRegexOpts :: CompOption -> ExecOption -> ByteString -> Regex # makeRegexM :: MonadFail m => ByteString -> m Regex # makeRegexOptsM :: MonadFail m => CompOption -> ExecOption -> ByteString -> m Regex # | |