{- copyright (c) sreservoir. license bsd three-clause. -} {-# LANGUAGE FlexibleInstances,TypeSynonymInstances #-} module Text.Regex.Less.Quackers (QLR(..)) where import qualified Text.Regex.PCRE.Light as R import qualified Data.ByteString.Char8 as B import Text.Regex.Less.REOpts -- the QLR (QuacksLikeRegex) class: -- compile -- runopts -- instances of QLR: -- String -- (String,[RECtOpts]) -- (String,[RERtOpts]) -- (String,([RECtOpts],[RERtOpts])) -- (String,([RERtOpts],[RECtOpts])) -- ((String,[RECtOpts]),[RERtOpts]) -- ((String,[RERtOpts]),[RECtOpts]) -- QuacksLikeRegex: can =~ . class QLR a where compile :: a -> R.Regex runopts :: a -> [R.PCREExecOption] -- standard string. instance QLR String where compile a = R.compile (B.pack a) [] runopts _ = [] -- re << compile instance QLR (String,[RECtOpt]) where compile (a,b) = R.compile (B.pack a) (reCtOpts b) runopts (_,_) = [] -- re << runtime instance QLR (String,[RERtOpt]) where compile (a,_) = R.compile (B.pack a) [] runopts (_,b) = reRtOpts b -- re << compile << runtime instance QLR (String,([RECtOpt],[RERtOpt])) where compile (a,(b,_)) = R.compile (B.pack a) (reCtOpts b) runopts (_,(_,c)) = reRtOpts c -- re << runtime << compile instance QLR (String,([RERtOpt],[RECtOpt])) where compile (a,(_,b)) = R.compile (B.pack a) (reCtOpts b) runopts (_,(c,_)) = reRtOpts c -- (re << compile) << runtime instance QLR ((String,[RECtOpt]),[RERtOpt]) where compile ((a,b),_) = R.compile (B.pack a) (reCtOpts b) runopts ((_,_),c) = reRtOpts c -- (re << runtime) << compile instance QLR ((String,[RERtOpt]),[RECtOpt]) where compile ((a,_),b) = R.compile (B.pack a) (reCtOpts b) runopts ((_,c),_) = reRtOpts c