| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Hledger.Utils.Regex
Description
Easy regular expression helpers, currently based on regex-tdfa. These should:
- be cross-platform, not requiring C libraries
 - support unicode
 - support extended regular expressions
 - support replacement, with backreferences etc.
 - support splitting
 - have mnemonic names
 - have simple monomorphic types
 - work with simple strings
 
Regex strings are automatically compiled into regular expressions the first time they are seen, and these are cached. If you use a huge number of unique regular expressions this might lead to increased memory usage. Several functions have memoised variants (*Memo), which also trade space for time.
Currently two APIs are provided:
- The old partial one (with ' suffixes') which will call error on any problem (eg with malformed regexps). This comes from hledger's origin as a command-line tool.
 - The new total one which will return an error message. This is better for long-running apps like hledger-web.
 
Current limitations:
- (?i) and similar are not supported
 
Synopsis
- data Regexp
 - toRegex :: Text -> Either RegexError Regexp
 - toRegexCI :: Text -> Either RegexError Regexp
 - toRegex' :: Text -> Regexp
 - toRegexCI' :: Text -> Regexp
 - type Replacement = String
 - type RegexError = String
 - regexMatch :: Regexp -> String -> Bool
 - regexMatchText :: Regexp -> Text -> Bool
 - regexReplace :: Regexp -> Replacement -> String -> Either RegexError String
 - regexReplaceUnmemo :: Regexp -> Replacement -> String -> Either RegexError String
 - regexReplaceAllBy :: Regexp -> (String -> String) -> String -> String
 
Regexp type and constructors
Regular expression. Extended regular expression-ish syntax ? But does not support eg (?i) syntax.
Instances
| Eq Regexp Source # | |
| Ord Regexp Source # | |
| Read Regexp Source # | |
| Show Regexp Source # | |
| ToJSON Regexp Source # | |
Defined in Hledger.Utils.Regex  | |
| RegexLike Regexp String Source # | |
Defined in Hledger.Utils.Regex Methods matchOnce :: Regexp -> String -> Maybe MatchArray # matchAll :: Regexp -> String -> [MatchArray] # matchCount :: Regexp -> String -> Int # matchTest :: Regexp -> String -> Bool # matchAllText :: Regexp -> String -> [MatchText String] # matchOnceText :: Regexp -> String -> Maybe (String, MatchText String, String) #  | |
| RegexContext Regexp String String Source # | |
toRegexCI' :: Text -> Regexp Source #
type aliases
type Replacement = String Source #
A replacement pattern. May include numeric backreferences (N).
type RegexError = String Source #
An error message arising during a regular expression operation. Eg: trying to compile a malformed regular expression, or trying to apply a malformed replacement pattern.
total regex operations
regexMatch :: Regexp -> String -> Bool Source #
Test whether a Regexp matches a String. This is an alias for matchTest for consistent
 naming.
regexMatchText :: Regexp -> Text -> Bool Source #
Tests whether a Regexp matches a Text.
This currently unpacks the Text to a String an works on that. This is due to a performance bug in regex-tdfa (#9), which may or may not be relevant here.
regexReplace :: Regexp -> Replacement -> String -> Either RegexError String Source #
A memoising version of regexReplace. Caches the result for each search pattern, replacement pattern, target string tuple. This won't generate a regular expression parsing error since that is pre-compiled nowadays, but there can still be a runtime error from the replacement pattern, eg with a backreference referring to a nonexistent match group.
regexReplaceUnmemo :: Regexp -> Replacement -> String -> Either RegexError String Source #