{- copyright (c) sreservoir. license bsd three-clause. -} module Text.Regex.Less ( (=~),(<<), truth,subs,subg,derefs,bref,matchN) where import qualified Text.Regex.PCRE as R import qualified Data.Array.IArray as A import Text.Regex.Less.Quackers type Match = (String,[R.MatchArray]) -- standard usage: -- "" =~ "" -- "" =~ "" << [RECtOpts] -- "" =~ "" << [RERtOpts] -- "" =~ "" << [RECtOpts] << RERtOpts -- value is suitable for use below. infixl 4 =~ (=~) :: QLR a => String -> a -> Match a =~ b = a << execute b a -- (a << b) = (a,b) infixl 5 << (<<) :: a -> b -> (a,b) a << b = (a,b) -- whether the match succeeded. truth :: Match -> Bool truth (_,a) = not (null a) -- replaces matched substring with supplied string. -- supplied string is passed through derefs first. subs :: Match -> String -> String subs a b = s ++ derefs (bref a) b ++ f where o = fst a (i,c) = head (snd a) A.! 0 (s,r) = splitAt i o f = drop c r -- as subs, to every match. subg :: Match -> String -> String subg a b = subg' o (decay (map A.elems m)) b where (o,m) = a -- for each match part, does just what it needs. -- if there are more, repeat with the rest. subg' :: String -> [[(Int,Int)]] -> String -> String subg' ors (cur@((ini,chs):_):ms) sub = take ini ors ++ derefs bref' sub ++ subg' (drop (ini + chs) ors) ms sub where bref' a = R.extract (cur !! a) ors subg' _ _ _ = [] -- reduces offset by number used by the previous. decay :: [[(Int,Int)]] -> [[(Int,Int)]] decay (x:xs) = x : decay rest where rest = map (map proc) xs proc (a,b) = a - uncurry (+) (head x) << b decay [] = [] -- does backreferences with ` . derefs :: (Int -> String) -> String -> String derefs f ('`':'`':bs) = '`' : derefs f bs derefs f ('`':'.':bs) = derefs f bs derefs f ('`':bs) = case reads bs of [(c,d)] -> f c ++ derefs f d _ -> undefined derefs f (b:bs) = b : derefs f bs derefs _ [] = [] -- returns the indexed substring. -- backref 0 is the entire match. bref :: Match -> Int -> String bref a i = R.extract (head (snd a) A.! i) (fst a) -- takes one of the matches. matchN :: Match -> Int -> Match matchN (a,b) i = (a,[b !! i])