\begin{code}
module Text.RE.Tools.Grep
(
grep
, Verbosity(..)
, Line(..)
, grepLines
, grepFilter
, GrepScript
, grepWithScript
, report
, linesMatched
, IsRegex(..)
, SearchReplace(..)
, searchReplaceAll
, searchReplaceFirst
, LineNo(..)
, firstLine
, getLineNo
, lineNo
, module Text.RE.Replace
) where
import qualified Data.ByteString.Lazy.Char8 as LBS
import Prelude.Compat
import Text.Printf
import Text.RE.Replace
import Text.RE.Tools.IsRegex
import Text.RE.ZeInternals.Types.LineNo
\end{code}
\begin{code}
grep :: IsRegex re LBS.ByteString => Verbosity -> re -> FilePath -> IO ()
grep v rex fp = grepLines rex fp >>= putStr . report v
\end{code}
\begin{code}
data Verbosity
= LinesMatched
| LinesNotMatched
deriving (Show,Eq,Ord)
\end{code}
\begin{code}
data Line s =
Line
{ getLineNumber :: LineNo
, getLineMatches :: Matches s
}
deriving (Show)
\end{code}
\begin{code}
grepLines :: IsRegex re LBS.ByteString
=> re
-> FilePath
-> IO [Line LBS.ByteString]
grepLines rex fp = grepFilter rex <$> LBS.readFile fp
\end{code}
\begin{code}
grepFilter :: IsRegex re s => re -> s -> [Line s]
grepFilter rex = grepWithScript [(rex,mk)] . linesR
where
mk i mtchs = Just $ Line i mtchs
\end{code}
\begin{code}
type GrepScript re s t = [(re,LineNo -> Matches s -> Maybe t)]
grepWithScript :: IsRegex re s => GrepScript re s t -> [s] -> [t]
grepWithScript scr = loop firstLine
where
loop _ [] = []
loop i (ln:lns) = seq i $ choose i ln lns scr
choose i _ lns [] = loop (succ i) lns
choose i ln lns ((rex,f):scr') = case f i $ matchMany rex ln of
Nothing -> choose i ln lns scr'
Just t -> t : loop (succ i) lns
report :: Verbosity -> [Line LBS.ByteString] -> String
report v = unlines . map fmt . linesMatched v
where
fmt Line{..} =
printf "%05d %s" (getLineNo getLineNumber) $
LBS.unpack $ matchesSource getLineMatches
linesMatched :: Verbosity -> [Line s] -> [Line s]
linesMatched v = filter $ f . anyMatches . getLineMatches
where
f = case v of
LinesMatched -> id
LinesNotMatched -> not
\end{code}
\begin{code}
\end{code}