\begin{code}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__ >= 800
{-# OPTIONS_GHC -fno-warn-redundant-constraints #-}
#endif
module Text.RE.Tools.Edit
(
Edits(..)
, Edit(..)
, LineEdit(..)
, applyEdits
, applyEdit
, applyLineEdit
, IsRegex(..)
, SearchReplace(..)
, searchReplaceAll
, searchReplaceFirst
, LineNo(..)
, firstLine
, getLineNo
, lineNo
, module Text.RE.Replace
) where
import Data.Maybe
import Prelude.Compat
import Text.RE.Replace
import Text.RE.Tools.IsRegex
import Text.RE.ZeInternals.Types.LineNo
\end{code}
\begin{code}
data Edits m re s
= Select ![Edit m re s]
| Pipe ![Edit m re s]
data Edit m re s
= Template !(SearchReplace re s)
| Function !re REContext !(LineNo->Match s->RELocation->Capture s->m (Maybe s))
| LineEdit !re !(LineNo->Matches s->m (LineEdit s))
data LineEdit s
= NoEdit
| ReplaceWith !s
| Delete
deriving (Functor,Show)
\end{code}
\begin{code}
applyEdits :: (IsRegex re s,Monad m,Functor m)
=> LineNo
-> Edits m re s
-> s
-> m s
applyEdits lno ez0 s0 = case ez0 of
Select ez -> select_edit_scripts lno ez s0
Pipe ez -> pipe_edit_scripts lno ez s0
applyEdit :: (IsRegex re s,Monad m,Functor m)
=> (s->s)
-> LineNo
-> Edit m re s
-> s
-> m (Maybe s)
applyEdit anl lno edit s =
case allMatches acs of
[] -> return Nothing
_ -> fmap Just $ case edit of
Template srch_rpl -> return $ anl $ replaceAll (getTemplate srch_rpl) acs
Function _ ctx f -> anl <$> replaceAllCapturesM replaceMethods ctx (f lno) acs
LineEdit _ g -> fromMaybe (anl s) . applyLineEdit anl <$> g lno acs
where
acs = matchMany rex s
rex = case edit of
Template srch_rpl -> getSearch srch_rpl
Function rex_ _ _ -> rex_
LineEdit rex_ _ -> rex_
applyLineEdit :: Monoid s => (s->s) -> LineEdit s -> Maybe s
applyLineEdit _ NoEdit = Nothing
applyLineEdit anl (ReplaceWith s) = Just $ anl s
applyLineEdit _ Delete = Just mempty
select_edit_scripts :: (IsRegex re s,Monad m,Functor m)
=> LineNo
-> [Edit m re s]
-> s
-> m s
select_edit_scripts lno ps0 s = select ps0
where
select [] = return $ appendNewlineR s
select (edit:edits) =
applyEdit appendNewlineR lno edit s >>= maybe (select edits) return
pipe_edit_scripts :: (IsRegex re s,Monad m,Functor m)
=> LineNo
-> [Edit m re s]
-> s
-> m s
pipe_edit_scripts lno edits s0 =
appendNewlineR <$> foldr f (return s0) edits
where
f edit act = do
s <- act
fromMaybe s <$> applyEdit id lno edit s
\end{code}
\begin{code}
\end{code}