\begin{code}
#if __GLASGOW_HASKELL__ >= 800
#endif
module Text.RE.Tools.Find
(
FindMethods(..)
, findMatches_
, findMatches_'
, IsRegex(..)
, SearchReplace(..)
, searchReplaceAll
, searchReplaceFirst
, module Text.RE.Replace
) where
import qualified Data.List as L
import Prelude.Compat
import Text.RE.Replace
import Text.RE.Tools.IsRegex
\end{code}
\begin{code}
data FindMethods s =
FindMethods
{ doesDirectoryExistDM :: s -> IO Bool
, listDirectoryDM :: s -> IO [s]
, combineDM :: s -> s -> s
}
\end{code}
\begin{code}
findMatches_ :: IsRegex re s => FindMethods s -> re -> s -> IO [s]
findMatches_ fm = findMatches_' fm L.sort matched
findMatches_' :: IsRegex re s
=> FindMethods s
-> ([s]->[s])
-> (Match s->Bool)
-> re
-> s
-> IO [s]
findMatches_' fm srt tst re fp = srt <$> find_ fm tst re (packR "") fp
find_ :: IsRegex re s
=> FindMethods s
-> (Match s->Bool)
-> re
-> s
-> s
-> IO [s]
find_ fm@FindMethods{..} tst re fn fp = do
is_dir <- doesDirectoryExistDM fp
case is_dir of
True -> do
fns <- filter ordinary <$> listDirectoryDM fp
concat <$>
mapM (uncurry $ find_ fm tst re) [ (fn_,abs_path fn_) | fn_<-fns ]
False -> return [ fp | lengthR fp /= 0 && tst (matchOnce re fn) ]
where
abs_path fn_ = fp `combineDM` fn_
ordinary fn_ = not $ fn_ `elem` [packR ".",packR ".."]
\end{code}
\begin{code}
\end{code}