{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
module Headroom.Data.Regex
(
Regex(..)
, RegexError(..)
, compile
, match
, re
, replace
, scan
, compileUnsafe
)
where
import Data.Aeson ( FromJSON(..)
, Value(String)
)
import Headroom.Types ( fromHeadroomError
, toHeadroomError
)
import Language.Haskell.TH hiding ( match )
import Language.Haskell.TH.Quote ( QuasiQuoter(..) )
import RIO
import qualified RIO.Text as T
import qualified Text.Regex.PCRE.Heavy as PH
import qualified Text.Regex.PCRE.Light as PL
import qualified Text.Regex.PCRE.Light.Char8 as PLC
newtype Regex = Regex PL.Regex deriving (Eq, Show)
instance FromJSON Regex where
parseJSON (String s) = pure . compileUnsafe $ s
parseJSON val = error $ "Invalid value: expected regex, found: " <> show val
compile :: MonadThrow m
=> Text
-> m Regex
compile raw = either (throwM . CompilationFailed raw . T.pack) pure compile'
where compile' = Regex <$> PH.compileM (encodeUtf8 raw) [PLC.utf8]
match :: Regex
-> Text
-> Maybe [Text]
match (Regex r) subject = fmap T.pack <$> PLC.match r (T.unpack subject) []
re :: QuasiQuoter
re = QuasiQuoter { quoteExp = quoteExpRegex
, quotePat = undefined
, quoteType = undefined
, quoteDec = undefined
}
replace :: Regex
-> (Text -> [Text] -> Text)
-> Text
-> Text
replace (Regex regex) = PH.gsub regex
scan :: Regex
-> Text
-> [(Text, [Text])]
scan (Regex regex) = PH.scan regex
compileUnsafe :: Text
-> Regex
compileUnsafe raw = case compile raw of
Left err -> error . displayException $ err
Right res -> res
quoteExpRegex :: String -> ExpQ
quoteExpRegex txt = [| compileUnsafe . T.pack $ txt |]
where !_ = compileUnsafe . T.pack $ txt
data RegexError = CompilationFailed !Text !Text
deriving (Show, Typeable)
instance Exception RegexError where
displayException = displayException'
toException = toHeadroomError
fromException = fromHeadroomError
displayException' :: RegexError -> String
displayException' = T.unpack . \case
CompilationFailed raw reason ->
mconcat ["Cannot compile regex from input '", raw, "', reason: ", reason]