Skip to content

Commit

Permalink
Refactor tests
Browse files Browse the repository at this point in the history
Move cli-test back to test
  • Loading branch information
sgillespie committed Apr 30, 2017
1 parent 5968b1d commit 0bb2b5e
Show file tree
Hide file tree
Showing 7 changed files with 51 additions and 83 deletions.
70 changes: 0 additions & 70 deletions cli-test/Test/Elocrypt/Instances.hs

This file was deleted.

10 changes: 5 additions & 5 deletions elocrypt.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -75,9 +75,9 @@ test-suite ui-test
tasty-quickcheck,
tasty-th >= 0.1.7
default-language: Haskell2010
hs-source-dirs: cli-test
main-is: CliTests.hs
other-modules: Test.Elocrypt.Instances,
Test.Elocrypt.PassphraseTest
Test.Elocrypt.PasswordTest
hs-source-dirs: test
main-is: IntegTests.hs
other-modules: IntegTest.Elocrypt.PassphraseTest,
IntegTest.Elocrypt.PasswordTest,
Test.Elocrypt.Instances
type: exitcode-stdio-1.0
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
{-# LANGUAGE TemplateHaskell #-}
module Test.Elocrypt.PassphraseTest where
module IntegTest.Elocrypt.PassphraseTest where

import Control.Monad
import Data.List
Expand Down
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
{-# LANGUAGE TemplateHaskell #-}
module Test.Elocrypt.PasswordTest where
module IntegTest.Elocrypt.PasswordTest where

import Data.List
import Data.Maybe
Expand Down
6 changes: 3 additions & 3 deletions cli-test/CliTests.hs → test/IntegTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,8 +15,8 @@ import Test.Tasty hiding (Timeout)
import Test.Tasty.QuickCheck (QuickCheckTests(..), testProperty)
import Test.Tasty.TH

import qualified Test.Elocrypt.PasswordTest as PasswordTest
import qualified Test.Elocrypt.PassphraseTest as PassphraseTest
import qualified IntegTest.Elocrypt.PasswordTest as PasswordTest
import qualified IntegTest.Elocrypt.PassphraseTest as PassphraseTest

main :: IO ()
main = defaultMain (options tests)
Expand All @@ -25,7 +25,7 @@ options :: TestTree -> TestTree
options = localOption (QuickCheckTests 10)

tests :: TestTree
tests = testGroup "CLI Tests" [
tests = testGroup "Integration Tests" [
PasswordTest.tests,
PassphraseTest.tests
]
Expand Down
40 changes: 39 additions & 1 deletion test/Test/Elocrypt/Instances.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,14 +2,52 @@ module Test.Elocrypt.Instances where

import Control.Monad
import System.Random
import Text.Printf

import Test.QuickCheck

newtype CliArgs
= CliArgs { getArgs :: [String] }
deriving Eq

instance Show CliArgs where
show = unwords . getArgs

instance Arbitrary CliArgs where
arbitrary = do
len <- arbitrary `suchThat` (>0) `suchThat` (<=40) :: Gen Int
num <- arbitrary `suchThat` (>2) `suchThat` (<=20) :: Gen Int
args <- sublistOf ["-n %d" `printf` num,
show len]
return (CliArgs args)

newtype PhraseCliArgs
= PhraseCliArgs { getPhraseArgs :: [String] }
deriving Eq

instance Show PhraseCliArgs where
show = unwords . getPhraseArgs

instance Arbitrary PhraseCliArgs where
arbitrary = do
num <- arbitrary `suchThat` (>2) `suchThat` (<=20) :: Gen Int
minLen <- arbitrary `suchThat` (>0) `suchThat` (<=40) :: Gen Int
maxLen <- arbitrary `suchThat` (>0) `suchThat` (<=40) :: Gen Int

-- Need Either [], [num], or [num, minLength, maxLength]
args <- sublistOf ["-n %d" `printf` num,
show minLen,
show (maxLen + minLen)]

return $ PhraseCliArgs ("-p" : args)

-- Uh oh! I copy/pasted this!
instance Arbitrary StdGen where
arbitrary = mkStdGen `liftM` arbitrary

newtype AlphaChar = Alpha Char
deriving (Eq, Ord, Show)

--
instance Arbitrary AlphaChar where
arbitrary = Alpha `liftM` elements ['a'..'z']

Expand Down
4 changes: 2 additions & 2 deletions test/Tests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,5 +10,5 @@ main :: IO ()
main = defaultMain tests

tests :: TestTree
tests = testGroup "All Tests" [PasswordTest.tests,
TrigraphTest.tests]
tests = testGroup "Unit Tests" [PasswordTest.tests,
TrigraphTest.tests]

0 comments on commit 0bb2b5e

Please sign in to comment.