module Text.Regex.TDFA.NewDFA.Tester(matchTest) where
import qualified Data.IntMap.CharMap2 as CMap(findWithDefault)
import qualified Data.IntMap as IMap(null)
import qualified Data.IntSet as ISet(null)
import Data.Sequence(Seq)
import qualified Data.ByteString.Char8 as SBS(ByteString)
import qualified Data.ByteString.Lazy.Char8 as LBS(ByteString)
import Text.Regex.Base()
import Text.Regex.TDFA.Common hiding (indent)
import Text.Regex.TDFA.NewDFA.Uncons (Uncons(uncons))
import Text.Regex.TDFA.NewDFA.MakeTest(test_singleline,test_multiline)
{-# SPECIALIZE matchTest :: Regex -> ([] Char) -> Bool #-}
{-# SPECIALIZE matchTest :: Regex -> (Seq Char) -> Bool #-}
{-# SPECIALIZE matchTest :: Regex -> SBS.ByteString -> Bool #-}
{-# SPECIALIZE matchTest :: Regex -> LBS.ByteString -> Bool #-}
matchTest :: Uncons text => Regex -> text -> Bool
matchTest :: Regex -> text -> Bool
matchTest (Regex { regex_dfa :: Regex -> DFA
regex_dfa = DFA
dfaIn
                 , regex_isFrontAnchored :: Regex -> Bool
regex_isFrontAnchored = Bool
ifa } )
          text
inputIn = Bool
ans where
  ans :: Bool
ans = case Bool
ifa of
          Bool
True -> DT -> text -> Bool
forall a. Uncons a => DT -> a -> Bool
single0 (DFA -> DT
d_dt DFA
dfaIn) text
inputIn
          Bool
False -> DT -> text -> Bool
forall a. Uncons a => DT -> a -> Bool
multi0 (DFA -> DT
d_dt DFA
dfaIn) text
inputIn
  multi0 :: DT -> a -> Bool
multi0 (Testing' {dt_test :: DT -> WhichTest
dt_test=WhichTest
wt,dt_a :: DT -> DT
dt_a=DT
a,dt_b :: DT -> DT
dt_b=DT
b}) a
input =
    if WhichTest -> a -> Bool
forall text. Uncons text => WhichTest -> text -> Bool
test0 WhichTest
wt a
input
      then DT -> a -> Bool
multi0 DT
a a
input
      else DT -> a -> Bool
multi0 DT
b a
input
  multi0 (Simple' {dt_win :: DT -> IntMap Instructions
dt_win=IntMap Instructions
w,dt_trans :: DT -> CharMap Transition
dt_trans=CharMap Transition
t, dt_other :: DT -> Transition
dt_other=Transition
o}) a
input
    | IntMap Instructions -> Bool
forall a. IntMap a -> Bool
IMap.null IntMap Instructions
w =
        case a -> Maybe (Char, a)
forall a. Uncons a => a -> Maybe (Char, a)
uncons a
input of
          Maybe (Char, a)
Nothing -> Bool
False
          Just (Char
c,a
input') ->
            case Transition -> Char -> CharMap Transition -> Transition
forall a. a -> Char -> CharMap a -> a
CMap.findWithDefault Transition
o Char
c CharMap Transition
t of
              Transition {trans_many :: Transition -> DFA
trans_many=DFA {d_dt :: DFA -> DT
d_dt=DT
dt'}} -> DT -> Char -> a -> Bool
forall a. Uncons a => DT -> Char -> a -> Bool
multi DT
dt' Char
c a
input'
    | Bool
otherwise = Bool
True
  multi :: DT -> Char -> a -> Bool
multi (Testing' {dt_test :: DT -> WhichTest
dt_test=WhichTest
wt,dt_a :: DT -> DT
dt_a=DT
a,dt_b :: DT -> DT
dt_b=DT
b}) Char
prev a
input =
    if WhichTest -> Char -> a -> Bool
forall text. Uncons text => WhichTest -> Char -> text -> Bool
test WhichTest
wt Char
prev a
input
      then DT -> Char -> a -> Bool
multi DT
a Char
prev a
input
      else DT -> Char -> a -> Bool
multi DT
b Char
prev a
input
  multi (Simple' {dt_win :: DT -> IntMap Instructions
dt_win=IntMap Instructions
w,dt_trans :: DT -> CharMap Transition
dt_trans=CharMap Transition
t, dt_other :: DT -> Transition
dt_other=Transition
o}) Char
_prev a
input
    | IntMap Instructions -> Bool
forall a. IntMap a -> Bool
IMap.null IntMap Instructions
w =
        case a -> Maybe (Char, a)
forall a. Uncons a => a -> Maybe (Char, a)
uncons a
input of
          Maybe (Char, a)
Nothing -> Bool
False
          Just (Char
c,a
input') ->
            case Transition -> Char -> CharMap Transition -> Transition
forall a. a -> Char -> CharMap a -> a
CMap.findWithDefault Transition
o Char
c CharMap Transition
t of
              Transition {trans_many :: Transition -> DFA
trans_many=DFA {d_dt :: DFA -> DT
d_dt=DT
dt'}} -> DT -> Char -> a -> Bool
multi DT
dt' Char
c a
input'
    | Bool
otherwise = Bool
True
  single0 :: DT -> a -> Bool
single0 (Testing' {dt_test :: DT -> WhichTest
dt_test=WhichTest
wt,dt_a :: DT -> DT
dt_a=DT
a,dt_b :: DT -> DT
dt_b=DT
b}) a
input =
    if WhichTest -> a -> Bool
forall text. Uncons text => WhichTest -> text -> Bool
testFA0 WhichTest
wt a
input
      then DT -> a -> Bool
single0 DT
a a
input
      else DT -> a -> Bool
single0 DT
b a
input
  single0 (Simple' {dt_win :: DT -> IntMap Instructions
dt_win=IntMap Instructions
w,dt_trans :: DT -> CharMap Transition
dt_trans=CharMap Transition
t, dt_other :: DT -> Transition
dt_other=Transition
o}) a
input
    | IntMap Instructions -> Bool
forall a. IntMap a -> Bool
IMap.null IntMap Instructions
w =
        case a -> Maybe (Char, a)
forall a. Uncons a => a -> Maybe (Char, a)
uncons a
input of
             Maybe (Char, a)
Nothing -> Bool
False
             Just (Char
c,a
input') ->
               case Transition -> Char -> CharMap Transition -> Transition
forall a. a -> Char -> CharMap a -> a
CMap.findWithDefault Transition
o Char
c CharMap Transition
t of
                 Transition {trans_single :: Transition -> DFA
trans_single=DFA {d_id :: DFA -> SetIndex
d_id=SetIndex
did',d_dt :: DFA -> DT
d_dt=DT
dt'}}
                   | SetIndex -> Bool
ISet.null SetIndex
did' -> Bool
False
                   | Bool
otherwise -> DT -> Char -> a -> Bool
forall a. Uncons a => DT -> Char -> a -> Bool
single DT
dt' Char
c a
input'
    | Bool
otherwise = Bool
True
  single :: DT -> Char -> a -> Bool
single (Testing' {dt_test :: DT -> WhichTest
dt_test=WhichTest
wt,dt_a :: DT -> DT
dt_a=DT
a,dt_b :: DT -> DT
dt_b=DT
b}) Char
prev a
input =
    if WhichTest -> Char -> a -> Bool
forall text. Uncons text => WhichTest -> Char -> text -> Bool
testFA WhichTest
wt Char
prev a
input
      then DT -> Char -> a -> Bool
single DT
a Char
prev a
input
      else DT -> Char -> a -> Bool
single DT
b Char
prev a
input
  single (Simple' {dt_win :: DT -> IntMap Instructions
dt_win=IntMap Instructions
w,dt_trans :: DT -> CharMap Transition
dt_trans=CharMap Transition
t, dt_other :: DT -> Transition
dt_other=Transition
o}) Char
_prev a
input
    | IntMap Instructions -> Bool
forall a. IntMap a -> Bool
IMap.null IntMap Instructions
w =
        case a -> Maybe (Char, a)
forall a. Uncons a => a -> Maybe (Char, a)
uncons a
input of
             Maybe (Char, a)
Nothing -> Bool
False
             Just (Char
c,a
input') ->
               case Transition -> Char -> CharMap Transition -> Transition
forall a. a -> Char -> CharMap a -> a
CMap.findWithDefault Transition
o Char
c CharMap Transition
t of
                 Transition {trans_single :: Transition -> DFA
trans_single=DFA {d_id :: DFA -> SetIndex
d_id=SetIndex
did',d_dt :: DFA -> DT
d_dt=DT
dt'}}
                   | SetIndex -> Bool
ISet.null SetIndex
did' -> Bool
False
                   | Bool
otherwise -> DT -> Char -> a -> Bool
single DT
dt' Char
c a
input'
    | Bool
otherwise = Bool
True
{-# INLINE testFA0 #-}
testFA0 :: Uncons text => WhichTest -> text -> Bool
testFA0 :: WhichTest -> text -> Bool
testFA0 WhichTest
wt text
text = WhichTest -> Index -> Char -> text -> Bool
forall text.
Uncons text =>
WhichTest -> Index -> Char -> text -> Bool
test_singleline WhichTest
wt Index
0 Char
'\n' text
text
{-# INLINE testFA #-}
testFA :: Uncons text => WhichTest -> Char -> text -> Bool
testFA :: WhichTest -> Char -> text -> Bool
testFA WhichTest
wt Char
prev text
text = WhichTest -> Index -> Char -> text -> Bool
forall text.
Uncons text =>
WhichTest -> Index -> Char -> text -> Bool
test_singleline WhichTest
wt Index
1 Char
prev text
text
{-# INLINE test0 #-}
test0 :: Uncons text => WhichTest -> text -> Bool
test0 :: WhichTest -> text -> Bool
test0 WhichTest
wt text
input = WhichTest -> Index -> Char -> text -> Bool
forall text.
Uncons text =>
WhichTest -> Index -> Char -> text -> Bool
test_multiline WhichTest
wt Index
0 Char
'\n' text
input
{-# INLINE test #-}
test :: Uncons text => WhichTest -> Char -> text -> Bool
test :: WhichTest -> Char -> text -> Bool
test WhichTest
wt Char
prev text
input = WhichTest -> Index -> Char -> text -> Bool
forall text.
Uncons text =>
WhichTest -> Index -> Char -> text -> Bool
test_multiline WhichTest
wt Index
1 Char
prev text
input