module Text.Regex.Base.RegexLike (
  
  MatchOffset,
  MatchLength,
  MatchArray,
  MatchText,
  
  MatchResult(..),
  
  RegexOptions(..),
  RegexMaker(..),
  RegexLike(..),
  RegexContext(..),
  Extract(..),
  AllSubmatches(..),AllTextSubmatches(..),AllMatches(..),AllTextMatches(..)
  ) where
import Prelude
  (Int, Bool, String
  , (.), (+)
  , error, id, return, snd
  , drop, fmap, length, map, take
  , toEnum
  )
import Control.Monad.Fail (MonadFail)
import Data.Array(Array,(!))
import Data.Maybe(Maybe,isJust,maybe)
import qualified Data.ByteString as SB (take,drop,empty,ByteString)
import qualified Data.ByteString.Lazy as LB (take,drop,empty,ByteString)
import qualified Data.Sequence as S(take,drop,empty,Seq)
import qualified Data.Text as ST (take,drop,empty,Text)
import qualified Data.Text.Lazy as LT (take,drop,empty,Text)
type MatchOffset = Int
type MatchLength = Int
type MatchArray = Array Int (MatchOffset,MatchLength)
type MatchText source = Array Int (source,(MatchOffset,MatchLength))
data MatchResult a = MR {
    forall a. MatchResult a -> a
mrBefore :: a,
    forall a. MatchResult a -> a
mrMatch  :: a,
    forall a. MatchResult a -> a
mrAfter  :: a,
    forall a. MatchResult a -> [a]
mrSubList :: [a],
    forall a. MatchResult a -> Array Int a
mrSubs   :: Array Int a
}
class RegexOptions regex compOpt execOpt
  | regex   -> compOpt execOpt
  , compOpt -> regex execOpt
  , execOpt -> regex compOpt
  where
  
  blankCompOpt   :: compOpt
  
  blankExecOpt   :: execOpt
  
  defaultCompOpt :: compOpt
  
  defaultExecOpt :: execOpt
  
  setExecOpts    :: execOpt -> regex -> regex
  
  getExecOpts    :: regex -> execOpt
class (RegexOptions regex compOpt execOpt) => RegexMaker regex compOpt execOpt source
  | regex -> compOpt execOpt, compOpt -> regex execOpt, execOpt -> regex compOpt where
  
  makeRegex :: source -> regex
  
  makeRegexOpts :: compOpt -> execOpt -> source -> regex
  
  makeRegexM :: (MonadFail m) => source -> m regex
  
  makeRegexOptsM :: (MonadFail m) => compOpt -> execOpt -> source -> m regex
  makeRegex = compOpt -> execOpt -> source -> regex
forall regex compOpt execOpt source.
RegexMaker regex compOpt execOpt source =>
compOpt -> execOpt -> source -> regex
makeRegexOpts compOpt
forall regex compOpt execOpt.
RegexOptions regex compOpt execOpt =>
compOpt
defaultCompOpt execOpt
forall regex compOpt execOpt.
RegexOptions regex compOpt execOpt =>
execOpt
defaultExecOpt
  makeRegexM = compOpt -> execOpt -> source -> m regex
forall regex compOpt execOpt source (m :: * -> *).
(RegexMaker regex compOpt execOpt source, MonadFail m) =>
compOpt -> execOpt -> source -> m regex
forall (m :: * -> *).
MonadFail m =>
compOpt -> execOpt -> source -> m regex
makeRegexOptsM compOpt
forall regex compOpt execOpt.
RegexOptions regex compOpt execOpt =>
compOpt
defaultCompOpt execOpt
forall regex compOpt execOpt.
RegexOptions regex compOpt execOpt =>
execOpt
defaultExecOpt
  makeRegexOpts compOpt
c execOpt
e source
s = regex -> (regex -> regex) -> Maybe regex -> regex
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ([Char] -> regex
forall a. HasCallStack => [Char] -> a
error [Char]
"makeRegexOpts failed") regex -> regex
forall a. a -> a
id (compOpt -> execOpt -> source -> Maybe regex
forall regex compOpt execOpt source (m :: * -> *).
(RegexMaker regex compOpt execOpt source, MonadFail m) =>
compOpt -> execOpt -> source -> m regex
forall (m :: * -> *).
MonadFail m =>
compOpt -> execOpt -> source -> m regex
makeRegexOptsM compOpt
c execOpt
e source
s)
  makeRegexOptsM compOpt
