Copyright | (c) Chris Kuklewicz 2006 |
---|---|
License | BSD-3-Clause |
Maintainer | hvr@gnu.org, Andreas Abel |
Stability | stable |
Portability | non-portable (regex-base needs MPTC+FD) |
Safe Haskell | None |
Language | Haskell2010 |
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
- data Regex
- type MatchOffset = Int
- type MatchLength = Int
- data ReturnCode
- type WrapError = (ReturnCode, String)
- unusedOffset :: Int
- compile :: CompOption -> ExecOption -> Seq Char -> IO (Either WrapError Regex)
- regexec :: Regex -> Seq Char -> IO (Either WrapError (Maybe (Seq Char, Seq Char, Seq Char, [Seq Char])))
- execute :: Regex -> Seq Char -> IO (Either WrapError (Maybe (Array Int (MatchOffset, MatchLength))))
- 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 #
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 expressionretBadrpt
(REG_BADRPT
)?
,*
, or+
operand invalidretEcollate
(REG_ECOLLATE
) invalid collating elementretEctype
(REG_ECTYPE
) invalid character classretEescape
(REG_EESCAPE
)\
applied to unescapable characterretEsubreg
(REG_ESUBREG
) invalid backreference numberretEbrack
(REG_EBRACK
) brackets[ ]
not balancedretEparen
(REG_EPAREN
) parentheses( )
not balancedretEbrace
(REG_EBRACE
) braces{ }
not balancedretErange
(REG_ERANGE
) invalid character range in[ ]
retEspace
(REG_ESPACE
) ran out of memoryretNoMatch
(REG_NOMATCH
) The regexec() function failed to match
Instances
Eq ReturnCode Source # | |
Defined in Text.Regex.Posix.Wrap (==) :: ReturnCode -> ReturnCode -> Bool # (/=) :: ReturnCode -> ReturnCode -> Bool # | |
Show ReturnCode Source # | |
Defined in Text.Regex.Posix.Wrap 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
:: CompOption | Flags (summed together) |
-> ExecOption | Flags (summed together) |
-> Seq Char | The regular expression to compile (ASCII only, no null bytes) |
-> IO (Either WrapError Regex) | Returns: the compiled regular expression |
:: Regex | Compiled regular expression |
-> Seq Char | Text to match against |
-> IO (Either WrapError (Maybe (Seq Char, Seq Char, Seq Char, [Seq Char]))) | Returns: |
Matches a regular expression against a string
:: Regex | Compiled regular expression |
-> Seq Char | Text to match against |
-> IO (Either WrapError (Maybe (Array Int (MatchOffset, MatchLength)))) | Returns: |
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 theblankCompOpt
value.compExtended
(REG_EXTENDED) which can be set to use extended instead of basic regular expressions. This is set in thedefaultCompOpt
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 thedefaultCompOpt
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.
Instances
compBlank :: CompOption Source #
A completely zero value for all the flags.
This is also the blankCompOpt
value.
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 theblankExecOpt
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).
Instances
execBlank :: ExecOption Source #
A completely zero value for all the flags.
This is also the blankExecOpt
value.
Orphan instances
RegexMaker Regex CompOption ExecOption (Seq Char) Source # | |
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 # | |
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 # | |