commit ghc-irc-conduit for openSUSE:Factory

2017-04-14 Thread root
Hello community,

here is the log from the commit of package ghc-irc-conduit for openSUSE:Factory 
checked in at 2017-04-14 13:38:13

Comparing /work/SRC/openSUSE:Factory/ghc-irc-conduit (Old)
 and  /work/SRC/openSUSE:Factory/.ghc-irc-conduit.new (New)


Package is "ghc-irc-conduit"

Fri Apr 14 13:38:13 2017 rev:3 rq:485136 version:0.2.2.1

Changes:

--- /work/SRC/openSUSE:Factory/ghc-irc-conduit/ghc-irc-conduit.changes  
2017-02-20 13:16:00.308780469 +0100
+++ /work/SRC/openSUSE:Factory/.ghc-irc-conduit.new/ghc-irc-conduit.changes 
2017-04-14 13:38:15.594822045 +0200
@@ -1,0 +2,5 @@
+Tue Mar  7 11:19:26 UTC 2017 - psim...@suse.com
+
+- Update to version 0.2.2.1 with cabal2obs.
+
+---

Old:

  irc-conduit-0.2.2.0.tar.gz

New:

  irc-conduit-0.2.2.1.tar.gz



Other differences:
--
++ ghc-irc-conduit.spec ++
--- /var/tmp/diff_new_pack.NVcy0Z/_old  2017-04-14 13:38:16.218733867 +0200
+++ /var/tmp/diff_new_pack.NVcy0Z/_new  2017-04-14 13:38:16.222733303 +0200
@@ -18,7 +18,7 @@
 
 %global pkg_name irc-conduit
 Name:   ghc-%{pkg_name}
-Version:0.2.2.0
+Version:0.2.2.1
 Release:0
 Summary:Streaming IRC message library using conduits
 License:MIT

