pcre-heavy: A regexp library on top of pcre-light you can actually use.

[ library, public-domain, web ] [ Propose Tags ]

A regular expressions library that does not suck. - based on pcre-light - takes and returns Stringables everywhere - a QuasiQuoter for regexps that does compile time checking - SEARCHES FOR MULTIPLE MATCHES! DOES REPLACEMENT!


[Skip to Readme]

Modules

[Index]

Downloads

Note: This package has metadata revisions in the cabal description newer than included in the tarball. To unpack the package including the revisions, use 'cabal get'.

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.1.0, 0.2.0, 0.2.1, 0.2.2, 0.2.3, 0.2.4, 0.2.5, 1.0.0, 1.0.0.1, 1.0.0.2, 1.0.0.3
Dependencies base (>=4.0.0.0 && <5), bytestring, pcre-light, stringable, template-haskell [details]
License LicenseRef-OtherLicense
Copyright 2015 Val Packett <val@packett.cool>
Author Val Packett
Maintainer val@packett.cool
Revised Revision 1 made by myfreeweb at 2022-10-16T00:27:38Z
Category Web
Home page https://codeberg.org/valpackett/pcre-heavy
Source repo head: git clone https://codeberg.org/valpackett/pcre-heavy.git
Uploaded by myfreeweb at 2015-02-12T17:32:06Z
Distributions Arch:1.0.0.3, LTSHaskell:1.0.0.3, NixOS:1.0.0.3, Stackage:1.0.0.3
Reverse Dependencies 17 direct, 14 indirect [details]
Downloads 12348 total (71 in the last 30 days)
Rating 2.5 (votes: 5) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2015-02-12 [all 1 reports]

Readme for pcre-heavy-0.2.0

[back to package description]

pcre-heavy Hackage ISC License

Finally! A Haskell regular expressions library that does not suck.

  • based on pcre-light, none of that regex-compat-pluggable-backend stuff
  • takes and returns Stringables everywhere, use ANY STRING TYPE (String, ByteString, LByteString, Text, LText, FilePath) -- but you need a bit more type annotations than usual
  • a QuasiQuoter for regexps that does compile time checking (BTW, vim2hs has correct syntax highlighting for that!)
  • SEARCHES FOR MULTIPLE MATCHES! DOES REPLACEMENT!

Usage

{-# LANGUAGE QuasiQuotes #-}
import           Text.Regex.PCRE.Heavy

Checking

>>> "https://unrelenting.technology" =~ [re|^http.*|]
True

Matching (Searching)

(You can use any string type, not just String!)

scan returns all matches as pairs like (fullmatch, [group, group...]).

>>> scan [re|\s*entry (\d+) (\w+)\s*&?|] " entry 1 hello  &entry 2 hi" :: [(String, [String])]
[
  (" entry 1 hello  &", ["1", "hello"])
, ("entry 2 hi",        ["2", "hi"])
]

It is lazy! If you only need the first match, use head (or, much better, headMay from safe) -- no extra work will be performed!

>>> headMay $ scan [re|\s*entry (\d+) (\w+)\s*&?|] " entry 1 hello  &entry 2 hi"
Just (" entry 1 hello  &", ["1", "hello"])

Replacement

sub replaces the first match, gsub replaces all matches.

-- You can use a Stringable type as the replacement...
>>> gsub [re|\d+|] "!!!NUMBER!!!" "Copyright (c) 2015 The 000 Group"
"Copyright (c) !!!NUMBER!!! The !!!NUMBER!!! Group"

-- or a (Stringable a => [a] -> a) function -- that will get the groups...
>>> gsub [re|%(\d+)(\w+)|] (\(d:w:_) -> "{" ++ d ++ " of " ++ w ++ "}" :: String) "Hello, %20thing"
"Hello, {20 of thing}"

-- or a (Stringable a => a -> a) function -- that will get the full match...
>>> gsub [re|-\w+|] (\x -> "+" ++ (reverse $ drop 1 x) :: String) "hello -world"
"hello +dlrow"

-- or a (Stringable a => a -> [a] -> a) function.
-- That will get both the full match and the groups.
-- I have no idea why you would want to use that, but that's there :-)

Options

You can pass pcre-light options like this:

>>> let myRe = mkRegexQQ [multiline, utf8, ungreedy]
>>> scanO [myRe|\s*entry (\d+) (\w+)\s*&?|] [exec_no_utf8_check] " entry 1 hello  &entry 2 hi" :: [[String]]
>>> gsubO [myRe|\d+|] [exec_notempty] "!!!NUMBER!!!" "Copyright (c) 2015 The 000 Group"

utf8 is passed by default in the re QuasiQuoter.

License

Copyright 2015 Greg V greg@unrelenting.technology
Available under the ISC license, see the COPYING file