\begin{code}
\end{code}
\begin{code}
module Text.RE.Types.Matches
( Matches(..)
, anyMatches
, countMatches
, matches
, mainCaptures
) where
\end{code}
\begin{code}
import Data.Typeable
import Text.Regex.Base
import Text.RE.Types.Capture
import Text.RE.Types.CaptureID
import Text.RE.Types.Match
\end{code}
\begin{code}
data Matches a =
Matches
{ matchesSource :: !a
, allMatches :: ![Match a]
}
deriving (Show,Eq,Typeable)
\end{code}
\begin{code}
instance Functor Matches where
fmap f Matches{..} =
Matches
{ matchesSource = f matchesSource
, allMatches = map (fmap f) allMatches
}
\end{code}
\begin{code}
anyMatches :: Matches a -> Bool
anyMatches = not . null . allMatches
countMatches :: Matches a -> Int
countMatches = length . allMatches
matches :: Matches a -> [a]
matches = map capturedText . mainCaptures
mainCaptures :: Matches a -> [Capture a]
mainCaptures ac = [ capture c0 cs | cs<-allMatches ac ]
where
c0 = IsCaptureOrdinal $ CaptureOrdinal 0
\end{code}
\begin{code}
instance
( RegexContext regex source [MatchText source]
, RegexLike regex source
) =>
RegexContext regex source (Matches source) where
match r s = Matches s $ map (convertMatchText s) $ match r s
matchM r s = do
y <- matchM r s
return $ Matches s $ map (convertMatchText s) y
\end{code}