{- copyright (c) sreservoir. license bsd three-clause. -} {-# LANGUAGE FlexibleInstances,TypeSynonymInstances #-} module Text.Regex.Less.Quackers (QLR(..)) where import qualified Text.Regex.PCRE as R import Text.Regex.Less.REOpts bsR :: String -> String bsR ('`':'`':cs) = '`' : bsR cs bsR ('`':cs) = '\\' : bsR cs bsR ('\\':cs) = "\\\\" ++ bsR cs bsR (c:cs) = c : bsR cs bsR [] = [] class QLR a where compile :: a -> R.Regex execute :: a -> String -> [R.MatchArray] execute a b = R.matchAll (compile a) b instance QLR String where compile a = R.makeRegexOpts (reCtOpts []) (reRtOpts []) (bsR a) instance QLR (String,[RECtOpts]) where compile (a,b) = R.makeRegexOpts (reCtOpts b) (reRtOpts []) (bsR a) instance QLR (String,[RERtOpts]) where compile (a,b) = R.makeRegexOpts (reCtOpts []) (reRtOpts b) (bsR a) instance QLR ((String,[RECtOpts]),[RERtOpts]) where compile ((a,b),c) = R.makeRegexOpts (reCtOpts b) (reRtOpts c) (bsR a) instance QLR ((String,[RERtOpts]),[RECtOpts]) where compile ((a,b),c) = R.makeRegexOpts (reCtOpts c) (reRtOpts b) (bsR a) instance QLR (String,([RECtOpts],[RERtOpts])) where compile (a,(b,c)) = R.makeRegexOpts (reCtOpts b) (reRtOpts c) (bsR a) instance QLR (String,([RERtOpts],[RECtOpts])) where compile (a,(b,c)) = R.makeRegexOpts (reCtOpts c) (reRtOpts b) (bsR a)