{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-}
module Text.Regex.Base.RegexLike (
MatchOffset,
MatchLength,
MatchArray,
MatchText,
MatchResult(..),
RegexOptions(..),
RegexMaker(..),
RegexLike(..),
RegexContext(..),
Extract(..),
AllSubmatches(..),AllTextSubmatches(..),AllMatches(..),AllTextMatches(..)
) where
import Data.Array(Array,(!))
import Data.Maybe(isJust)
import qualified Data.ByteString as B (take,drop,empty,ByteString)
import qualified Data.ByteString.Lazy as L (take,drop,empty,ByteString)
import qualified Data.Sequence as S(take,drop,empty,Seq)
type MatchOffset = Int
type MatchLength = Int
type MatchArray = Array Int (MatchOffset,MatchLength)
type MatchText source = Array Int (source,(MatchOffset,MatchLength))
data MatchResult a = MR {
mrBefore :: a,
mrMatch :: a,
mrAfter :: a,
mrSubList :: [a],
mrSubs :: Array Int a
}
class RegexOptions regex compOpt execOpt
| regex->compOpt execOpt, compOpt->regex execOpt, execOpt->regex compOpt where
blankCompOpt :: compOpt
blankExecOpt :: execOpt
defaultCompOpt :: compOpt
defaultExecOpt :: execOpt
setExecOpts :: execOpt -> regex -> regex
getExecOpts :: regex -> execOpt
class (RegexOptions regex compOpt execOpt) => RegexMaker regex compOpt execOpt source
| regex -> compOpt execOpt, compOpt -> regex execOpt, execOpt -> regex compOpt where
makeRegex :: source -> regex
makeRegexOpts :: compOpt -> execOpt -> source -> regex
makeRegexM :: (Monad m) => source -> m regex
makeRegexOptsM :: (Monad m) => compOpt -> execOpt -> source -> m regex
makeRegex = makeRegexOpts defaultCompOpt defaultExecOpt
makeRegexM = makeRegexOptsM defaultCompOpt defaultExecOpt
makeRegexOpts c e s = maybe (error "makeRegexOpts failed") id (makeRegexOptsM c e s)
makeRegexOptsM c e s = return (makeRegexOpts c e s)
class (Extract source)=> RegexLike regex source where
matchOnce :: regex -> source-> Maybe MatchArray
matchAll :: regex -> source-> [MatchArray]
matchCount :: regex -> source-> Int
matchTest :: regex -> source-> Bool
matchAllText :: regex -> source-> [MatchText source]
matchOnceText :: regex -> source-> Maybe (source,MatchText source,source)
matchAll regex source = map (fmap snd) (matchAllText regex source)
matchOnce regex source = fmap (\(_,mt,_) -> fmap snd mt) (matchOnceText regex source)
matchTest regex source = isJust (matchOnce regex source)
matchCount regex source = length (matchAll regex source)
matchOnceText regex source =
fmap (\ma -> let (o,l) = ma!0
in (before o source
,fmap (\ol -> (extract ol source,ol)) ma
,after (o+l) source))
(matchOnce regex source)
matchAllText regex source =
map (fmap (\ol -> (extract ol source,ol)))
(matchAll regex source)
class (RegexLike regex source) => RegexContext regex source target where
match :: regex -> source -> target
matchM :: (Monad m) => regex -> source -> m target
class Extract source where
before :: Int -> source -> source
after :: Int -> source -> source
empty :: source
extract :: (Int,Int) -> source -> source
extract (off,len) source = before len (after off source)
instance Extract String where
before = take; after = drop; empty = []
instance Extract B.ByteString where
before = B.take; after = B.drop; empty = B.empty
instance Extract L.ByteString where
before = L.take . toEnum; after = L.drop . toEnum; empty = L.empty
instance Extract (S.Seq a) where
before = S.take; after = S.drop; empty = S.empty
newtype AllSubmatches f b = AllSubmatches {getAllSubmatches :: (f b)}
newtype AllTextSubmatches f b = AllTextSubmatches {getAllTextSubmatches :: (f b)}
newtype AllMatches f b = AllMatches {getAllMatches :: (f b)}
newtype AllTextMatches f b = AllTextMatches {getAllTextMatches :: (f b) }