A few changes to the project

This commit is contained in:
Yann Esposito (Yogsototh) 2020-01-03 08:21:17 +01:00
parent f8586974b6
commit f95b37c771
Signed by untrusted user who does not match committer: yogsototh
GPG key ID: 7B19A4C650D59646
5 changed files with 63 additions and 16 deletions

View file

@ -4,9 +4,9 @@ module Main where
import Protolude
import qualified MyLib (genPassword)
import qualified MyLib (someFunc)
main :: IO ()
main = do
pwd <- MyLib.genPassword
putText pwd
putText "Hello Haskell!"
MyLib.someFunc

View file

@ -18,7 +18,11 @@ in
packages = p: [drv];
# packages dependencies (by default haskellPackages)
buildInputs = with haskellPackages;
[ hlint
[ apply-refact
hlint
stylish-haskell
hasktags
hoogle
ghcid
cabal-install
cabal2nix

View file

@ -55,4 +55,8 @@ test-suite hspwg-test
type: exitcode-stdio-1.0
hs-source-dirs: test
main-is: MyLibTest.hs
-- build-depends: base ^>=4.12.0.0
build-depends: protolude,
tasty ^>= 1.2.0,
tasty-hunit,
tasty-smallcheck,
tasty-quickcheck

View file

@ -1,15 +1,8 @@
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module MyLib (genPassword) where
module MyLib (someFunc) where
import Protolude
import Data.Char (chr,ord)
import qualified System.Random as Random
genPassword :: IO Text
genPassword = do
let stdgen = Random.mkStdGen 0
numbers = take 10 (Random.randoms stdgen)
password = toS [ chr ( (n `mod` 27) + ord 'a') | n <- numbers ]
return password
someFunc :: IO ()
someFunc = putText "someFunc"

View file

@ -1,4 +1,50 @@
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Main (main) where
import Protolude
import Test.Tasty
import Test.Tasty.SmallCheck as SC
import Test.Tasty.QuickCheck as QC
import Test.Tasty.HUnit
main :: IO ()
main = putStrLn "Test suite not yet implemented."
main = defaultMain tests
tests :: TestTree
tests = testGroup "Tests" [properties, unitTests]
properties :: TestTree
properties = testGroup "Properties" [scProps, qcProps]
scProps = testGroup "(checked by SmallCheck)"
[ SC.testProperty "sort == sort . reverse" $
\list -> sort (list :: [Int]) == sort (reverse list)
, SC.testProperty "Fermat's little theorem" $
\x -> ((x :: Integer)^7 - x) `mod` 7 == 0
-- the following property does not hold
, SC.testProperty "Fermat's last theorem" $
\x y z n ->
(n :: Integer) >= 3 SC.==> x^n + y^n /= (z^n :: Integer)
]
qcProps = testGroup "(checked by QuickCheck)"
[ QC.testProperty "sort == sort . reverse" $
\list -> sort (list :: [Int]) == sort (reverse list)
, QC.testProperty "Fermat's little theorem" $
\x -> ((x :: Integer)^7 - x) `mod` 7 == 0
-- the following property does not hold
, QC.testProperty "Fermat's last theorem" $
\x y z n ->
(n :: Integer) >= 3 QC.==> x^n + y^n /= (z^n :: Integer)
]
unitTests = testGroup "Unit tests"
[ testCase "List comparison (different length)" $
[1, 2, 3] `compare` [1,2] @?= GT
-- the following test does not hold
, testCase "List comparison (same length)" $
[1, 2, 3] `compare` [1,2,2] @?= LT
]