[Git][ghc/ghc][wip/T18185] Add orderingTyCon to wiredInTyCons (#18185)

Ryan Scott gitlab at gitlab.haskell.org
Fri May 15 10:26:06 UTC 2020



Ryan Scott pushed to branch wip/T18185 at Glasgow Haskell Compiler / GHC


Commits:
28ee5a1f by Ryan Scott at 2020-05-15T06:23:45-04:00
Add orderingTyCon to wiredInTyCons (#18185)

`Ordering` needs to be wired in for use in the built-in `CmpNat` and
`CmpSymbol` type families, but somehow it was never added to the list
of `wiredInTyCons`, leading to the various oddities observed
in #18185. Easily fixed by moving `orderingTyCon` from
`basicKnownKeyNames` to `wiredInTyCons`.

Fixes #18185.

- - - - -


4 changed files:

- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Builtin/Types.hs
- + testsuite/tests/typecheck/should_compile/T18185.hs
- testsuite/tests/typecheck/should_compile/all.T


Changes:

=====================================
compiler/GHC/Builtin/Names.hs
=====================================
@@ -428,10 +428,6 @@ basicKnownKeyNames
         -- Annotation type checking
         toAnnotationWrapperName
 
-        -- The Ordering type
-        , orderingTyConName
-        , ordLTDataConName, ordEQDataConName, ordGTDataConName
-
         -- The SPEC type for SpecConstr
         , specTyConName
 


=====================================
compiler/GHC/Builtin/Types.hs
=====================================
@@ -202,8 +202,11 @@ names in GHC.Builtin.Names, so they use wTcQual, wDataQual, etc
 -- that occurs in this list that name will be assigned the wired-in key we
 -- define here.
 --
--- Because of their infinite nature, this list excludes tuples, Any and implicit
--- parameter TyCons (see Note [Built-in syntax and the OrigNameCache]).
+-- Because of their infinite nature, this list excludes
+--   * tuples, including boxed, unboxed and constraint tuples
+---       (mkTupleTyCon, unitTyCon, pairTyCon)
+--   * unboxed sums (sumTyCon)
+-- See Note [Infinite families of known-key names] in GHC.Builtin.Names
 --
 -- See also Note [Known-key names]
 wiredInTyCons :: [TyCon]
@@ -224,6 +227,7 @@ wiredInTyCons = [ -- Units are not treated like other tuples, because they
                 , wordTyCon
                 , word8TyCon
                 , listTyCon
+                , orderingTyCon
                 , maybeTyCon
                 , heqTyCon
                 , eqTyCon


=====================================
testsuite/tests/typecheck/should_compile/T18185.hs
=====================================
@@ -0,0 +1,31 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE MultiParamTypeClasses #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE TypeOperators #-}
+module T18185 where
+
+import GHC.TypeLits
+import Type.Reflection
+
+class iss :|+ is  ~ oss => AddT (iss :: [Symbol]) (is :: Symbol) (oss :: [Symbol]) where
+ type iss :|+ is :: [Symbol]
+
+class (CmpSymbol is ish ~ ord, AddT'I ord is ish ist ~ oss) => AddT' ord is ish ist oss where
+ type AddT'I ord is ish ist :: [Symbol]
+
+class (CmpSymbol "a" "a" ~ o) => C1 o
+class (CmpNat 1 1 ~ o) => C2 o
+class ((CmpSymbol "a" "a" :: Ordering) ~ o) => C3 o
+class ((CmpNat 1 1 :: Ordering) ~ o) => C4 o
+
+f1 :: TypeRep (CmpSymbol "a" "a")
+f1 = typeRep
+
+f2 :: TypeRep (CmpNat 1 1)
+f2 = typeRep
+
+f3 :: TypeRep (CmpSymbol "a" "a" :: Ordering)
+f3 = typeRep
+
+f4 :: TypeRep (CmpNat 1 1 :: Ordering)
+f4 = typeRep


=====================================
testsuite/tests/typecheck/should_compile/all.T
=====================================
@@ -707,3 +707,4 @@ test('T18036', normal, compile, [''])
 test('T18036a', normal, compile, [''])
 test('T17873', normal, compile, [''])
 test('T18129', expect_broken(18129), compile, [''])
+test('T18185', normal, compile, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/28ee5a1f407257fdcd39ac0c9fec523488da4998

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/28ee5a1f407257fdcd39ac0c9fec523488da4998
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/20200515/4a17aa1b/attachment-0001.html>


More information about the ghc-commits mailing list