{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE DataKinds #-}
module Text.Regex.Wrapper
( Matched()
, parseMatched
, parseMatchedEither
, parseMatchedM
, asStr
, asText
, asString
, asByteString
, compile
, parseMatchedWith
, parseMatchedEitherWith
, RegexPat()
) where
import Prelude hiding (fail)
import Control.Monad hiding (fail)
import Control.Monad.Fail
import Data.ByteString (ByteString)
import Data.Text (Text)
import Data.Proxy
import GHC.TypeLits
import Text.Regex.TDFA as TDFA
import Data.Hashable
import Data.Aeson
import Data.CaseInsensitive as CI
data RegexError str = NoMatch (MatchError str) | CompileError String
deriving Show
prettyRegexError :: Show str => RegexError str -> String
prettyRegexError (NoMatch err) = prettyMatchError err
prettyRegexError (CompileError err) = "Invalid regular expression: " ++ err
data MatchError str = MatchError
{ matchErrorPattern :: String
, matchErrorInput :: str
} deriving Show
prettyMatchError :: Show str => MatchError str -> String
prettyMatchError err
= "The input "
++ show (matchErrorInput err)
++ " did not match the pattern "
++ matchErrorPattern err
newtype RegexPat (pat :: Symbol) = RegexPat { unwrap :: TDFA.Regex }
compile :: forall pat m. (KnownSymbol pat) => Either String (RegexPat pat)
compile =
let
pat = symbolVal (Proxy :: Proxy pat)
in
case RegexPat <$> makeRegexM pat of
Success a -> Right a
Error s -> Left s
parseMatchedWith
:: RegexLike Regex str
=> RegexPat pat -> str -> Maybe (Matched str pat)
parseMatchedWith (RegexPat pat) str = do
guard $ matchTest pat str
pure (Matched str)
parseMatchedEitherWith
:: forall pat str m.
( RegexLike Regex str
, Show str
, KnownSymbol pat
) => RegexPat pat -> str -> Either (MatchError str) (Matched str pat)
parseMatchedEitherWith reg str = do
let pat = symbolVal (Proxy :: Proxy pat)
case parseMatchedWith reg str of
Nothing -> Left MatchError
{ matchErrorPattern = pat
, matchErrorInput = str
}
Just x -> Right x
newtype Matched str (pat :: Symbol) = Matched str
deriving newtype (Show, Eq, Ord, Hashable, FoldCase)
asStr :: Matched str pat -> str
asStr (Matched str) = str
instance (KnownSymbol pat, RegexLike Regex str, Read str)
=> Read (Matched str pat) where
readsPrec p s = do
r@(a,s) <- readsPrec p s
Just m <- pure (parseMatched a)
pure (m, s)
instance ToJSON str => ToJSON (Matched str pat) where
toJSON = toJSON . asStr
toEncoding = toEncoding . asStr
instance (KnownSymbol pat, Show str, FromJSON str, RegexLike Regex str)
=> FromJSON (Matched str pat) where
parseJSON v = parseJSON v >>= either (fail . prettyRegexError) pure . parseMatchedEither
asText :: Matched Text p -> Text
asText = asStr
asString :: Matched String p -> String
asString = asStr
asByteString :: Matched ByteString p -> ByteString
asByteString = asStr
parseMatched
:: forall str pat. (KnownSymbol pat, RegexLike Regex str)
=> str -> Maybe (Matched str pat)
parseMatched str = case compile of
Left _ -> Nothing
Right r -> parseMatchedWith r str
parseMatchedEither
:: forall pat str. (Show str, KnownSymbol pat, RegexLike Regex str)
=> str -> Either (RegexError str) (Matched str pat)
parseMatchedEither str = do
case compile of
Left e -> Left $ CompileError e
Right r -> case parseMatchedEitherWith r str of
Left e -> Left $ NoMatch e
Right r -> pure r
parseMatchedM
:: forall pat str m.
( KnownSymbol pat, RegexLike Regex str, MonadFail m, Show str)
=> str -> m (Matched str pat)
parseMatchedM str = case parseMatchedEither str of
Left e -> fail $ prettyRegexError e
Right r -> pure r