[Git][ghc/ghc][master] Add test for #23156

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Mon May 22 18:22:17 UTC 2023



Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
15b93d2f by Simon Peyton Jones at 2023-05-22T14:21:58-04:00
Add test for #23156

This program had exponential typechecking time in GHC 9.4 and 9.6

- - - - -


3 changed files:

- + testsuite/tests/typecheck/should_compile/T23156.hs
- + testsuite/tests/typecheck/should_compile/T23156.stderr
- testsuite/tests/typecheck/should_compile/all.T


Changes:

=====================================
testsuite/tests/typecheck/should_compile/T23156.hs
=====================================
@@ -0,0 +1,59 @@
+{-# LANGUAGE DataKinds, TypeFamilies, PartialTypeSignatures #-}
+{-# OPTIONS_GHC -fdefer-type-errors #-}
+module T23156 where
+
+import Prelude
+import GHC.TypeLits
+import Data.Kind
+
+type BooleanOf2 :: Type -> Type
+type family BooleanOf2 a
+
+type instance BooleanOf2 Double = Double
+
+-- Needs to be a type family, changing this to a datatype makes it fast
+type TensorOf2 :: Nat -> Type -> Type
+type family TensorOf2 k a
+
+type instance TensorOf2 n Double = Double
+
+
+-- With GHC 9.4 and 9.6, typechecking was
+-- exponential in the size of this tuple
+type ADReady r =
+  (  BooleanOf2 r ~ BooleanOf2 (TensorOf2 1 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 2 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 3 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 4 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 5 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 6 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 7 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 8 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 9 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 10 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 11 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 12 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 13 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 14 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 15 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 16 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 17 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 18 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 19 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 20 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 21 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 22 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 23 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 24 r)
+    , BooleanOf2 r ~ BooleanOf2 (TensorOf2 25 r)
+  )
+
+f :: forall r . (ADReady r) => ()
+f = undefined
+
+-- This uses a lot of memory
+g :: _ => ()
+g = f
+
+-- This is fine
+g' = f @Double


=====================================
testsuite/tests/typecheck/should_compile/T23156.stderr
=====================================
@@ -0,0 +1,25 @@
+
+T23156.hs:51:6: warning: [GHC-05617] [-Wdeferred-type-errors (in -Wdefault)]
+    • Could not deduce ‘BooleanOf2 (TensorOf2 1 r0) ~ BooleanOf2 r0’
+      from the context: ADReady r
+        bound by the type signature for:
+                   f :: forall r. ADReady r => ()
+        at T23156.hs:51:6-33
+      NB: ‘BooleanOf2’ is a non-injective type family
+      The type variables ‘r0’, ‘r0’ are ambiguous
+    • In the ambiguity check for ‘f’
+      To defer the ambiguity check to use sites, enable AllowAmbiguousTypes
+      In the type signature: f :: forall r. (ADReady r) => ()
+
+T23156.hs:55:6: warning: [GHC-88464] [-Wpartial-type-signatures (in -Wdefault)]
+    • Found extra-constraints wildcard standing for ‘() :: Constraint’
+    • In the type signature: g :: _ => ()
+
+T23156.hs:56:5: warning: [GHC-18872] [-Wdeferred-type-errors (in -Wdefault)]
+    • Couldn't match type: BooleanOf2 (TensorOf2 1 r0)
+                     with: BooleanOf2 r0
+        arising from a use of ‘f’
+      NB: ‘BooleanOf2’ is a non-injective type family
+      The type variables ‘r0’, ‘r0’ are ambiguous
+    • In the expression: f
+      In an equation for ‘g’: g = f


=====================================
testsuite/tests/typecheck/should_compile/all.T
=====================================
@@ -874,3 +874,4 @@ test('QualifiedRecordUpdate',
 test('T23171', normal, compile, [''])
 test('T23192', normal, compile, [''])
 test('T23199', normal, compile, [''])
+test('T23156', normal, compile, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/15b93d2f89464800465afa3a35151b904bddc730

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/15b93d2f89464800465afa3a35151b904bddc730
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20230522/60ff94a4/attachment-0001.html>


More information about the ghc-commits mailing list