refactor: abstract regular expression lib

This commit is contained in:
Simon Michael 2011-06-05 18:31:19 +00:00
parent 170154edfb
commit 6a185bc51f
6 changed files with 36 additions and 18 deletions

View File

@ -226,7 +226,7 @@ filterJournalTransactionsByAccount apats j@Journal{jtxns=ts} = j{jtxns=filter tm
tmatch t = (null positives || any positivepmatch ps) && (null negatives || not (any negativepmatch ps)) where ps = tpostings t
positivepmatch p = any (`amatch` a) positives where a = paccount p
negativepmatch p = any (`amatch` a) negatives where a = paccount p
amatch pat a = containsRegex (abspat pat) a
amatch pat a = regexMatches (abspat pat) a
(negatives,positives) = partition isnegativepat apats
-- | Keep only postings which affect accounts matched by the account patterns.
@ -352,7 +352,7 @@ matchpats pats str =
where
(negatives,positives) = partition isnegativepat pats
match "" = True
match pat = containsRegex (abspat pat) str
match pat = regexMatches (abspat pat) str
negateprefix = "not:"

View File

@ -27,6 +27,7 @@ where
import Codec.Binary.UTF8.String as UTF8 (decodeString, encodeString, isUTF8Encoded)
import Data.Char
import Data.List
import Data.Maybe
import Data.Time.Clock
import Data.Time.LocalTime
import Data.Tree
@ -208,10 +209,31 @@ difforzero a b = maximum [(a - b), 0]
-- regexps
containsRegex :: String -> String -> Bool
containsRegex r s = case matchRegexPR ("(?i)"++r) s of
Just _ -> True
_ -> False
-- regexMatch :: String -> String -> MatchFun Maybe
regexMatch r s = matchRegexPR r s
-- regexMatchCI :: String -> String -> MatchFun Maybe
regexMatchCI r s = regexMatch (regexToCaseInsensitive r) s
regexMatches :: String -> String -> Bool
regexMatches r s = isJust $ matchRegexPR r s
regexMatchesCI :: String -> String -> Bool
regexMatchesCI r s = regexMatches (regexToCaseInsensitive r) s
containsRegex = regexMatchesCI
regexReplace :: String -> String -> String -> String
regexReplace r repl s = gsubRegexPR r repl s
regexReplaceCI :: String -> String -> String -> String
regexReplaceCI r s = regexReplace (regexToCaseInsensitive r) s
regexReplaceBy :: String -> (String -> String) -> String -> String
regexReplaceBy r replfn s = gsubRegexPRBy r replfn s
regexToCaseInsensitive :: String -> String
regexToCaseInsensitive r = "(?i)"++ r
-- lists
@ -273,7 +295,7 @@ treeany f t = f (root t) || any (treeany f) (branches t)
-- | show a compact ascii representation of a tree
showtree :: Show a => Tree a -> String
showtree = unlines . filter (containsRegex "[^ \\|]") . lines . drawTree . treemap show
showtree = unlines . filter (regexMatches "[^ \\|]") . lines . drawTree . treemap show
-- | show a compact ascii representation of a forest
showforest :: Show a => Forest a -> String

View File

@ -20,7 +20,6 @@ import System.FilePath (takeFileName, (</>))
import System.IO.Storage (putValue, getValue)
import Text.Hamlet hiding (hamletFile)
import Text.Printf
import Text.RegexPR
import Yesod.Form
import Yesod.Json
@ -442,7 +441,7 @@ accountNameToAccountRegex "" = ""
accountNameToAccountRegex a = printf "^%s(:|$)" a
accountRegexToAccountName :: String -> String
accountRegexToAccountName = gsubRegexPR "^\\^(.*?)\\(:\\|\\$\\)$" "\\1"
accountRegexToAccountName = regexReplace "^\\^(.*?)\\(:\\|\\$\\)$" "\\1"
isAccountRegex :: String -> Bool
isAccountRegex s = take 1 s == "^" && (take 5 $ reverse s) == ")$|:("

View File

@ -20,7 +20,6 @@ import Test.HUnit
import Text.CSV (parseCSV, parseCSVFromFile, printCSV, CSV)
import Text.ParserCombinators.Parsec
import Text.Printf (hPrintf)
import Text.RegexPR (matchRegexPR, gsubRegexPR)
import Hledger.Cli.Options (Opt(Debug), progname_cli, rulesFileFromOpts)
import Hledger.Cli.Version (progversionstr)
@ -28,7 +27,7 @@ import Hledger.Data (Journal,AccountName,Transaction(..),Posting(..),PostingType
import Hledger.Data.Amount (nullmixedamt, costOfMixedAmount)
import Hledger.Data.Journal (nullctx)
import Hledger.Read.JournalReader (someamount,ledgeraccountname)
import Hledger.Utils (strip, spacenonewline, restofline, parseWithCtx, assertParse, assertParseEqual, error')
import Hledger.Utils (strip, spacenonewline, restofline, parseWithCtx, assertParse, assertParseEqual, error', regexMatchesCI, regexReplaceCI)
import Hledger.Utils.UTF8 (getContents)
{- |
@ -399,11 +398,11 @@ identify rules defacct desc | null matchingrules = (defacct,desc)
| otherwise = (acct,newdesc)
where
matchingrules = filter ismatch rules :: [AccountRule]
where ismatch = any (isJust . flip matchRegexPR (caseinsensitive desc) . fst) . fst
where ismatch = any ((`regexMatchesCI` desc) . fst) . fst
(prs,acct) = head matchingrules
p_ms_r = filter (\(_,m,_) -> isJust m) $ map (\(p,r) -> (p, matchRegexPR (caseinsensitive p) desc, r)) prs
p_ms_r = filter (\(_,m,_) -> m) $ map (\(p,r) -> (p, p `regexMatchesCI` desc, r)) prs
(p,_,r) = head p_ms_r
newdesc = case r of Just rpat -> gsubRegexPR (caseinsensitive p) rpat desc
newdesc = case r of Just repl -> regexReplaceCI p repl desc
Nothing -> desc
caseinsensitive = ("(?i)"++)

View File

@ -12,7 +12,6 @@ import Data.Time.LocalTime
import System.Console.GetOpt
import System.Environment
import Test.HUnit
import Text.RegexPR
import Hledger.Data
import Hledger.Read (myJournalPath, myTimelogPath)
@ -175,7 +174,7 @@ fixOptDates opts = do
fixopt d (Begin s) = Begin $ fixSmartDateStr d s
fixopt d (End s) = End $ fixSmartDateStr d s
fixopt d (Display s) = -- hacky
Display $ gsubRegexPRBy "\\[.+?\\]" fixbracketeddatestr s
Display $ regexReplaceBy "\\[.+?\\]" fixbracketeddatestr s
where fixbracketeddatestr s = "[" ++ fixSmartDateStr d (init $ tail s) ++ "]"
fixopt _ o = o

View File

@ -35,7 +35,6 @@ import System.Process (readProcessWithExitCode)
import System.Time (ClockTime, getClockTime, diffClockTimes, TimeDiff(TimeDiff))
import Test.HUnit
import Text.Printf
import Text.RegexPR
import Hledger.Cli.Options (Opt(..),journalFilePathFromOpts)
import Hledger.Data
@ -161,6 +160,6 @@ safeGetDirectoryContents fp = getDirectoryContents fp
-- | Does the second file represent a backup of the first, and if so which version is it ?
backupNumber :: FilePath -> FilePath -> Maybe Int
backupNumber f g = case matchRegexPR ("^" ++ f ++ "\\.([0-9]+)$") g of
backupNumber f g = case regexMatch ("^" ++ f ++ "\\.([0-9]+)$") g of
Just (_, ((_,suffix):_)) -> readMay suffix
_ -> Nothing