| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Text.Regex.Do.Type.Regex
- class Regex a where
- makeRegex' :: Regex a => Pattern a -> Pattern Regex
- makeRegexOpt' :: Regex a => Pattern a -> [Comp] -> [Exec] -> Pattern Regex
- newtype RegexResult a = RegexResult (Either [String] a)
- type Rx_ a b = (Regex a, Extract b, RegexLike Regex b)
- type Opt_ a = RegexMaker Regex CompOption ExecOption a
- type Ro_ rx = (Regex rx, Opt_ rx)
Documentation
monadic
let catch regex construction errors
for m to catch errors, implement fail in m
default m implementation: RegexResult
makeRegexM test case:
>>>it "RegexResult test case" $ dorx1 `shouldNotSatisfy` isok1 rx2 `shouldSatisfy` isok1 where rx1 = T.makeRegexM $ Pattern "[["::RegexResult R.Regex rx2 = T.makeRegexM $ Pattern "."::RegexResult R.Regex isok1 (RegexResult (Left e1)) = traceShow e1 False isok1 _ = True
>>>instance Show (RegexResult R.Regex) whereshow _ = "bon"
newtype RegexResult a Source
catches regex construction errors
Constructors
| RegexResult (Either [String] a) |
type Opt_ a = RegexMaker Regex CompOption ExecOption a Source