++ irc-conduit-0.2.2.0.tar.gz -> irc-conduit-0.2.2.1.tar.gz ++
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/irc-conduit-0.2.2.0/Network/IRC/Conduit/Lens.hs 
new/irc-conduit-0.2.2.1/Network/IRC/Conduit/Lens.hs
--- old/irc-conduit-0.2.2.0/Network/IRC/Conduit/Lens.hs 2017-01-03 
18:41:45.0 +0100
+++ new/irc-conduit-0.2.2.1/Network/IRC/Conduit/Lens.hs 2017-03-02 
04:23:33.0 +0100
@@ -1,12 +1,10 @@
-{-# LANGUAGE CPP #-}
-
 -- |
 -- Module  : Network.IRC.Conduit
 -- Copyright   : (c) 2017 Michael Walker
 -- License : MIT
 -- Maintainer  : Michael Walker 
 -- Stability   : experimental
--- Portability : CPP
+-- Portability : portable
 --
 -- 'Lens'es and 'Prism's.
 module Network.IRC.Conduit.Lens where
@@ -17,44 +15,142 @@
 import Network.IRC.CTCP (CTCPByteString)
 import Network.IRC.Conduit.Internal
 
--- CPP seem to dislike the first ' on the RHS…
-#define PRIME() '
-
-#define LENS(S,F,A) \
-{-# INLINE F #-}; \
-{-| PRIME()Lens' for '_/**/F'. -}; \
-F :: Lens' S A; \
-F = \ afb s -> (\ b -> s {_/**/F = b}) <$> afb (_/**/F s)
-
-#define PRISM(S,C,ARG,TUP,A) \
-{-| PRIME()Prism' for 'C'. -}; \
-{-# INLINE _/**/C #-}; \
-_/**/C :: Prism' S A; \
-_/**/C = dimap (\ s -> case s of C ARG -> Right TUP; _ -> Left s) \
-(either pure $ fmap (\ TUP -> C ARG)) . right'
-
 -- * Lenses for 'Event'
-LENS((Event a),raw,ByteString)
-LENS((Event a),source,(Source a))
-LENS((Event a),message,(Message a))
+
+-- | 'Lens' for '_raw'.
+raw :: Lens' (Event a) ByteString
+{-# INLINE raw #-}
+raw afb s = (\b -> s { _raw = b }) <$> afb (_raw s)
+
+-- | 'Lens' for '_source'.
+source :: Lens' (Event a) (Source a)
+{-# INLINE source #-}
+source afb s = (\b -> s { _source = b }) <$> afb (_source s)
+
+-- | 'Lens' for '_message'.
+message :: Lens' (Event a) (Message a)
+{-# INLINE message #-}
+message afb s = (\b -> s { _message = b }) <$> afb (_message s)
 
 -- * Prisms for 'Source'
-PRISM((Source a),User,name,name,(NickName a))
-PRISM((Source a),Channel,chan name,(chan,name),(ChannelName a, NickName a))
-PRISM((Source a),Server,name,name,(ServerName a))
-
--- * #Message# Prisms for 'Message'
-PRISM((Message a),Privmsg,tar msg,(tar, msg),(Target a, Either CTCPByteString 
a))
-PRISM((Message a),Notice,tar msg,(tar, msg),(Target a, Either CTCPByteString 
a))
-PRISM((Message a),Nick,name,name,(NickName a))
-PRISM((Message a),Join,chan,chan,(ChannelName a))
-PRISM((Message a),Part,chan reason,(chan, reason),(ChannelName a, Reason a))
-PRISM((Message a),Quit,reason,reason,(Reason a))
-PRISM((Message a),Mode,tar is flags args,(tar, is, flags, args),(Target a, 
IsModeSet, [ModeFlag a], [ModeArg a]))
-PRISM((Message a),Topic,name topic,(name, topic),(ChannelName a, a))
-PRISM((Message a),Invite,chan name,(chan, name),(ChannelName a, NickName a))
-PRISM((Message a),Kick,chan name reason,(chan, name, reason),(ChannelName a, 
NickName a, Reason a))
-PRISM((Message a),Ping,ser ver,(ser, ver),(ServerName a, Maybe (ServerName a)))
-PRISM((Message a),Pong,ser,ser,(ServerName a))
-PRISM((Message a),Numeric,num args,(num, args),(Int, [NumericArg a]))
-PRISM((Message a),RawMsg,msg,msg,a)
+
+-- | 'Prism' for 'User'
+_User :: Prism' (Source a) (NickName a)
+{-# INLINE _User #-}
+_User = dimap
+  (\s -> case s of User n -> Right n; _ -> Left s)
+  (either pure $ fmap User) . right'
+
+-- | 'Prism' for 'Channel'
+_Channel :: Prism' (Source a

commit ghc-irc-conduit for openSUSE:Factory

2017-02-20 Thread root
Hello community,

here is the log from the commit of package ghc-irc-conduit for openSUSE:Factory 
checked in at 2017-02-20 13:16:00

Comparing /work/SRC/openSUSE:Factory/ghc-irc-conduit (Old)
 and  /work/SRC/openSUSE:Factory/.ghc-irc-conduit.new (New)


Package is "ghc-irc-conduit"

Changes:

--- /work/SRC/openSUSE:Factory/ghc-irc-conduit/ghc-irc-conduit.changes  
2017-02-13 07:48:21.408776627 +0100
+++ /work/SRC/openSUSE:Factory/.ghc-irc-conduit.new/ghc-irc-conduit.changes 
2017-02-20 13:16:00.308780469 +0100
@@ -1,0 +2,20 @@
+Sun Jan  8 21:13:38 UTC 2017 - psim...@suse.com
+
+- Update to version 0.2.2.0 with cabal2obs.
+
+---
+Sun Oct 30 16:26:13 UTC 2016 - psim...@suse.com
+
+- Update to version 0.2.1.1 with cabal2obs.
+
+---
+Mon Sep 26 06:49:59 UTC 2016 - psim...@suse.com
+
+- Update to version 0.2.1.0 with cabal2obs.
+
+---
+Thu Sep 15 06:45:09 UTC 2016 - psim...@suse.com
+
+- Update to version 0.2.0.0 revision 0 with cabal2obs.
+
+---

Old:

  irc-conduit-0.1.2.0.tar.gz

New:

  irc-conduit-0.2.2.0.tar.gz



Other differences:
--
++ ghc-irc-conduit.spec ++
--- /var/tmp/diff_new_pack.v8LYo7/_old  2017-02-20 13:16:00.776714677 +0100
+++ /var/tmp/diff_new_pack.v8LYo7/_new  2017-02-20 13:16:00.776714677 +0100
@@ -1,7 +1,7 @@
 #
 # spec file for package ghc-irc-conduit
 #
-# Copyright (c) 2016 SUSE LINUX GmbH, Nuernberg, Germany.
+# Copyright (c) 2017 SUSE LINUX GmbH, Nuernberg, Germany.
 #
 # All modifications and additions to the file contributed by third parties
 # remain the property of their copyright owners, unless otherwise agreed
@@ -18,15 +18,14 @@
 
 %global pkg_name irc-conduit
 Name:   ghc-%{pkg_name}
-Version:0.1.2.0
+Version:0.2.2.0
 Release:0
 Summary:Streaming IRC message library using conduits
 License:MIT
-Group:  System/Libraries
+Group:  Development/Languages/Other
 Url:https://hackage.haskell.org/package/%{pkg_name}
 Source0:
https://hackage.haskell.org/package/%{pkg_name}-%{version}/%{pkg_name}-%{version}.tar.gz
 BuildRequires:  ghc-Cabal-devel
-# Begin cabal-rpm deps:
 BuildRequires:  ghc-async-devel
 BuildRequires:  ghc-bytestring-devel
 BuildRequires:  ghc-conduit-devel
@@ -35,6 +34,7 @@
 BuildRequires:  ghc-irc-ctcp-devel
 BuildRequires:  ghc-irc-devel
 BuildRequires:  ghc-network-conduit-tls-devel
+BuildRequires:  ghc-profunctors-devel
 BuildRequires:  ghc-rpm-macros
 BuildRequires:  ghc-text-devel
 BuildRequires:  ghc-time-devel
@@ -42,7 +42,6 @@
 BuildRequires:  ghc-transformers-devel
 BuildRequires:  ghc-x509-validation-devel
 BuildRoot:  %{_tmppath}/%{name}-%{version}-build
-# End cabal-rpm deps
 
 %description
 IRC messages consist of an optional identifying prefix, a command name, and a
@@ -71,15 +70,12 @@
 %prep
 %setup -q -n %{pkg_name}-%{version}
 
-
 %build
 %ghc_lib_build
 
-
 %install
 %ghc_lib_install
 
-
 %post devel
 %ghc_pkg_recache
 

++ irc-conduit-0.1.2.0.tar.gz -> irc-conduit-0.2.2.0.tar.gz ++
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' 
old/irc-conduit-0.1.2.0/Network/IRC/Conduit/Internal/Conduits.hs 
new/irc-conduit-0.2.2.0/Network/IRC/Conduit/Internal/Conduits.hs
--- old/irc-conduit-0.1.2.0/Network/IRC/Conduit/Internal/Conduits.hs
2014-09-05 19:53:38.0 +0200
+++ new/irc-conduit-0.2.2.0/Network/IRC/Conduit/Internal/Conduits.hs
1970-01-01 01:00:00.0 +0100
@@ -1,55 +0,0 @@
-{-# LANGUAGE ImpredicativeTypes #-}
-{-# LANGUAGE OverloadedStrings  #-}
-
--- |Internal helper conduits
-module Network.IRC.Conduit.Internal.Conduits where
-
-import Control.Arrow  ((&&&))
-import Control.Monad.IO.Class (MonadIO, liftIO)
-import Data.ByteString(ByteString, isSuffixOf, singleton)
-import Data.Conduit   (Conduit, await, yield)
-import Data.Monoid((<>))
-
-import qualified Data.ByteString as B
-
--- |Split up incoming bytestrings into new lines.
-chunked :: Monad m => Conduit ByteString m ByteString
-chunked = chunked' ""
-  where
-chunked' leftover = do
-  -- Wait for a value from upstream
-  val <- await
-
-  case val of
-Just val' ->
-  let
-carriage = fromIntegral $ fromEnum '\r'
-newline  = fromIntegral $ fromEnum '\n'
-
--- Split on '\n's, removing any stray '\r's (line endings
--- are usually '\r\n's, but this isn't certain).
-bytes= B.filter (/=carriage) $ leftov