Hello community,

here is the log from the commit of package ghc-rot13 for openSUSE:Factory 
checked in at 2017-08-31 20:58:56
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Comparing /work/SRC/openSUSE:Factory/ghc-rot13 (Old)
 and      /work/SRC/openSUSE:Factory/.ghc-rot13.new (New)
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

Package is "ghc-rot13"

Thu Aug 31 20:58:56 2017 rev:2 rq:513478 version:0.2.0.1

Changes:
--------
--- /work/SRC/openSUSE:Factory/ghc-rot13/ghc-rot13.changes      2017-04-12 
18:08:49.824619492 +0200
+++ /work/SRC/openSUSE:Factory/.ghc-rot13.new/ghc-rot13.changes 2017-08-31 
20:58:57.402398307 +0200
@@ -1,0 +2,5 @@
+Thu Jul 27 14:08:03 UTC 2017 - psim...@suse.com
+
+- Update to version 0.2.0.1.
+
+-------------------------------------------------------------------

Old:
----
  rot13-0.1.0.2.tar.gz

New:
----
  rot13-0.2.0.1.tar.gz

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

Other differences:
------------------
++++++ ghc-rot13.spec ++++++
--- /var/tmp/diff_new_pack.Rj65P0/_old  2017-08-31 20:58:58.430253890 +0200
+++ /var/tmp/diff_new_pack.Rj65P0/_new  2017-08-31 20:58:58.434253329 +0200
@@ -19,7 +19,7 @@
 %global pkg_name rot13
 %bcond_with tests
 Name:           ghc-%{pkg_name}
-Version:        0.1.0.2
+Version:        0.2.0.1
 Release:        0
 Summary:        Fast ROT13 cipher for Haskell
 License:        BSD-3-Clause
@@ -29,6 +29,7 @@
 BuildRequires:  ghc-Cabal-devel
 BuildRequires:  ghc-bytestring-devel
 BuildRequires:  ghc-rpm-macros
+BuildRequires:  ghc-text-devel
 BuildRoot:      %{_tmppath}/%{name}-%{version}-build
 %if %{with tests}
 BuildRequires:  ghc-QuickCheck-devel

++++++ rot13-0.1.0.2.tar.gz -> rot13-0.2.0.1.tar.gz ++++++
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/rot13-0.1.0.2/rot13.cabal 
new/rot13-0.2.0.1/rot13.cabal
--- old/rot13-0.1.0.2/rot13.cabal       2014-11-19 12:13:06.000000000 +0100
+++ new/rot13-0.2.0.1/rot13.cabal       2017-07-11 15:20:37.000000000 +0200
@@ -1,5 +1,5 @@
 name:                 rot13
-version:              0.1.0.2
+version:              0.2.0.1
 synopsis:             Fast ROT13 cipher for Haskell.
 description:
                       A fast ROT13 cipher for Haskell implemented using as few 
branches as possible.
@@ -21,7 +21,8 @@
     Codec.Rot13
   build-depends:
     base == 4.*,
-    bytestring >= 0.9
+    bytestring >= 0.9,
+    text >= 0.9
   hs-source-dirs:     src
   default-language:   Haskell2010
 
@@ -32,5 +33,7 @@
   build-depends:
     base == 4.*,
     hspec >= 1.3,
