{-# LANGUAGE OverloadedStrings #-} module Regex.KDE (Regex(..), compileRegex, matchRegex, testRegex, isWordChar) where import Regex.KDE.Regex import Regex.KDE.Compile import Regex.KDE.Match import qualified Data.ByteString.UTF8 as U import qualified Data.IntMap.Strict as M import qualified Data.ByteString as B import Data.List (sortOn) testRegex :: Bool -> String -> String -> Maybe (String, [(Int, String)]) testRegex :: Bool -> String -> String -> Maybe (String, [(Int, String)]) testRegex Bool caseSensitive String re String s = let bs :: ByteString bs = String -> ByteString U.fromString String s toSlice :: (Int, Int) -> String toSlice (Int off,Int len) = ByteString -> String U.toString forall a b. (a -> b) -> a -> b $ Int -> ByteString -> ByteString B.take Int len forall a b. (a -> b) -> a -> b $ Int -> ByteString -> ByteString B.drop Int off ByteString bs in case Bool -> ByteString -> Either String Regex compileRegex Bool caseSensitive (String -> ByteString U.fromString String re) of Right Regex r -> case Regex -> ByteString -> Maybe (ByteString, IntMap (Int, Int)) matchRegex Regex r ByteString bs of Maybe (ByteString, IntMap (Int, Int)) Nothing -> forall a. Maybe a Nothing Just (ByteString m,IntMap (Int, Int) cs) -> forall a. a -> Maybe a Just (ByteString -> String U.toString ByteString m, forall b a. Ord b => (a -> b) -> [a] -> [a] sortOn forall a b. (a, b) -> a fst (forall a. IntMap a -> [(Int, a)] M.toList (forall a b. (a -> b) -> IntMap a -> IntMap b M.map (Int, Int) -> String toSlice IntMap (Int, Int) cs))) Left String e -> forall a. HasCallStack => String -> a error String e