Skip to content
Draft
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
3 changes: 2 additions & 1 deletion halg-core-test/halg-core-test.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ cabal-version: 1.12
--
-- see: https://github.com/sol/hpack
--
-- hash: 9e31175e35b0b93f2f915aa2ec9fcd5a447c3a05722120d942aa470640d42279
-- hash: 2775958dc78ed62c1a1ec0e22067ce1381c763d699bb7bdd0a3e3095bb179b02

name: halg-core-test
version: 0.1.0.0
Expand Down Expand Up @@ -53,6 +53,7 @@ library
Algebra.Field.Finite.Test
Algebra.Field.Fraction.Test
Algebra.Field.Prime.Test
Algebra.Ring.Euclidean.Quotient.Test
Algebra.Ring.Ideal.Test
Algebra.Ring.Polynomial.Monomial.Test
Algebra.Ring.Polynomial.Test
Expand Down
14 changes: 14 additions & 0 deletions halg-core-test/src/Algebra/Ring/Euclidean/Quotient/Test.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,14 @@
{-# LANGUAGE PolyKinds #-}

module Algebra.Ring.Euclidean.Quotient.Test () where

import Algebra.Ring.Euclidean.Quotient
import AlgebraicPrelude (Euclidean)
import Data.Reflection
import Test.QuickCheck

instance
(Euclidean a, Arbitrary a, Reifies s a) =>
Arbitrary (Quotient s a)
where
arbitrary = quotient <$> arbitrary
7 changes: 5 additions & 2 deletions halg-core-test/src/Algebra/TestUtils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -33,10 +33,13 @@ import qualified Test.QuickCheck as QC
import Test.QuickCheck.Instances ()
import Prelude (($))

liftSNat :: (forall n. KnownNat (n :: Nat) => SNat n -> Property) -> Natural -> Property
liftSNat :: (forall n. KnownNat (n :: Nat) => SNat n -> x) -> Natural -> x
liftSNat f i =
case toSomeSNat i of
SomeSNat sn -> withKnownNat sn $ f sn

checkForTypeNat :: [Natural] -> (forall n. KnownNat (n :: Nat) => SNat n -> Property) -> Property
checkForTypeNat ::
[Natural] ->
(forall n. KnownNat (n :: Nat) => SNat n -> Property) ->
Property
checkForTypeNat as test = forAll (QC.elements as) $ liftSNat test
2 changes: 2 additions & 0 deletions halg-core/src/Algebra/Ring/Euclidean/Quotient.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,6 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PolyKinds #-}
Expand Down
20 changes: 14 additions & 6 deletions halg-polynomials/halg-polynomials.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -36,6 +36,7 @@ library
Algebra.Prelude.Core
Algebra.Ring.Polynomial
Algebra.Ring.Polynomial.Labeled
Algebra.Ring.Polynomial.List
Algebra.Ring.Polynomial.Quotient
Algebra.Ring.Polynomial.Univariate
other-modules:
Expand Down Expand Up @@ -74,6 +75,7 @@ library
, reflection
, singletons-presburger
, sized
, strict
, text
, type-natural
, unamb
Expand All @@ -92,11 +94,13 @@ test-suite halg-polynomials-spec
type: exitcode-stdio-1.0
main-is: Spec.hs
other-modules:
GroebnerSpec
PolynomialSpec
UnivariateSpec
QuotientSpec
Algebra.Algorithms.GroebnerSpec
Algebra.Ring.Polynomial.ListSpec
Algebra.Ring.Polynomial.QuotientSpec
Algebra.Ring.Polynomial.UnivariateSpec
Algebra.Ring.PolynomialSpec
Utils
Paths_halg_polynomials
hs-source-dirs:
test
default-extensions:
Expand All @@ -112,6 +116,8 @@ test-suite halg-polynomials-spec
TypeInType
UndecidableInstances
ghc-options: -Wall -threaded -rtsopts -with-rtsopts=-N
build-tool-depends:
tasty-discover:tasty-discover
build-depends:
QuickCheck
, algebra
Expand All @@ -121,9 +127,11 @@ test-suite halg-polynomials-spec
, halg-core
, halg-core-test
, halg-polynomials
, hspec
, hspec-discover
, matrix
, sized
, tasty
, tasty-expected-failure
, tasty-hunit
, tasty-quickcheck
, vector
default-language: Haskell2010
15 changes: 7 additions & 8 deletions halg-polynomials/package.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -58,6 +58,7 @@ library:
- deepseq
- equational-reasoning
- ghc-typelits-knownnat
- strict
- singletons-presburger
- hashable
- heaps
Expand Down Expand Up @@ -100,23 +101,21 @@ tests:
halg-polynomials-spec:
main: Spec.hs
source-dirs: test
other-modules:
- GroebnerSpec
- PolynomialSpec
- UnivariateSpec
- QuotientSpec
- Utils
ghc-options:
- -Wall
- -threaded
- -rtsopts
- -with-rtsopts=-N
build-tools:
- tasty-discover
dependencies:
- QuickCheck
- containers
- halg-core-test
- halg-polynomials
- hspec
- hspec-discover
- tasty
- tasty-expected-failure
- tasty-hunit
- tasty-quickcheck
- matrix
- vector
Loading