{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__ >= 800
{-# OPTIONS_GHC -fno-warn-redundant-constraints #-}
{-# LANGUAGE TemplateHaskellQuotes #-}
#else
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
#endif
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module Text.RE.ZeInternals.PCRE
(
RE
, regexType
, reOptions
, reSource
, reCaptureNames
, reRegex
, IsOption(..)
, REOptions
, defaultREOptions
, noPreludeREOptions
, unpackSimpleREOptions
, compileRegex
, compileRegexWith
, compileRegexWithOptions
, compileSearchReplace
, compileSearchReplaceWith
, compileSearchReplaceWithOptions
, escape
, escapeWith
, escapeWithOptions
, escapeREString
, prelude
, preludeEnv
, preludeTestsFailing
, preludeTable
, preludeSummary
, preludeSources
, preludeSource
, re
, reMS
, reMI
, reBS
, reBI
, reMultilineSensitive
, reMultilineInsensitive
, reBlockSensitive
, reBlockInsensitive
, re_
, cp
) where
import Control.Monad.Fail
import Data.Bits
import Data.Functor.Identity
import Language.Haskell.TH
import Language.Haskell.TH.Quote
import Prelude.Compat hiding (fail)
import Text.RE.REOptions
import Text.RE.Replace
import Text.RE.TestBench
import Text.RE.Tools
import Text.RE.ZeInternals
import Text.RE.ZeInternals.Types.Poss
import Text.Regex.PCRE
data RE =
RE
{ _re_options :: !REOptions
, _re_source :: !String
, _re_cnames :: !CaptureNames
, _re_regex :: !Regex
}
regexType :: RegexType
regexType =
mkPCRE $ \txt env md -> txt =~ mdRegexSource regexType ExclCaptures env md
reOptions :: RE -> REOptions
reOptions = _re_options
reSource :: RE -> String
reSource = _re_source
reCaptureNames :: RE -> CaptureNames
reCaptureNames = _re_cnames
reRegex :: RE -> Regex
reRegex = _re_regex
class IsOption o where
makeREOptions :: o -> REOptions
type REOptions = REOptions_ RE CompOption ExecOption
instance IsOption SimpleREOptions where
makeREOptions = unpackSimpleREOptions
instance IsOption (Macros RE) where
makeREOptions ms = REOptions ms def_comp_option def_exec_option
instance IsOption CompOption where
makeREOptions co = REOptions prelude co def_exec_option
instance IsOption ExecOption where
makeREOptions eo = REOptions prelude def_comp_option eo
instance IsOption REOptions where
makeREOptions = id
instance IsOption () where
makeREOptions _ = unpackSimpleREOptions minBound
defaultREOptions :: REOptions
defaultREOptions = makeREOptions (minBound::SimpleREOptions)
noPreludeREOptions :: REOptions
noPreludeREOptions = defaultREOptions { optionsMacs = emptyMacros }
unpackSimpleREOptions :: SimpleREOptions -> REOptions
unpackSimpleREOptions sro =
REOptions
{ optionsMacs = prelude
, optionsComp = comp
, optionsExec = defaultExecOpt
}
where
comp =
wiggle ml compMultiline $
wiggle ci compCaseless
defaultCompOpt
wiggle True m v = v .|. m
wiggle False m v = v .&. complement m
(ml,ci) = case sro of
MultilineSensitive -> (,) True False
MultilineInsensitive -> (,) True True
BlockSensitive -> (,) False False
BlockInsensitive -> (,) False True
compileRegex :: (Functor m,Monad m, MonadFail m) => String -> m RE
compileRegex = compileRegexWith minBound
compileRegexWith :: (Functor m,Monad m, MonadFail m) => SimpleREOptions -> String -> m RE
compileRegexWith = compileRegexWithOptions
compileRegexWithOptions :: (IsOption o, Functor m, Monad m, MonadFail m)
=> o
-> String
-> m RE
compileRegexWithOptions = compileRegex_ . makeREOptions
compileSearchReplace :: (Monad m,MonadFail m,Functor m,IsRegex RE s)
=> String
-> String
-> m (SearchReplace RE s)
compileSearchReplace = compileSearchReplaceWith minBound
compileSearchReplaceWith :: (Monad m,MonadFail m,Functor m,IsRegex RE s)
=> SimpleREOptions
-> String
-> String
-> m (SearchReplace RE s)
compileSearchReplaceWith sro = compileSearchAndReplace_ packR $ poss2either . compileRegexWith sro
compileSearchReplaceWithOptions :: (Monad m,MonadFail m,Functor m,IsRegex RE s)
=> REOptions
-> String
-> String
-> m (SearchReplace RE s)
compileSearchReplaceWithOptions os = compileSearchAndReplace_ packR $ poss2either . compileRegexWithOptions os
escape :: (Functor m,Monad m, MonadFail m)
=> (String->String)
-> String
-> m RE
escape = escapeWith minBound
escapeWith :: (Functor m,Monad m, MonadFail m)
=> SimpleREOptions
-> (String->String)
-> String
-> m RE
escapeWith = escapeWithOptions
escapeWithOptions :: ( IsOption o, Functor m, Monad m, MonadFail m)
=> o
-> (String->String)
-> String
-> m RE
escapeWithOptions o f = compileRegexWithOptions o . f . escapeREString
prelude :: Macros RE
prelude = runIdentity $ preludeMacros mk regexType ExclCaptures
where
mk = Identity . unsafeCompileRegex_ noPreludeREOptions
preludeEnv :: MacroEnv
preludeEnv = preludeMacroEnv regexType
preludeTestsFailing :: [MacroID]
preludeTestsFailing = badMacros preludeEnv
preludeTable :: String
preludeTable = preludeMacroTable regexType
preludeSummary :: PreludeMacro -> String
preludeSummary = preludeMacroSummary regexType
preludeSources :: String
preludeSources = preludeMacroSources regexType
preludeSource :: PreludeMacro -> String
preludeSource = preludeMacroSource regexType
re :: QuasiQuoter
re = re' $ Just minBound
reMultilineSensitive :: QuasiQuoter
reMultilineSensitive = re' $ Just MultilineSensitive
reMultilineInsensitive :: QuasiQuoter
reMultilineInsensitive = re' $ Just MultilineInsensitive
reBlockSensitive :: QuasiQuoter
reBlockSensitive = re' $ Just BlockSensitive
reBlockInsensitive :: QuasiQuoter
reBlockInsensitive = re' $ Just BlockInsensitive
reMS :: QuasiQuoter
reMS = reMultilineSensitive
reMI :: QuasiQuoter
reMI = reMultilineInsensitive
reBS :: QuasiQuoter
reBS = reBlockSensitive
reBI :: QuasiQuoter
reBI = reBlockInsensitive
re_ :: QuasiQuoter
re_ = re' Nothing
re' :: Maybe SimpleREOptions -> QuasiQuoter
re' mb = case mb of
Nothing ->
(qq0 "re'")
{ quoteExp = parse minBound (\rs->[|flip unsafeCompileRegex rs|])
}
Just sro ->
(qq0 "re'")
{ quoteExp = parse sro (\rs->[|unsafeCompileRegexSimple sro rs|])
}
where
parse :: SimpleREOptions -> (String->Q Exp) -> String -> Q Exp
parse sro mk rs = poss error (\_->mk rs) $ compileRegex_ os rs
where
os = unpackSimpleREOptions sro
unsafeCompileRegexSimple :: SimpleREOptions -> String -> RE
unsafeCompileRegexSimple sro re_s = unsafeCompileRegex os re_s
where
os = unpackSimpleREOptions sro
unsafeCompileRegex :: IsOption o
=> o
-> String
-> RE
unsafeCompileRegex = unsafeCompileRegex_ . makeREOptions
unsafeCompileRegex_ :: REOptions -> String -> RE
unsafeCompileRegex_ os = poss oops id . compileRegexWithOptions os
where
oops = error . ("unsafeCompileRegex: " ++)
compileRegex' :: (Functor m,Monad m,MonadFail m)
=> REOptions
-> String
-> m (CaptureNames,Regex)
compileRegex' REOptions{..} s0 = do
((_,cnms),s2) <- either fail return $ extractNamedCaptures s1
(,) cnms <$> makeRegexOptsM optionsComp optionsExec s2
where
s1 = expandMacros reSource optionsMacs s0
compileRegex_ :: ( Functor m , Monad m, MonadFail m )
=> REOptions
-> String
-> m RE
compileRegex_ os re_s = uncurry mk <$> compileRegex' os re_s
where
mk cnms rex =
RE
{ _re_options = os
, _re_source = re_s
, _re_cnames = cnms
, _re_regex = rex
}
def_comp_option :: CompOption
def_comp_option = optionsComp defaultREOptions
def_exec_option :: ExecOption
def_exec_option = optionsExec defaultREOptions