\begin{code}
{-# LANGUAGE RecordWildCards            #-}
{-# LANGUAGE MultiParamTypeClasses      #-}
{-# LANGUAGE AllowAmbiguousTypes        #-}
{-# LANGUAGE CPP                        #-}
#if __GLASGOW_HASKELL__ >= 800
{-# OPTIONS_GHC -fno-warn-redundant-constraints #-}
{-# OPTIONS_GHC -fno-warn-unused-imports        #-}
#endif

module Text.RE.ZeInternals.Types.IsRegex
  ( IsRegex(..)
  , SearchReplace(..)
  , searchReplaceAll
  , searchReplaceFirst
  ) where

import           Control.Monad.Fail
import           Text.RE.REOptions
import           Text.RE.Replace
import           Text.RE.ZeInternals.EscapeREString
import           Text.RE.ZeInternals.Types.SearchReplace
\end{code}

\begin{code}
-- | the 'IsRegex' class allows polymorhic tools to be written that
-- will work with a variety of regex back ends and text types
class Replace s => IsRegex re s where
  -- | finding the first match
  matchOnce             :: re -> s -> Match s
  -- | finding all matches
  matchMany             :: re -> s -> Matches s
  -- | compiling an RE, failing if the RE is not well formed
  makeRegex             :: (Functor m,Monad m, MonadFail m) => s -> m re
  -- | comiling an RE, specifying the 'SimpleREOptions'
  makeRegexWith         :: (Functor m,Monad m, MonadFail m) => SimpleREOptions -> s -> m re
  -- | compiling a 'SearchReplace' template from the RE text and the template Text, failing if they are not well formed
  makeSearchReplace     :: (Functor m,Monad m, MonadFail m,IsRegex re s) => s -> s -> m (SearchReplace re s)
  -- | compiling a 'SearchReplace' template specifying the 'SimpleREOptions' for the RE
  makeSearchReplaceWith :: (Functor m,Monad m, MonadFail m,IsRegex re s) => SimpleREOptions -> s -> s -> m (SearchReplace re s)
  -- | incorporate an escaped string into a compiled RE with the default options
  makeEscaped           :: (Functor m,Monad m, MonadFail m) => (s->s) -> s -> m re
  -- | incorporate an escaped string into a compiled RE with the specified 'SimpleREOptions'
  makeEscapedWith       :: (Functor m,Monad m, MonadFail m) => SimpleREOptions -> (s->s) -> s -> m re
  -- | extract the text of the RE from the RE
  regexSource           :: re -> s

  makeRegex           = SimpleREOptions -> s -> m re
forall re s (m :: * -> *).
(IsRegex re s, Functor m, Monad m, MonadFail m) =>
SimpleREOptions -> s -> m re
makeRegexWith         SimpleREOptions
forall a. Bounded a => a
minBound
  makeSearchReplace   = SimpleREOptions -> s -> s -> m (SearchReplace re s)
forall re s (m :: * -> *).
(IsRegex re s, Functor m, Monad m, MonadFail m, IsRegex re s) =>
SimpleREOptions -> s -> s -> m (SearchReplace re s)
makeSearchReplaceWith SimpleREOptions
forall a. Bounded a => a
minBound
  makeEscaped         = SimpleREOptions -> (s -> s) -> s -> m re
forall re s (m :: * -> *).
(IsRegex re s, Functor m, Monad m, MonadFail m) =>
SimpleREOptions -> (s -> s) -> s -> m re
makeEscapedWith       SimpleREOptions
forall a. Bounded a => a
minBound
  makeEscapedWith SimpleREOptions
o s -> s
f = SimpleREOptions -> s -> m re
forall re s (m :: * -> *).
(IsRegex re s, Functor m, Monad m, MonadFail m) =>
SimpleREOptions -> s -> m re
makeRegexWith SimpleREOptions
o (s -> m re) -> (s -> s) -> s -> m re
forall b c a. (b -> c) -> (a -> b) -> a -> c
. s -> s
f (s -> s) -> (s -> s) -> s -> s
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> s
forall a. Replace a => String -> a
packR (String -> s) -> (s -> String) -> s -> s
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
escapeREString (String -> String) -> (s -> String) -> s -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. s -> String
forall a. Replace a => a -> String
unpackR
\end{code}

\begin{code}
-- | search and replace all matches in the argument text; e.g., this function
-- will convert every YYYY-MM-DD format date in its argument text into a
-- DD\/MM\/YYYY date:
--
--   @searchReplaceAll [ed|${y}([0-9]{4})-0*${m}([0-9]{2})-0*${d}([0-9]{2})\/\/\/${d}\/${m}\/${y}|]@
--
searchReplaceAll :: IsRegex re s => SearchReplace re s -> s -> s
searchReplaceAll :: SearchReplace re s -> s -> s
searchReplaceAll SearchReplace{re
s
getTemplate :: forall re s. SearchReplace re s -> s
getSearch :: forall re s. SearchReplace re s -> re
getTemplate :: s
getSearch :: re
..} = s -> Matches s -> s
forall a. Replace a => a -> Matches a -> a
replaceAll s
getTemplate (Matches s -> s) -> (s -> Matches s) -> s -> s
forall b c a. (b -> c) -> (a -> b) -> a -> c
. re -> s -> Matches s
forall re s. IsRegex re s => re -> s -> Matches s
matchMany re
getSearch

-- | search and replace the first occurrence only (if any) in the input text
-- e.g., to prefix the first string of four hex digits in the imput text,
-- if any, with @0x@:
--
--  @searchReplaceFirst [ed|[0-9A-Fa-f]{4}\/\/\/0x$0|]@
--
searchReplaceFirst :: IsRegex re s => SearchReplace re s -> s -> s
searchReplaceFirst :: SearchReplace re s -> s -> s
searchReplaceFirst SearchReplace{re
s
getTemplate :: s
getSearch :: re
getTemplate :: forall re s. SearchReplace re s -> s
getSearch :: forall re s. SearchReplace re s -> re
..} = s -> Match s -> s
forall a. Replace a => a -> Match a -> a
replace    s
getTemplate (Match s -> s) -> (s -> Match s) -> s -> s
forall b c a. (b -> c) -> (a -> b) -> a -> c
. re -> s -> Match s
forall re s. IsRegex re s => re -> s -> Match s
matchOnce re
getSearch
\end{code}