+    bytestring,
+    text,
     QuickCheck,
     rot13
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/rot13-0.1.0.2/src/Codec/Rot13.hs 
new/rot13-0.2.0.1/src/Codec/Rot13.hs
--- old/rot13-0.1.0.2/src/Codec/Rot13.hs        2014-11-19 12:13:06.000000000 
+0100
+++ new/rot13-0.2.0.1/src/Codec/Rot13.hs        2017-07-11 15:14:00.000000000 
+0200
@@ -1,4 +1,6 @@
 {-# LANGUAGE Trustworthy #-}
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE UndecidableInstances #-}
 
 -- |
 -- Module      : Codec.Rot13
@@ -9,60 +11,150 @@
 -- Stability   : experimental
 -- Portability : portable
 --
--- This module exposes all the API for this package.
+-- This module exposes the API for this package.
 module Codec.Rot13
-  ( -- * Word
-    rot13word
+  ( -- * Typeclass Interfaces
+    Rot13(..)
+  , Rot13Bytes(..)
+
+    -- * Constraint Interfaces
+  , rot13enum
+  , rot13int
+
+    -- * Compatibility
+  , rot13word
   , rot13word8
-    -- * Char
   , rot13char
-  , rot13
-    -- * ByteString
-  , rot13bs
+  , rot13string
   ) where
 
 import           Data.Char
 import           Data.Word
-import qualified Data.ByteString as BS
+import           Data.Int
+import qualified Data.ByteString            as BS
+import qualified Data.ByteString.Internal   as BS
+import qualified Data.Text                  as Text
+import           Foreign.Ptr
+import           Foreign.Storable
+import qualified Foreign.C.Types            as Foreign
+
+
+-- | The 'Rot13' typeclass is intended to perform the ROT13 cipher on the 
provided data, as if it
+--   were representing a single ANSI-encoded character. This interface doesn't 
consider the storage
+--   behaviour of the type at all, but is the fastest implementation if you 
need to integrate the
+--   transformation as part of a stream.
+
+class Rot13 a where
+  rot13 :: a -> a
+
+
+-- | The 'Rot13Bytes' typeclass is intended for when you need to perform the 
ROT13 cipher on some
+--   data at the memory level. It stores the given data into a temporary 
buffer in memory, then runs
+--   the cipher over the stored bytes to produce a new buffer. This operation 
is typically slower
+--   than just using 'rot13' as part of a fusion pipeline.
+
+class Rot13Bytes a where
+  rot13bs :: a -> BS.ByteString
+
+
+-- | Perform the ROT13 cipher on the given 'Integral' instance (in the sense 
of 'Rot13').
+rot13int :: Integral a => a -> a
+rot13int x
+  | (fromIntegral x :: Word) - 97 < 26 = 97 + rem (x - 84) 26
+  | (fromIntegral x :: Word) - 65 < 26 = 65 + rem (x - 52) 26
+  | otherwise   = x
+{-# INLINE rot13int #-}
+{-# SPECIALIZE rot13int :: Word -> Word #-}
+{-# SPECIALIZE rot13int :: Word8 -> Word8 #-}
+{-# SPECIALIZE rot13int :: Word16 -> Word16 #-}
+{-# SPECIALIZE rot13int :: Word32 -> Word32 #-}
+{-# SPECIALIZE rot13int :: Word64 -> Word64 #-}
+{-# SPECIALIZE rot13int :: Int -> Int #-}
+{-# SPECIALIZE rot13int :: Int8 -> Int8 #-}
+{-# SPECIALIZE rot13int :: Int16 -> Int16 #-}
+{-# SPECIALIZE rot13int :: Int32 -> Int32 #-}
+{-# SPECIALIZE rot13int :: Int64 -> Int64 #-}
+{-# SPECIALIZE rot13int :: Integer -> Integer #-}
+{-# SPECIALIZE rot13int :: Foreign.CChar -> Foreign.CChar #-}
+{-# SPECIALIZE rot13int :: Foreign.CSChar -> Foreign.CSChar #-}
+{-# SPECIALIZE rot13int :: Foreign.CUChar -> Foreign.CUChar #-}
+{-# SPECIALIZE rot13int :: Foreign.CShort -> Foreign.CShort #-}
+{-# SPECIALIZE rot13int :: Foreign.CUShort -> Foreign.CUShort #-}
+{-# SPECIALIZE rot13int :: Foreign.CInt -> Foreign.CInt #-}
+{-# SPECIALIZE rot13int :: Foreign.CUInt -> Foreign.CUInt #-}
+{-# SPECIALIZE rot13int :: Foreign.CLong -> Foreign.CLong #-}
+{-# SPECIALIZE rot13int :: Foreign.CULong -> Foreign.CULong #-}
+{-# SPECIALIZE rot13int :: Foreign.CWchar -> Foreign.CWchar #-}
+{-# SPECIALIZE rot13int :: Foreign.CLLong -> Foreign.CLLong #-}
+{-# SPECIALIZE rot13int :: Foreign.CULLong -> Foreign.CULLong #-}
+
+-- | Perform the ROT13 cipher on the given 'Enum' instance (in the sense of 
'Rot13').
+{-# INLINE rot13enum #-}
+rot13enum :: Enum a => a -> a
+rot13enum = toEnum . (rot13int :: Int -> Int) . fromEnum
+
+-- | Perform the ROT13 cipher on the given 'Storable' instance bytes to yield 
a 'BS.ByteString'.
+{-# INLINE rot13stor #-}
+rot13stor :: Storable a => a -> BS.ByteString
+rot13stor x = rot13bs $! BS.unsafeCreate (sizeOf x) $ \ptr -> poke (castPtr 
ptr) x
+
+
+--------------------------------------------------------------------------------------------------
+-- Rot13 Instances
+
+instance Rot13 Char                   where rot13 = rot13enum
+instance Rot13 String                 where rot13 = map rot13
+instance Rot13 BS.ByteString          where rot13 = BS.map rot13
+instance Rot13 Text.Text              where rot13 = Text.map rot13
+
+instance Rot13 Word                   where rot13 = rot13int
+instance Rot13 Word8                  where rot13 = rot13int
+instance Rot13 Word16                 where rot13 = rot13int
+instance Rot13 Word32                 where rot13 = rot13int
+instance Rot13 Word64                 where rot13 = rot13int
+
+instance Rot13 Int                    where rot13 = rot13int
+instance Rot13 Int8                   where rot13 = rot13int
+instance Rot13 Int16                  where rot13 = rot13int
+instance Rot13 Int32                  where rot13 = rot13int
+instance Rot13 Int64                  where rot13 = rot13int
+instance Rot13 Integer                where rot13 = rot13int
+
+instance Rot13 Foreign.CChar          where rot13 = rot13
+instance Rot13 Foreign.CSChar         where rot13 = rot13
+instance Rot13 Foreign.CUChar         where rot13 = rot13
+instance Rot13 Foreign.CShort         where rot13 = rot13
+instance Rot13 Foreign.CUShort        where rot13 = rot13
+instance Rot13 Foreign.CInt           where rot13 = rot13
+instance Rot13 Foreign.CUInt          where rot13 = rot13
+instance Rot13 Foreign.CLong          where rot13 = rot13
+instance Rot13 Foreign.CULong         where rot13 = rot13
+instance Rot13 Foreign.CWchar         where rot13 = rot13
+instance Rot13 Foreign.CLLong         where rot13 = rot13
+instance Rot13 Foreign.CULLong        where rot13 = rot13
+
+--------------------------------------------------------------------------------------------------
+-- Rot13Bytes Instances
+
+instance {-# OVERLAPPING #-} Rot13Bytes BS.ByteString where rot13bs = rot13
+instance {-# OVERLAPPING #-} Storable a => Rot13Bytes a where rot13bs = 
rot13stor
+
 
+--------------------------------------------------------------------------------------------------
+-- Compatibility
 
--- | Perform the ROT13 cipher on the given ANSI encoded 'Word'.
 {-# INLINE rot13word #-}
 rot13word :: Word -> Word
-rot13word x
-  | x - 97 < 26 = 97 + rem (x - 84) 26
-  | x - 65 < 26 = 65 + rem (x - 52) 26
-  | otherwise   = x
+rot13word = rot13
 
--- | Like 'rot13word', but using the smaller 'Word8' type.
---
--- @
---    rot13word8 = fromIntegral . rot13word . fromIntegral
--- @
 {-# INLINE rot13word8 #-}
 rot13word8 :: Word8 -> Word8
-rot13word8 = \x -> (fromIntegral . rot13word . fromIntegral) x
+rot13word8 = rot13
 
--- | Perform the ROT13 cipher on a single 'Char'. A ROT13 cipher is the 
inverse of itself, so one
---   function will both suitably encode and decode. Thus, the following holds:
---
--- @
---    rot13char . rot13char = id
--- @
 {-# INLINE rot13char #-}
 rot13char :: Char -> Char
-rot13char = \x -> (chr . fromIntegral . rot13word . fromIntegral . ord) x
+rot13char = rot13
 
--- | Perform the ROT13 cipher on a 'String'. This is just equivalent to:
---
--- @
---    rot13 = map rot13char
--- @
-{-# INLINABLE rot13 #-}
-rot13 :: String -> String
-rot13 = \s -> map rot13char s
-
--- | Like 'rot13' but for 'BS.ByteString's.
-{-# INLINABLE rot13bs #-}
-rot13bs :: BS.ByteString -> BS.ByteString
-rot13bs = \s -> BS.map rot13word8 s
+{-# INLINE rot13string #-}
+rot13string :: String -> String
+rot13string = rot13
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/rot13-0.1.0.2/test/Spec.hs 
new/rot13-0.2.0.1/test/Spec.hs
--- old/rot13-0.1.0.2/test/Spec.hs      2014-11-19 12:13:06.000000000 +0100
+++ new/rot13-0.2.0.1/test/Spec.hs      2017-07-11 15:16:13.000000000 +0200
@@ -1,20 +1,40 @@
+{-# LANGUAGE OverloadedStrings #-}
 
 module Main
   ( main
   ) where
 
-import Test.Hspec
-import Test.QuickCheck
+import           Test.Hspec
+import           Test.QuickCheck
 
-import Codec.Rot13
+import qualified Data.ByteString    as BS
+import qualified Data.Text          as T
+
+import           Codec.Rot13
 
 main :: IO ()
 main = hspec $ do
   describe "Codec.Rot13" $ do
 
-    it "correctly ciphers the alphabet" $ do
-      rot13 "ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz"
+    it "correctly ciphers the alphabet (rot13 String)" $ do
+      rot13 ("ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz" :: String)
         `shouldBe` "NOPQRSTUVWXYZABCDEFGHIJKLMnopqrstuvwxyzabcdefghijklm"
 
-    it "is reversible" $
-      property $ \s -> s == (rot13 . rot13) s
+    it "correctly ciphers the alphabet (rot13 ByteString)" $ do
+      rot13 "ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz"
+        `shouldBe` ("NOPQRSTUVWXYZABCDEFGHIJKLMnopqrstuvwxyzabcdefghijklm" :: 
BS.ByteString)
+
+    it "correctly ciphers the alphabet (rot13 Text)" $ do
+      rot13 "ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz"
+        `shouldBe` ("NOPQRSTUVWXYZABCDEFGHIJKLMnopqrstuvwxyzabcdefghijklm" :: 
T.Text)
+
+    it "is reversible (String)" $
+      property $ \s -> s == (rot13 . rot13 :: String -> String) s
+
+    it "is reversible (ByteString)" $
+      property $ \s -> let s' = BS.pack s
+                        in s' == (rot13 . rot13 :: BS.ByteString -> 
BS.ByteString) s'
+
+    it "is reversible (Text)" $
+      property $ \s -> let s' = T.pack s
+                        in s' == (rot13 . rot13 :: T.Text -> T.Text) s'


Reply via email to