Skip to content

Commit

Permalink
Fix breakage, add more tests
Browse files Browse the repository at this point in the history
  • Loading branch information
kvanbere committed Jul 11, 2017
1 parent a4a4ed0 commit f891b4c
Show file tree
Hide file tree
Showing 3 changed files with 32 additions and 10 deletions.
2 changes: 2 additions & 0 deletions rot13.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -33,5 +33,7 @@ test-suite spec
build-depends:
base == 4.*,
hspec >= 1.3,
bytestring,
text,
QuickCheck,
rot13
6 changes: 3 additions & 3 deletions src/Codec/Rot13.hs
Original file line number Diff line number Diff line change
Expand Up @@ -60,8 +60,8 @@ class Rot13Bytes a where
-- | Perform the ROT13 cipher on the given 'Integral' instance (in the sense of 'Rot13').
rot13int :: Integral a => a -> a
rot13int x
| x - 97 < 26 = 97 + rem (x - 84) 26
| x - 65 < 26 = 65 + rem (x - 52) 26
| (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 #-}
Expand Down Expand Up @@ -91,7 +91,7 @@ rot13int x
-- | Perform the ROT13 cipher on the given 'Enum' instance (in the sense of 'Rot13').
{-# INLINE rot13enum #-}
rot13enum :: Enum a => a -> a
rot13enum = toEnum . rot13int . fromEnum
rot13enum = toEnum . (rot13int :: Int -> Int) . fromEnum

-- | Perform the ROT13 cipher on the given 'Storable' instance bytes to yield a 'BS.ByteString'.
{-# INLINE rot13stor #-}
Expand Down
34 changes: 27 additions & 7 deletions test/Spec.hs
Original file line number Diff line number Diff line change
@@ -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'

0 comments on commit f891b4c

Please sign in to comment.