rex: A quasi-quoter for typeful results of regex captures.

[ bsd3, control, library ] [ Propose Tags ]

Provides a quasi-quoter for regular expressions which yields a tuple, of appropriate arity and types, representing the results of the captures. Allows the user to specify parsers for captures as inline Haskell. Can also be used to provide typeful pattern matching in function definitions and pattern matches. Also, it precompiles the regular expressions into a PCRE compiled byte-array representation, at compile time.


[Skip to Readme]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 0.1, 0.2, 0.3, 0.3.1, 0.4.1, 0.4.2, 0.4.3, 0.5, 0.5.1, 0.5.2, 0.6, 0.6.1, 0.6.2
Change log changelog.md
Dependencies base (>=3.0 && <6), bytestring, containers, haskell-src-exts (>=1.14), haskell-src-meta (>=0.5), pcre-light, template-haskell (>=2.5.0.0) [details]
License BSD-3-Clause
Copyright Michael Sloan 2011
Author Michael Sloan
Maintainer Michael Sloan <mgsloan at gmail>
Category Control
Home page http://github.com/mgsloan/rex
Bug tracker http://github.com/mgsloan/rex/issues
Source repo head: git clone git://github.com/mgsloan/rex
Uploaded by MichaelSloan at 2020-04-11T23:03:21Z
Distributions LTSHaskell:0.6.2, NixOS:0.6.2, Stackage:0.6.2
Reverse Dependencies 1 direct, 0 indirect [details]
Downloads 8461 total (42 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2020-04-12 [all 1 reports]

Readme for rex-0.6.1

[back to package description]

http://hackage.haskell.org/package/rex

Provides a quasi-quoter for regular expressions which yields a tuple, of appropriate arity and types, representing the results of the captures. Allows the user to specify parsers for captures as inline Haskell. Can also be used to provide typeful pattern matching in function definitions and case patterns.

To build / install:

./Setup.hs configure --user
./Setup.hs build
./Setup.hs install

See the haddock or Text/Regex/PCRE/Rex.hs for documentation.

Some examples (verbatim from Test.hs):

math x = mathl x 0

mathl [] x = x
mathl [rex|^  \s*(?{ read -> y }\d+)\s*(?{ s }.*)$|] x = mathl s y
mathl [rex|^\+\s*(?{ read -> y }\d+)\s*(?{ s }.*)$|] x = mathl s $ x + y
mathl [rex|^ -\s*(?{ read -> y }\d+)\s*(?{ s }.*)$|] x = mathl s $ x - y
mathl [rex|^\*\s*(?{ read -> y }\d+)\s*(?{ s }.*)$|] x = mathl s $ x * y
mathl [rex|^ /\s*(?{ read -> y }\d+)\s*(?{ s }.*)$|] x = mathl s $ x / y
mathl str x = error str

-- math "1 + 3" == 4.0
-- math "3 * 2 + 100" == 106.0
-- math "20 / 3 + 100 * 2" == 213.33333333333334
peano :: String -> Maybe Int
peano = [rex|^(?{ length . filter (=='S') } \s* (?:S\s+)*Z)\s*$|]

--  peano "S Z" == Just 1
--  peano "S S S S Z" == Just 4
--  peano "S   S   Z" == Just 2
parsePair :: String -> Maybe (String, String)
parsePair = [rex|^<\s* (?{ }[^\s,>]+) \s*,\s* (?{ }[^\s,>]+) \s*>$|]

--  parsePair "<-1, 3>" == Just ("-1","3")
--  parsePair "<-4,3b0>" == Just ("-4","3b0")
--  parsePair "< a,  -30 >" == Just ("a","-30")
--  parsePair "< a,  other>" == Just ("a","other")
-- From http://www.regular-expressions.info/dates.html
parseDate :: String -> Maybe (Int, Int, Int)
parseDate [rex|^(?{ read -> y }(?:19|20)\d\d)[- /.]
                (?{ read -> m }0[1-9]|1[012])[- /.]
                (?{ read -> d }0[1-9]|[12][0-9]|3[01])$|]
  |  (d > 30 && (m `elem` [4, 6, 9, 11]))
  || (m == 2 &&
       (d ==29 && not (mod y 4 == 0 && (mod y 100 /= 0 || mod y 400 == 0)))
    || (d > 29)) = Nothing
  | otherwise = Just (y, m, d)
parseDate _ = Nothing

--  parseDate "1993.8.10" == Nothing
--  parseDate "1993.08.10" == Just (1993,8,10)
--  parseDate "2003.02.28" == Just (2003,2,28)
--  parseDate "2003.02.27" == Just (2003,2,27)
onNull a f [] = a
onNull _ f xs = f xs

nonNull = onNull Nothing

disjunct [rex| ^(?:(?{nonNull $ Just . head -> a} .)
             | (?{nonNull $ Just . head -> b} ..)
             | (?{nonNull $ Just . last -> c} ...))$|] =
  head $ catMaybes [a, b, c]

--  disjunct "a" == 'a'
--  disjunct "ab" == 'a'
--  disjunct "abc" == 'c'