Skip to content

Commit

Permalink
Merge pull request #3 from them492017/updated
Browse files Browse the repository at this point in the history
Updated library for latest Haskell package versions
  • Loading branch information
vrthra authored Mar 24, 2024
2 parents ddedf4c + 2f9d7e5 commit e04065f
Show file tree
Hide file tree
Showing 10 changed files with 30 additions and 28 deletions.
4 changes: 4 additions & 0 deletions .gitignore
Original file line number Diff line number Diff line change
@@ -1,6 +1,10 @@
test.log
Examples/*
dist/*
dist-newstyle/*
.hpc/*
*.tix
.mutants/*
.gitignore
.cabal-sandbox/*
cabal.sandbox.config
Expand Down
2 changes: 1 addition & 1 deletion Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -41,7 +41,7 @@ testrepl:
cabal repl --ghc-option='-package QuickCheck-2.6'

hpcex:
- rm Examples/*.hi Examples/*.o *.tix tests
#- rm Examples/*.hi Examples/*.o *.tix tests
cabal build sample-test
./dist/build/sample-test/sample-test
./dist/build/mucheck/mucheck -tix sample-test.tix Examples/AssertCheckTest.hs
10 changes: 5 additions & 5 deletions MuCheck.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -62,7 +62,7 @@ executable mucheck
main-is: Main.hs
ghc-options: -Wall
build-depends: base >=4 && <5,
haskell-src-exts >=1.16,
haskell-src-exts >=1.23,
syb >= 0.4.0,
time >= 1.4.0.1,
hint >= 0.3.1.0,
Expand All @@ -78,6 +78,7 @@ executable mucheck

executable sample-test
main-is: Examples/Main.hs
other-modules: Examples.AssertCheckTest
build-depends: base >=4 && <5,
MuCheck
default-language: Haskell2010
Expand All @@ -89,18 +90,17 @@ test-suite spec
main-is: Spec.hs
default-language: Haskell2010
build-depends: base >=4 && <5,
haskell-src-exts >=1.13,
haskell-src-exts >= 1.23,
syb >= 0.4.0,
time >= 1.4.0.1,
hint >= 0.3.1.0,
mtl>=2.1.2,
hspec>= 2.0,
MuCheck,
random >= 1.0.0,
random >= 1.2.1,
directory >= 1.2.0.1,
temporary >= 1.1,
hashable >= 1.2,
hpc >= 0.5.1.1,
template-haskell >= 2.5.0
default-language: Haskell2010

build-tool-depends: hspec-discover:hspec-discover
2 changes: 1 addition & 1 deletion src/Test/MuCheck/MuOp.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@ module Test.MuCheck.MuOp (MuOp
import qualified Data.Generics as G
import Control.Monad (MonadPlus, mzero)

import Language.Haskell.Exts.Annotated(Module, Name, QName, QOp, Exp, Decl, Literal, GuardedRhs, Annotation, SrcSpanInfo(..), srcSpanStart, srcSpanEnd, prettyPrint, Pretty(), Annotated(..))
import Language.Haskell.Exts(Module, Name, QName, QOp, Exp, Decl, Literal, GuardedRhs, Annotation, SrcSpanInfo(..), srcSpanStart, srcSpanEnd, prettyPrint, Pretty(), Annotated(..))

-- | SrcSpanInfo wrapper
type Module_ = Module SrcSpanInfo
Expand Down
2 changes: 1 addition & 1 deletion src/Test/MuCheck/Mutation.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@
-- | This module handles the mutation of different patterns.
module Test.MuCheck.Mutation where

import Language.Haskell.Exts.Annotated(Literal(Int, Char, Frac, String, PrimInt, PrimChar, PrimFloat, PrimDouble, PrimWord, PrimString),
import Language.Haskell.Exts(Literal(Int, Char, Frac, String, PrimInt, PrimChar, PrimFloat, PrimDouble, PrimWord, PrimString),
Exp(App, Var, If, Lit), QName(UnQual),
Match(Match), Pat(PVar),
Stmt(Qualifier), Module(Module),
Expand Down
2 changes: 1 addition & 1 deletion src/Test/MuCheck/Utils/Helpers.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
-- | Helper module for easier visualization
module Test.MuCheck.Utils.Helpers where
import Language.Haskell.Exts.Annotated
import Language.Haskell.Exts
import Test.MuCheck.MuOp

-- | Class to allow easier visualization of values without munging `show`
Expand Down
2 changes: 1 addition & 1 deletion test/Test/MuCheck/MutationSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@ import Test.MuCheck.Mutation
import Control.Monad (MonadPlus, mplus, mzero)
import Test.MuCheck.MuOp (mkMpMuOp, MuOp, (==>))
import Data.Generics (GenericQ, mkQ, Data, Typeable, mkMp, listify)
import Language.Haskell.Exts.Annotated
import Language.Haskell.Exts
import Here

main :: IO ()
Expand Down
2 changes: 1 addition & 1 deletion test/Test/MuCheck/MutationSpec/Helpers.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@ module Test.MuCheck.MutationSpec.Helpers where
import Here
import Test.MuCheck.Utils.Helpers
import Test.MuCheck.Mutation
import Language.Haskell.Exts.Annotated
import Language.Haskell.Exts
_myprop = [e|
module Prop where
import Test.QuickCheck
Expand Down
4 changes: 2 additions & 2 deletions test/Test/MuCheck/Utils/CommonSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,11 +32,11 @@ spec = do

describe "sample" $ do
it "must sample a given size subset" $ do
sample (mkStdGen 1) 2 [1,2,3,4] `shouldBe` [2, 3]
sample (mkStdGen 1) 2 [1,2,3,4] `shouldBe` [2, 4]

describe "sampleF" $ do
it "must sample a given fraction subset" $ do
sampleF (mkStdGen 1) 0.5 [1,2,3,4] `shouldBe` [2, 3]
sampleF (mkStdGen 1) 0.5 [1,2,3,4] `shouldBe` [2, 4]

describe "coupling" $ do
it "must sample a given fraction subset" $ do
Expand Down
28 changes: 13 additions & 15 deletions test/Test/MuCheck/Utils/SybSpec.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,6 @@
module Test.MuCheck.Utils.SybSpec where

import Test.Hspec
import System.Random
import qualified Test.MuCheck.Utils.Syb as S
import Control.Monad (MonadPlus, mplus, mzero)
import Test.MuCheck.MuOp (mkMpMuOp, MuOp)
Expand All @@ -11,27 +10,26 @@ import Language.Haskell.Exts
main :: IO ()
main = hspec spec

m1 a b = Match (SrcLoc "<unknown>.hs" 15 1)
(Ident a)
[PApp (UnQual (Ident b)) [],PLit Signless (Int 0)]
Nothing
(UnGuardedRhs (Lit (Int 1)))
(BDecls [])
dummySrcLoc = SrcLoc "<unknown>.hs" 15 1

replM :: MonadPlus m => Name -> m Name
replM (Ident "x") = return $ Ident "y"
replM t = mzero
m1 a b = Match (dummySrcLoc)
(Ident dummySrcLoc a)
[PApp dummySrcLoc (UnQual dummySrcLoc (Ident dummySrcLoc b)) [],PLit dummySrcLoc (Signless dummySrcLoc) (Int dummySrcLoc 0 "0")]
(UnGuardedRhs dummySrcLoc (Lit dummySrcLoc (Int dummySrcLoc 1 "1")))
(Just (BDecls dummySrcLoc []))

replM :: MonadPlus m => Name SrcLoc -> m (Name SrcLoc)
replM (Ident l "x") = return $ Ident l "y"
replM t = mzero

spec :: Spec
spec = do
describe "once" $ do
it "apply a function once on exp" $ do
(S.once (mkMp replM) (FunBind [m1 "y" "x"]) :: Maybe Decl) `shouldBe` Just (FunBind [m1 "y" "y"] :: Decl)
(S.once (mkMp replM) (FunBind dummySrcLoc [m1 "y" "x"]) :: Maybe (Decl SrcLoc)) `shouldBe` Just (FunBind dummySrcLoc [m1 "y" "y"] :: (Decl SrcLoc))
it "apply a function just once" $ do
(S.once (mkMp replM) (FunBind [m1 "x" "x"]) :: Maybe Decl) `shouldBe` Just (FunBind [m1 "y" "x"] :: Decl)
(S.once (mkMp replM) (FunBind dummySrcLoc [m1 "x" "x"]) :: Maybe (Decl SrcLoc)) `shouldBe` Just (FunBind dummySrcLoc [m1 "y" "x"] :: (Decl SrcLoc))
it "apply a function just once if possible" $ do
(S.once (mkMp replM) (FunBind [m1 "y" "y"]) :: Maybe Decl) `shouldBe` Nothing
(S.once (mkMp replM) (FunBind dummySrcLoc [m1 "y" "y"]) :: Maybe (Decl SrcLoc)) `shouldBe` Nothing
it "should return all possibilities" $ do
(S.once (mkMp replM) (FunBind [m1 "x" "x"]) :: [Decl]) `shouldBe` ([FunBind [m1 "y" "x"], FunBind [m1 "x" "y"]] :: [Decl])

(S.once (mkMp replM) (FunBind dummySrcLoc [m1 "x" "x"]) :: [(Decl SrcLoc)]) `shouldBe` ([FunBind dummySrcLoc [m1 "y" "x"], FunBind dummySrcLoc [m1 "x" "y"]] :: [(Decl SrcLoc)])

0 comments on commit e04065f

Please sign in to comment.