c execOpt
e source
s = regex -> m regex
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (compOpt -> execOpt -> source -> regex
forall regex compOpt execOpt source.
RegexMaker regex compOpt execOpt source =>
compOpt -> execOpt -> source -> regex
makeRegexOpts compOpt
c execOpt
e source
s)
class (Extract source) => RegexLike regex source where
  
  
  
  
  
  
  matchOnce  :: regex -> source -> Maybe MatchArray
  
  
  
  matchAll   :: regex -> source -> [MatchArray]
  
  
  matchCount :: regex -> source -> Int
  
  
  matchTest  :: regex -> source -> Bool
  
  
  matchAllText  :: regex -> source -> [MatchText source]
  
  
  
  matchOnceText :: regex -> source -> Maybe (source, MatchText source, source)
  matchAll regex
regex source
source = (Array Int (source, (Int, Int)) -> MatchArray)
-> [Array Int (source, (Int, Int))] -> [MatchArray]
forall a b. (a -> b) -> [a] -> [b]
map (((source, (Int, Int)) -> (Int, Int))
-> Array Int (source, (Int, Int)) -> MatchArray
forall a b. (a -> b) -> Array Int a -> Array Int b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (source, (Int, Int)) -> (Int, Int)
forall a b. (a, b) -> b
snd) (regex -> source -> [Array Int (source, (Int, Int))]
forall regex source.
RegexLike regex source =>
regex -> source -> [Array Int (source, (Int, Int))]
matchAllText regex
regex source
source)
  matchOnce regex
regex source
source = ((source, Array Int (source, (Int, Int)), source) -> MatchArray)
-> Maybe (source, Array Int (source, (Int, Int)), source)
-> Maybe MatchArray
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(source
_,Array Int (source, (Int, Int))
mt,source
_) -> ((source, (Int, Int)) -> (Int, Int))
-> Array Int (source, (Int, Int)) -> MatchArray
forall a b. (a -> b) -> Array Int a -> Array Int b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (source, (Int, Int)) -> (Int, Int)
forall a b. (a, b) -> b
snd Array Int (source, (Int, Int))
mt) (regex
-> source -> Maybe (source, Array Int (source, (Int, Int)), source)
forall regex source.
RegexLike regex source =>
regex
-> source -> Maybe (source, Array Int (source, (Int, Int)), source)
matchOnceText regex
regex source
source)
  matchTest regex
regex source
source = Maybe MatchArray -> Bool
forall a. Maybe a -> Bool
isJust (regex -> source -> Maybe MatchArray
forall regex source.
RegexLike regex source =>
regex -> source -> Maybe MatchArray
matchOnce regex
regex source
source)
  matchCount regex
regex source
source = [MatchArray] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (regex -> source -> [MatchArray]
forall regex source.
RegexLike regex source =>
regex -> source -> [MatchArray]
matchAll regex
regex source
source)
  matchOnceText regex
regex source
source =
    (MatchArray -> (source, Array Int (source, (Int, Int)), source))
-> Maybe MatchArray
-> Maybe (source, Array Int (source, (Int, Int)), source)
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\MatchArray
ma -> let (Int
o,Int
l) = MatchArray
ma MatchArray -> Int -> (Int, Int)
forall i e. Ix i => Array i e -> i -> e
! Int
0
                 in (Int -> source -> source
forall source. Extract source => Int -> source -> source
before Int
o source
source
                    ,((Int, Int) -> (source, (Int, Int)))
-> MatchArray -> Array Int (source, (Int, Int))
forall a b. (a -> b) -> Array Int a -> Array Int b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(Int, Int)
ol -> ((Int, Int) -> source -> source
forall source. Extract source => (Int, Int) -> source -> source
extract (Int, Int)
ol source
source,(Int, Int)
ol)) MatchArray
ma
                    ,Int -> source -> source
forall source. Extract source => Int -> source -> source
after (Int
oInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
l) source
source))
         (regex -> source -> Maybe MatchArray
forall regex source.
RegexLike regex source =>
regex -> source -> Maybe MatchArray
matchOnce regex
regex source
source)
  matchAllText regex
regex source
source =
    (MatchArray -> Array Int (source, (Int, Int)))
