\begin{code}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE DeriveDataTypeable #-}
\end{code}
\begin{code}
module Text.RE.ZeInternals.Types.Capture
( Capture(..)
, hasCaptured
, capturePrefix
, captureSuffix
) where
\end{code}
\begin{code}
import Text.Regex.Base
\end{code}
\begin{code}
data Capture a =
Capture
{ captureSource :: !a
, capturedText :: !a
, captureOffset :: !Int
, captureLength :: !Int
}
deriving (Show,Eq)
\end{code}
\begin{code}
instance Functor Capture where
fmap f c@Capture{..} =
c
{ captureSource = f captureSource
, capturedText = f capturedText
}
\end{code}
\begin{code}
hasCaptured :: Capture a -> Bool
hasCaptured = (>=0) . captureOffset
capturePrefix :: Extract a => Capture a -> a
capturePrefix Capture{..} = before captureOffset captureSource
captureSuffix :: Extract a => Capture a -> a
captureSuffix Capture{..} = after (captureOffset+captureLength) captureSource
\end{code}