module Language.Lexer.Tlex.Plugin.Encoding.CharSetP ( Pattern, CharSetStdP, CharSetP (..), charSetP, charSetPWithWarnings, chP, charsP, stringP, EncodeWarning (..), CharSetEncoder (..), ) where import Language.Lexer.Tlex.Prelude import qualified Data.CharSet as CharSet import qualified Data.String as String import qualified Language.Lexer.Tlex.Data.Reporter as Reporter import qualified Language.Lexer.Tlex.Syntax as Tlex type Pattern = Tlex.Pattern Word8 type CharSetStdP = CharSetP Identity newtype CharSetP m = CharSetP { forall (m :: * -> *). CharSetP m -> CharSet -> m Pattern charSetEncodingP :: CharSet.CharSet -> m Pattern } data EncodeWarning = NotSupportedChar Char | CustomWarning String.String deriving (EncodeWarning -> EncodeWarning -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: EncodeWarning -> EncodeWarning -> Bool $c/= :: EncodeWarning -> EncodeWarning -> Bool == :: EncodeWarning -> EncodeWarning -> Bool $c== :: EncodeWarning -> EncodeWarning -> Bool Eq, Int -> EncodeWarning -> ShowS [EncodeWarning] -> ShowS EncodeWarning -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [EncodeWarning] -> ShowS $cshowList :: [EncodeWarning] -> ShowS show :: EncodeWarning -> String $cshow :: EncodeWarning -> String showsPrec :: Int -> EncodeWarning -> ShowS $cshowsPrec :: Int -> EncodeWarning -> ShowS Show) charSetP :: CharSetStdP -> CharSet.CharSet -> Pattern charSetP :: CharSetStdP -> CharSet -> Pattern charSetP CharSetStdP p CharSet cs = forall a. Identity a -> a runIdentity do forall (m :: * -> *). CharSetP m -> CharSet -> m Pattern charSetEncodingP CharSetStdP p CharSet cs charSetPWithWarnings :: CharSetEncoder m => CharSetP m -> CharSet.CharSet -> m Pattern charSetPWithWarnings :: forall (m :: * -> *). CharSetEncoder m => CharSetP m -> CharSet -> m Pattern charSetPWithWarnings CharSetP m p CharSet cs = forall (m :: * -> *). CharSetP m -> CharSet -> m Pattern charSetEncodingP CharSetP m p CharSet cs chP :: CharSetStdP -> Char -> Pattern chP :: CharSetStdP -> Char -> Pattern chP CharSetStdP p Char c = CharSetStdP -> CharSet -> Pattern charSetP CharSetStdP p do Char -> CharSet CharSet.singleton Char c charsP :: CharSetStdP -> [Char] -> Pattern charsP :: CharSetStdP -> String -> Pattern charsP CharSetStdP p String cs = CharSetStdP -> CharSet -> Pattern charSetP CharSetStdP p do String -> CharSet CharSet.fromList String cs stringP :: CharSetStdP -> String.String -> Pattern stringP :: CharSetStdP -> String -> Pattern stringP CharSetStdP p String s = forall (t :: * -> *) m a. (Foldable t, Monoid m) => (a -> m) -> t a -> m foldMap do CharSetStdP -> Char -> Pattern chP CharSetStdP p do String s class Monad m => CharSetEncoder m where reportEncodeWarning :: EncodeWarning -> m () instance CharSetEncoder Identity where reportEncodeWarning :: EncodeWarning -> Identity () reportEncodeWarning EncodeWarning _ = forall (f :: * -> *) a. Applicative f => a -> f a pure () instance CharSetEncoder (Either EncodeWarning) where reportEncodeWarning :: EncodeWarning -> Either EncodeWarning () reportEncodeWarning EncodeWarning e = forall a b. a -> Either a b Left EncodeWarning e instance CharSetEncoder (Reporter.Reporter EncodeWarning) where reportEncodeWarning :: EncodeWarning -> Reporter EncodeWarning () reportEncodeWarning EncodeWarning e = forall e. e -> Reporter e () Reporter.report EncodeWarning e