-> [MatchArray] -> [Array Int (source, (Int, Int))]
forall a b. (a -> b) -> [a] -> [b]
map (((Int, Int) -> (source, (Int, Int)))
-> MatchArray -> Array Int (source, (Int, Int))
forall a b. (a -> b) -> Array Int a -> Array Int b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(Int, Int)
ol -> ((Int, Int) -> source -> source
forall source. Extract source => (Int, Int) -> source -> source
extract (Int, Int)
ol source
source,(Int, Int)
ol)))
        (regex -> source -> [MatchArray]
forall regex source.
RegexLike regex source =>
regex -> source -> [MatchArray]
matchAll regex
regex source
source)
class (RegexLike regex source) => RegexContext regex source target where
  match :: regex -> source -> target
  matchM :: (MonadFail m) => regex -> source -> m target
class  source where
  
  before :: Int -> source -> source
  
  after :: Int -> source -> source
  
  empty :: source
  
  
  
  
  
   :: (Int,Int) -> source -> source
  extract (Int
off,Int
len) source
source = Int -> source -> source
forall source. Extract source => Int -> source -> source
before Int
len (Int -> source -> source
forall source. Extract source => Int -> source -> source
after Int
off source
source)
instance Extract String where
  before :: Int -> [Char] -> [Char]
before =  Int -> [Char] -> [Char]
forall a. Int -> [a] -> [a]
take; after :: Int -> [Char] -> [Char]
after = Int -> [Char] -> [Char]
forall a. Int -> [a] -> [a]
drop; empty :: [Char]
empty = []
instance Extract SB.ByteString where
  before :: Int -> ByteString -> ByteString
before = Int -> ByteString -> ByteString
SB.take; after :: Int -> ByteString -> ByteString
after = Int -> ByteString -> ByteString
SB.drop; empty :: ByteString
empty = ByteString
SB.empty
instance Extract LB.ByteString where
  before :: Int -> ByteString -> ByteString
before = Int64 -> ByteString -> ByteString
LB.take (Int64 -> ByteString -> ByteString)
-> (Int -> Int64) -> Int -> ByteString -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int64
forall a. Enum a => Int -> a
toEnum; after :: Int -> ByteString -> ByteString
after = Int64 -> ByteString -> ByteString
LB.drop (Int64 -> ByteString -> ByteString)
-> (Int -> Int64) -> Int -> ByteString -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int64
forall a. Enum a => Int -> a
toEnum; empty :: ByteString
empty = ByteString
LB.empty
instance Extract (S.Seq a) where
  before :: Int -> Seq a -> Seq a
before = Int -> Seq a -> Seq a
forall a. Int -> Seq a -> Seq a
S.take; after :: Int -> Seq a -> Seq a
after = Int -> Seq a -> Seq a
forall a. Int -> Seq a -> Seq a
S.drop; empty :: Seq a
empty = Seq a
forall a. Seq a
S.empty
instance Extract ST.Text where
  before :: Int -> Text -> Text
before = Int -> Text -> Text
ST.take; after :: Int -> Text -> Text
after = Int -> Text -> Text
ST.drop; empty :: Text
empty = Text
ST.empty
instance Extract LT.Text where
  before :: Int -> Text -> Text
before = Int64 -> Text -> Text
LT.take (Int64 -> Text -> Text) -> (Int -> Int64) -> Int -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int64
forall a. Enum a => Int -> a
toEnum; after :: Int -> Text -> Text
after = Int64 -> Text -> Text
LT.drop (Int64 -> Text -> Text) -> (Int -> Int64) -> Int -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int64
forall a. Enum a => Int -> a
toEnum; empty :: Text
empty = Text
LT.empty
newtype AllSubmatches f b = AllSubmatches {forall (f :: * -> *) b. AllSubmatches f b -> f b
getAllSubmatches :: (f b)}
newtype AllTextSubmatches f b = AllTextSubmatches {forall (f :: * -> *) b. AllTextSubmatches f b -> f b
getAllTextSubmatches :: (f b)}
newtype AllMatches f b = AllMatches {forall (f :: * -> *) b. AllMatches f b -> f b
getAllMatches :: (f b)}
newtype AllTextMatches f b = AllTextMatches {forall (f :: * -> *) b. AllTextMatches f b -> f b
getAllTextMatches :: (f b) }