\begin{code}
module Text.RE.Tools.Grep
( grep
, Line(..)
, grepLines
, GrepScript
, grepScript
, report
, Verbosity(..)
, linesMatched
, IsRegex(..)
, LineNo(..)
, firstLine
, getLineNo
, lineNo
, module Text.RE
) where
import qualified Data.ByteString.Lazy.Char8 as LBS
import Prelude.Compat
import Text.Printf
import Text.RE
import Text.RE.Types.IsRegex
import Text.RE.Types.LineNo
grep :: IsRegex re LBS.ByteString => Verbosity -> re -> FilePath -> IO ()
grep v rex fp = grepLines rex fp >>= putStr . report v
data Line =
Line
{ getLineNumber :: LineNo
, getLineMatches :: Matches LBS.ByteString
}
deriving (Show)
grepLines :: IsRegex re LBS.ByteString => re -> FilePath -> IO [Line]
grepLines rex fp =
grepScript [(rex,mk)] . LBS.lines <$> LBS.readFile fp
where
mk i mtchs = Just $ Line i mtchs
type GrepScript re s t = [(re,LineNo -> Matches s -> Maybe t)]
grepScript :: IsRegex re s => GrepScript re s t -> [s] -> [t]
grepScript 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] -> String
report v = unlines . map fmt . linesMatched v
where
fmt Line{..} =
printf "%05d %s" (getLineNo getLineNumber) $
LBS.unpack $ matchesSource getLineMatches
data Verbosity
= LinesMatched
| LinesNotMatched
deriving (Show,Eq,Ord)
linesMatched :: Verbosity -> [Line] -> [Line]
linesMatched v = filter $ f . anyMatches . getLineMatches
where
f = case v of
LinesMatched -> id
LinesNotMatched -> not
\end{code}