18
18
19
19
module SensStaticHMatrix where
20
20
21
- import GHC.TypeLits (Nat )
21
+ import GHC.TypeLits (Nat , SomeNat ( SomeNat ) )
22
22
import GHC.TypeLits qualified as TL
23
23
import GHC.TypeNats (KnownNat , SNat )
24
24
import Numeric.LinearAlgebra.Static
@@ -45,6 +45,11 @@ import Test.QuickCheck.Test (test)
45
45
newtype SensStaticHMatrix (x :: Nat ) (y :: Nat ) (m :: CMetric ) (n :: NMetric ) (s :: SEnv ) =
46
46
SensStaticHMatrixUNSAFE { unSensStaticHMatrix :: L x y }
47
47
48
+ instance (KnownNat x , KnownNat y ) => Eq (SensStaticHMatrix x y m n s ) where
49
+ -- What on earth is this supposed to be? L doesn't even have an Eq
50
+ -- instance!
51
+ (==) = error " Eq for SensStaticHMatrix unimplemented"
52
+
48
53
49
54
instance (forall senv . KnownNat x , KnownNat y ) => Arbitrary (SensStaticHMatrix x y cmetric nmetric s1 ) where
50
55
arbitrary = do
@@ -210,12 +215,31 @@ exampleTwo = do
210
215
elems2 <- replicateM ( fromInteger x' * fromInteger y') (arbitrary @ Double )
211
216
pure (SomeMatrix @ x @ y $ SensStaticHMatrixUNSAFE $ matrix elems1, SomeMatrix @ x @ y $ SensStaticHMatrixUNSAFE $ matrix elems2)
212
217
218
+ exampleThree ::
219
+ forall x y c n s1 .
220
+ (KnownNat x , KnownNat y ) =>
221
+ Gen (SensStaticHMatrix x y c n s1 )
222
+ exampleThree = do
223
+ elems1 <- replicateM (fromInteger (reflect (Proxy @ x ))) (arbitrary @ Double )
224
+ pure (SensStaticHMatrixUNSAFE $ matrix elems1)
213
225
214
- test = do
215
- (SomeMatrix m1, SomeMatrix m2) <- generate $ exampleTwo @ L2 @ Diff
226
+ arbitraryKnownNat :: Gen SomeNat
227
+ arbitraryKnownNat = do
228
+ x' <- arbitrary
229
+ reifyNat x' $ \ (Proxy @ x ) ->
230
+ pure (SomeNat @ x Proxy )
231
+
232
+ test = generate $ do
233
+ SomeNat @ x _ <- arbitraryKnownNat
234
+ SomeNat @ y _ <- arbitraryKnownNat
235
+ m1 <- exampleThree @ x @ y @ L2 @ Diff
236
+ m2 <- exampleThree @ x @ y @ L2 @ Diff
216
237
pure $ (plus m1 m2) == (plus m1 m2)
217
- -- ^ ^^
218
- -- Couldn't match type ‘y1’ with ‘y’
219
- -- Expected: SensStaticHMatrix x y L2 Diff s20
220
- -- Actual: SensStaticHMatrix x1 y1 L2 Diff s20
221
238
239
+ test2 = generate $ do
240
+ SomeNat @ x _ <- arbitraryKnownNat
241
+ SomeNat @ y _ <- arbitraryKnownNat
242
+ SomeNat @ z _ <- arbitraryKnownNat
243
+ m1 <- exampleThree @ x @ y @ L2 @ Diff
244
+ m2 <- exampleThree @ y @ z @ L2 @ Diff
245
+ pure $ (mult m1 m2) == (mult m1 m2)
0 commit comments