Hello community,

here is the log from the commit of package ghc-pcre-heavy for openSUSE:Factory 
checked in at 2016-01-08 15:22:48
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Comparing /work/SRC/openSUSE:Factory/ghc-pcre-heavy (Old)
 and      /work/SRC/openSUSE:Factory/.ghc-pcre-heavy.new (New)
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

Package is "ghc-pcre-heavy"

Changes:
--------
--- /work/SRC/openSUSE:Factory/ghc-pcre-heavy/ghc-pcre-heavy.changes    
2015-11-26 17:02:54.000000000 +0100
+++ /work/SRC/openSUSE:Factory/.ghc-pcre-heavy.new/ghc-pcre-heavy.changes       
2016-01-08 15:22:49.000000000 +0100
@@ -1,0 +2,5 @@
+Wed Dec 16 17:25:44 UTC 2015 - mimi...@gmail.com
+
+- update to 1.0.0.1
+
+-------------------------------------------------------------------

Old:
----
  pcre-heavy-0.2.5.tar.gz

New:
----
  pcre-heavy-1.0.0.1.tar.gz

++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

Other differences:
------------------
++++++ ghc-pcre-heavy.spec ++++++
--- /var/tmp/diff_new_pack.FaY1KW/_old  2016-01-08 15:22:50.000000000 +0100
+++ /var/tmp/diff_new_pack.FaY1KW/_new  2016-01-08 15:22:50.000000000 +0100
@@ -20,7 +20,7 @@
 %bcond_with tests
 
 Name:           ghc-pcre-heavy
-Version:        0.2.5
+Version:        1.0.0.1
 Release:        0
 Summary:        A regexp library on top of pcre-light you can actually use
 Group:          System/Libraries
@@ -33,9 +33,12 @@
 BuildRequires:  ghc-Cabal-devel
 BuildRequires:  ghc-rpm-macros
 # Begin cabal-rpm deps:
+BuildRequires:  ghc-base-compat-devel
 BuildRequires:  ghc-bytestring-devel
 BuildRequires:  ghc-pcre-light-devel
 BuildRequires:  ghc-stringable-devel
+BuildRequires:  ghc-string-conversions-devel
+BuildRequires:  ghc-semigroups-devel
 BuildRequires:  ghc-template-haskell-devel
 %if %{with tests}
 BuildRequires:  ghc-Glob-devel

++++++ pcre-heavy-0.2.5.tar.gz -> pcre-heavy-1.0.0.1.tar.gz ++++++
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/pcre-heavy-0.2.5/README.md 
new/pcre-heavy-1.0.0.1/README.md
--- old/pcre-heavy-0.2.5/README.md      2015-08-23 09:54:27.000000000 +0200
+++ new/pcre-heavy-1.0.0.1/README.md    2015-09-02 22:23:43.000000000 +0200
@@ -2,19 +2,20 @@
 
 *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
