module TestRegex.TestPcre where import Test.Hspec import Text.Regex.Do.Type.Do as M import Text.Regex.Do.Pcre.Match as M import Text.Regex.Do.Convert import Data.ByteString import Text.Regex.Do.Pcre.MatchHint as S import Text.Regex.Do.Type.MatchHint as S main::IO() main = hspec $ describe " matchTest " $ do it " ?String " $ (M.match (Pattern n) h::[String]) `shouldBe` ["d1"] it " [String] " $ (M.match (Pattern n) h::[[String]]) `shouldBe` [["d1"],["d1"]] it " ?ByteString " $ (M.match (Pattern $ b n) (b <$> h)::[ByteString]) `shouldBe` [b "d1"] it " [ByteString] " $ (M.match (Pattern $ b n) (b <$> h)::[[ByteString]]) `shouldBe` [[b "d1"],[b "d1"]] it " ша " $ S.match (Test $ Pattern ("^ша"::String)) (Body "шапка") `shouldBe` True it " cd " $ S.match (Test $ Pattern ("^cd"::String)) (Body "abcde") `shouldBe` False it " cd " $ S.match (PosLen' $ Pattern ("^cd"::String)) (Body "abcde") `shouldBe` [] it " ab " $ S.match (Test $ Pattern ("^ab"::String)) (Body "abc") `shouldBe` True it "doc 1" $ Test ("в"::ByteString) S.=~ "тихо в лесу" `shouldBe` True it "doc 2" $ S.Once ("^all"::String) S.=~ "all the time" `shouldBe` ["all"] it "doc 3" $ S.Once ("^all"::ByteString) S.=~ "all the time" `shouldBe` ["all"] it "doc 4" $ S.All ("well"::ByteString) S.=~ "all is well that ends well" `shouldBe` ([["well"],["well"]]) it "doc 5" $ PosLen' ("и"::String) S.=~ "бывает и хуже" `shouldBe` [(13,2)] n = "d1" h = Body "abcd1efg d1hij" b = toByteString