+- based on [pcre-light], none of that regex-base complicated pluggable-backend 
stuff
+- takes and returns [ConvertibleStrings] everywhere, use ANY STRING TYPE 
(String, ByteString, Lazy ByteString, Text, Lazy Text) -- but you need a bit 
more type annotations (or [ClassyPrelude]'s `asText`, `asString`, etc.) if you 
use `OverloadedStrings` which you probably can't live without
 - a QuasiQuoter for regexps that does compile time checking (BTW, [vim2hs] has 
correct syntax highlighting for that!)
 - **SEARCHES FOR MULTIPLE MATCHES! DOES REPLACEMENT!**
 
 [pcre-light]: https://hackage.haskell.org/package/pcre-light
-[Stringables]: https://hackage.haskell.org/package/stringable
+[ConvertibleStrings]: https://hackage.haskell.org/package/string-conversions
+[ClassyPrelude]: https://hackage.haskell.org/package/classy-prelude
 [vim2hs]: https://github.com/dag/vim2hs#quasi-quoting
 
 ## Usage
 
 ```haskell
-{-# LANGUAGE QuasiQuotes #-}
+{-# LANGUAGE QuasiQuotes, FlexibleContexts #-}
 import           Text.Regex.PCRE.Heavy
 ```
 
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/pcre-heavy-0.2.5/library/Text/Regex/PCRE/Heavy.hs 
new/pcre-heavy-1.0.0.1/library/Text/Regex/PCRE/Heavy.hs
--- old/pcre-heavy-0.2.5/library/Text/Regex/PCRE/Heavy.hs       2015-08-23 
17:30:13.000000000 +0200
+++ new/pcre-heavy-1.0.0.1/library/Text/Regex/PCRE/Heavy.hs     2015-09-03 
01:44:49.000000000 +0200
@@ -1,9 +1,7 @@
 {-# OPTIONS_GHC -fno-warn-orphans -fno-warn-unused-binds #-}
-{-# LANGUAGE UndecidableInstances #-}
-{-# LANGUAGE FlexibleInstances, BangPatterns #-}
-{-# LANGUAGE TemplateHaskell, QuasiQuotes #-}
+{-# LANGUAGE NoImplicitPrelude, UndecidableInstances, FlexibleInstances, 
FlexibleContexts, BangPatterns #-}
+{-# LANGUAGE TemplateHaskell, QuasiQuotes, UnicodeSyntax #-}
 {-# LANGUAGE ForeignFunctionInterface #-}
-{-# LANGUAGE UnicodeSyntax, CPP #-}
 
 -- | A usable regular expressions library on top of pcre-light.
 module Text.Regex.PCRE.Heavy (
@@ -34,9 +32,7 @@
 , rawSub
 ) where
 
-#if __GLASGOW_HASKELL__ < 709
-import           Control.Applicative ((<$>))
-#endif
+import           Prelude.Compat
 import           Language.Haskell.TH hiding (match)
 import           Language.Haskell.TH.Quote
 import           Language.Haskell.TH.Syntax
@@ -44,33 +40,33 @@
 import           Text.Regex.PCRE.Light.Base
 import           Data.Maybe (isJust, fromMaybe)
 import           Data.List (unfoldr, mapAccumL)
-import           Data.Stringable
+import qualified Data.List.NonEmpty as NE
+import           Data.String.Conversions
+import           Data.String.Conversions.Monomorphic
 import qualified Data.ByteString.Char8 as BS
 import qualified Data.ByteString.Internal as BS
 import           System.IO.Unsafe (unsafePerformIO)
 import           Foreign (withForeignPtr, allocaBytes, nullPtr, plusPtr, 
peekElemOff)
-import           Debug.Trace
 
-substr ∷ BS.ByteString → (Int, Int) → BS.ByteString
+substr ∷ SBS → (Int, Int) → SBS
 substr s (f, t) = BS.take (t - f) . BS.drop f $ s
 
-behead ∷ [a] → (a, [a])
-behead (h:t) = (h, t)
-behead [] = error "no head to behead"
+behead ∷ NE.NonEmpty a → (a, [a])
+behead l = (NE.head l, NE.tail l)
 
-reMatch ∷ Stringable a ⇒ Regex → a → Bool
-reMatch r s = isJust $ PCRE.match r (toByteString s) []
+reMatch ∷ (ConvertibleStrings SBS a, ConvertibleStrings a SBS) ⇒ Regex → a → 
Bool
+reMatch r s = isJust $ PCRE.match r (cs s) []
 
 -- | Checks whether a string matches a regex.
 --
 -- >>> :set -XQuasiQuotes
+-- >>> :set -XFlexibleContexts
 -- >>> "https://unrelenting.technology"; =~ [re|^http.*|]
 -- True
-(=~) ∷ Stringable a ⇒ a → Regex → Bool
+(=~), (≈) ∷ (ConvertibleStrings SBS a, ConvertibleStrings a SBS) ⇒ a → Regex → 
Bool
 (=~) = flip reMatch
 
 -- | Same as =~.
-(≈) ∷ Stringable a ⇒ a → Regex → Bool
 (≈) = (=~)
 
 -- | Does raw PCRE matching (you probably shouldn't use this directly).
@@ -82,7 +78,7 @@
 -- Just [(7,9)]
 -- >>> rawMatch [re|(\w)(\w)|] "a a ab abc ba" 0 []
 -- Just [(4,6),(4,5),(5,6)]
-rawMatch ∷ Regex → BS.ByteString → Int → [PCREExecOption] → Maybe [(Int, Int)]
+rawMatch ∷ Regex → SBS → Int → [PCREExecOption] → Maybe [(Int, Int)]
 rawMatch r@(Regex pcreFp _) s offset opts = unsafePerformIO $ do
   withForeignPtr pcreFp $ \pcrePtr → do
     let nCapt = PCRE.captureCount r
@@ -103,62 +99,59 @@
                   loop (n + 1) (o + 2) ((fromIntegral i, fromIntegral j) : acc)
           in loop 0 0 []
 
-nextMatch ∷ Regex → [PCREExecOption] → BS.ByteString → Int → Maybe ([(Int, 
Int)], Int)
+nextMatch ∷ Regex → [PCREExecOption] → SBS → Int → Maybe (NE.NonEmpty (Int, 
Int), Int)
 nextMatch r opts str offset =
-  case rawMatch r str offset opts of
-    Nothing → Nothing
-    Just [] → Nothing
-    Just ms → Just (ms, maximum $ map snd ms)
+  rawMatch r str offset opts >>= NE.nonEmpty >>= \ms → return (ms, maximum $ 
fmap snd ms)
 
 -- | Searches the string for all matches of a given regex.
 --
--- >>> scan [re|\s*entry (\d+) (\w+)\s*&?|] " entry 1 hello  &entry 2 hi"
+-- >>> scan [re|\s*entry (\d+) (\w+)\s*&?|] (" entry 1 hello  &entry 2 hi" :: 
String)
 -- [(" entry 1 hello  &",["1","hello"]),("entry 2 hi",["2","hi"])]
 --
 -- It is lazy! If you only need the first match, just apply 'head' (or
 -- 'headMay' from the "safe" library) -- no extra work will be performed!
 --
--- >>> head $ scan [re|\s*entry (\d+) (\w+)\s*&?|] " entry 1 hello  &entry 2 
hi"
+-- >>> head $ scan [re|\s*entry (\d+) (\w+)\s*&?|] (" entry 1 hello  &entry 2 
hi" :: String)
 -- (" entry 1 hello  &",["1","hello"])
-scan ∷ (Stringable a) ⇒ Regex → a → [(a, [a])]
+scan ∷ (ConvertibleStrings SBS a, ConvertibleStrings a SBS) ⇒ Regex → a → [(a, 
[a])]
 scan r s = scanO r [] s
 
 -- | Exactly like 'scan', but passes runtime options to PCRE.
-scanO ∷ (Stringable a) ⇒ Regex → [PCREExecOption] → a → [(a, [a])]
-scanO r opts s = map behead $ map (fromByteString . substr str) <$> unfoldr 
(nextMatch r opts str) 0
-  where str = toByteString s
+scanO ∷ (ConvertibleStrings SBS a, ConvertibleStrings a SBS) ⇒ Regex → 
[PCREExecOption] → a → [(a, [a])]
+scanO r opts s = map behead $ fmap (cs . substr str) <$> unfoldr (nextMatch r 
opts str) 0
+  where str = toSBS s
 
 -- | Searches the string for all matches of a given regex, like 'scan', but
 -- returns positions inside of the string.
 --
--- >>> scanRanges [re|\s*entry (\d+) (\w+)\s*&?|] " entry 1 hello  &entry 2 hi"
+-- >>> scanRanges [re|\s*entry (\d+) (\w+)\s*&?|] (" entry 1 hello  &entry 2 
hi" :: String)
 -- [((0,17),[(7,8),(9,14)]),((17,27),[(23,24),(25,27)])]
 --
 -- And just like 'scan', it's lazy.
-scanRanges ∷ (Stringable a) ⇒ Regex → a → [((Int, Int), [(Int, Int)])]
+scanRanges ∷ (ConvertibleStrings SBS a, ConvertibleStrings a SBS) ⇒ Regex → a 
→ [((Int, Int), [(Int, Int)])]
 scanRanges r s = scanRangesO r [] s
 
 -- | Exactly like 'scanRanges', but passes runtime options to PCRE.
-scanRangesO ∷ Stringable a ⇒ Regex → [PCREExecOption] → a → [((Int, Int), 
[(Int, Int)])]
+scanRangesO ∷ (ConvertibleStrings SBS a, ConvertibleStrings a SBS) ⇒ Regex → 
[PCREExecOption] → a → [((Int, Int), [(Int, Int)])]
 scanRangesO r opts s = map behead $ unfoldr (nextMatch r opts str) 0
-  where str = toByteString s
+  where str = toSBS s
 
 class RegexReplacement a where
-  performReplacement ∷ BS.ByteString → [BS.ByteString] → a → BS.ByteString
+  performReplacement ∷ SBS → [SBS] → a → SBS
 
-instance {-# OVERLAPPABLE #-} Stringable a ⇒ RegexReplacement a where
-  performReplacement _ _ to = toByteString to
+instance {-# OVERLAPPABLE #-} ConvertibleStrings a SBS ⇒ RegexReplacement a 
where
+  performReplacement _ _ to = cs to
 
-instance Stringable a ⇒ RegexReplacement (a → [a] → a) where
-  performReplacement from groups replacer = toByteString $ replacer 
(fromByteString from) (map fromByteString groups)
+instance (ConvertibleStrings SBS a, ConvertibleStrings a SBS) ⇒ 
RegexReplacement (a → [a] → a) where
+  performReplacement from groups replacer = cs $ replacer (cs from) (map cs 
groups)
 
-instance Stringable a ⇒ RegexReplacement (a → a) where
-  performReplacement from _ replacer = toByteString $ replacer (fromByteString 
from)
+instance (ConvertibleStrings SBS a, ConvertibleStrings a SBS) ⇒ 
RegexReplacement (a → a) where
+  performReplacement from _ replacer = cs $ replacer (cs from)
 
-instance Stringable a ⇒ RegexReplacement ([a] → a) where
-  performReplacement _ groups replacer = toByteString $ replacer (map 
fromByteString groups)
+instance (ConvertibleStrings SBS a, ConvertibleStrings a SBS) ⇒ 
RegexReplacement ([a] → a) where
+  performReplacement _ groups replacer = cs $ replacer (map cs groups)
 
-rawSub ∷ RegexReplacement r ⇒ Regex → r → BS.ByteString → Int → 
[PCREExecOption] → Maybe (BS.ByteString, Int)
+rawSub ∷ RegexReplacement r ⇒ Regex → r → SBS → Int → [PCREExecOption] → Maybe 
(SBS, Int)
 rawSub r t s offset opts =
   case rawMatch r s offset opts of
     Just ((begin, end):groups) →
@@ -176,22 +169,22 @@
 -- >>> sub [re|a|] "b" "c" :: String
 -- "c"
 --
--- >>> sub [re|bad|] "xxxbad" "this is bad, right?"
+-- >>> sub [re|bad|] "xxxbad" "this is bad, right?" :: String
 -- "this is xxxbad, right?"
 --
 -- You can use functions!
--- A function of Stringable gets the full match.
--- A function of [Stringable] gets the groups.
--- A function of Stringable → [Stringable] gets both.
+-- A function of ConvertibleStrings SBS gets the full match.
+-- A function of [ConvertibleStrings SBS] gets the groups.
+-- A function of ConvertibleStrings SBS → [ConvertibleStrings SBS] gets both.
 --
 -- >>> sub [re|%(\d+)(\w+)|] (\(d:w:_) -> "{" ++ d ++ " of " ++ w ++ "}" :: 
String) "Hello, %20thing" :: String
 -- "Hello, {20 of thing}"
-sub ∷ (Stringable a, RegexReplacement r) ⇒ Regex → r → a → a
+sub ∷ (ConvertibleStrings SBS a, ConvertibleStrings a SBS, RegexReplacement r) 
⇒ Regex → r → a → a
 sub r t s = subO r [] t s
 
 -- | Exactly like 'sub', but passes runtime options to PCRE.
-subO ∷ (Stringable a, RegexReplacement r) ⇒ Regex → [PCREExecOption] → r → a → 
a
-subO r opts t s = fromMaybe s $ fromByteString <$> fst <$> rawSub r t 
(toByteString s) 0 opts
+subO ∷ (ConvertibleStrings SBS a, ConvertibleStrings a SBS, RegexReplacement 
r) ⇒ Regex → [PCREExecOption] → r → a → a
+subO r opts t s = fromMaybe s $ cs <$> fst <$> rawSub r t (cs s) 0 opts
 
 -- | Replaces all occurences of a given regex.
 --
@@ -204,18 +197,18 @@
 -- "Hello, world"
 --
 -- https://github.com/myfreeweb/pcre-heavy/issues/2
--- >>> gsub [re|good|] "bad" "goodgoodgood"
+-- >>> gsub [re|good|] "bad" "goodgoodgood" :: String
 -- "badbadbad"
 --
--- >>> gsub [re|bad|] "xxxbad" "this is bad, right? bad"
+-- >>> gsub [re|bad|] "xxxbad" "this is bad, right? bad" :: String
 -- "this is xxxbad, right? xxxbad"
-gsub ∷ (Stringable a, RegexReplacement r) ⇒ Regex → r → a → a
+gsub ∷ (ConvertibleStrings SBS a, ConvertibleStrings a SBS, RegexReplacement 
r) ⇒ Regex → r → a → a
 gsub r t s = gsubO r [] t s
 
 -- | Exactly like 'gsub', but passes runtime options to PCRE.
-gsubO ∷ (Stringable a, RegexReplacement r) ⇒ Regex → [PCREExecOption] → r → a 
→ a
-gsubO r opts t s = fromByteString $ loop 0 str
-  where str = toByteString s
+gsubO ∷ (ConvertibleStrings SBS a, ConvertibleStrings a SBS, RegexReplacement 
r) ⇒ Regex → [PCREExecOption] → r → a → a
+gsubO r opts t s = cs $ loop 0 str
+  where str = toSBS s
         loop offset acc =
           case rawSub r t acc offset opts of
             Just (result, newOffset) →
@@ -226,30 +219,30 @@
 --
 -- Is lazy.
 --
--- >>> split [re|%(begin|next|end)%|] "%begin%hello%next%world%end%"
+-- >>> split [re|%(begin|next|end)%|] ("%begin%hello%next%world%end%" :: 
String)
 -- ["","hello","world",""]
 --
--- >>> split [re|%(begin|next|end)%|] ""
+-- >>> split [re|%(begin|next|end)%|] ("" :: String)
 -- [""]
-split ∷ Stringable a ⇒ Regex → a → [a]
+split ∷ (ConvertibleStrings SBS a, ConvertibleStrings a SBS) ⇒ Regex → a → [a]
 split r s = splitO r [] s
 
 -- | Exactly like 'split', but passes runtime options to PCRE.
-splitO ∷ Stringable a ⇒ Regex → [PCREExecOption] → a → [a]
-splitO r opts s = map fromByteString $ map' (substr str) partRanges
+splitO ∷ (ConvertibleStrings SBS a, ConvertibleStrings a SBS) ⇒ Regex → 
[PCREExecOption] → a → [a]
+splitO r opts s = map cs $ map' (substr str) partRanges
   where map' f = foldr ((:) . f) [f (lastL, BS.length str)] -- avoiding the 
snoc operation
         (lastL, partRanges) = mapAccumL invRange 0 ranges
         invRange acc (xl, xr) = (xr, (acc, xl))
         ranges = map fst $ scanRangesO r opts str
-        str = toByteString s
+        str = toSBS s
 
 instance Lift PCREOption where
   -- well, the constructor isn't exported, but at least it implements 
Read/Show :D
   lift o = let o' = show o in [| read o' ∷ PCREOption |]
 
 quoteExpRegex ∷ [PCREOption] → String → ExpQ
-quoteExpRegex opts txt = [| PCRE.compile (toByteString (txt ∷ String)) opts |]
-  where !_ = PCRE.compile (toByteString txt) opts -- check at compile time
+quoteExpRegex opts txt = [| PCRE.compile (cs (txt ∷ String)) opts |]
+  where !_ = PCRE.compile (cs txt) opts -- check at compile time
 
 -- | Returns a QuasiQuoter like 're', but with given PCRE options.
 mkRegexQQ ∷ [PCREOption] → QuasiQuoter
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/pcre-heavy-0.2.5/pcre-heavy.cabal 
new/pcre-heavy-1.0.0.1/pcre-heavy.cabal
--- old/pcre-heavy-0.2.5/pcre-heavy.cabal       2015-08-23 17:30:31.000000000 
+0200
+++ new/pcre-heavy-1.0.0.1/pcre-heavy.cabal     2015-09-03 01:46:09.000000000 
+0200
@@ -1,5 +1,5 @@
 name:            pcre-heavy
-version:         0.2.5
+version:         1.0.0.1
 synopsis:        A regexp library on top of pcre-light you can actually use.
 description:
     A regular expressions library that does not suck.
@@ -32,14 +32,15 @@
 library
     build-depends:
         base >= 4.3.0.0 && < 5
+      , base-compat >= 0.8.0
       , pcre-light
       , bytestring
-      , stringable
+      , string-conversions
+      , semigroups
       , template-haskell
     default-language: Haskell2010
     exposed-modules:
         Text.Regex.PCRE.Heavy
-    ghc-prof-options: -prof
     ghc-options: -Wall
     hs-source-dirs: library
 


Reply via email to