[Git][ghc/ghc][wip/T16341] 3 commits: Update note

Brandon Chinn gitlab at gitlab.haskell.org
Mon Jul 27 19:15:30 UTC 2020



Brandon Chinn pushed to branch wip/T16341 at Glasgow Haskell Compiler / GHC


Commits:
db407f3f by Brandon Chinn at 2020-07-27T10:35:52-07:00
Update note

- - - - -
8855e414 by Brandon Chinn at 2020-07-27T11:12:36-07:00
Fix getting list of type variables for Functor derivation

- - - - -
700f1868 by Brandon Chinn at 2020-07-27T12:15:25-07:00
Fix test

- - - - -


3 changed files:

- compiler/GHC/Tc/Deriv/Generate.hs
- compiler/GHC/Tc/Deriv/Infer.hs
- testsuite/tests/deriving/should_compile/T16341.hs


Changes:

=====================================
compiler/GHC/Tc/Deriv/Generate.hs
=====================================
@@ -35,7 +35,7 @@ module GHC.Tc.Deriv.Generate (
         ordOpTbl, boxConTbl, litConTbl,
         mkRdrFunBind, mkRdrFunBindEC, mkRdrFunBindSE, error_Expr,
 
-        getPossibleDataCons
+        getPossibleDataCons, getTyConArgs
     ) where
 
 #include "HsVersions.h"
@@ -2523,7 +2523,17 @@ newAuxBinderRdrName loc parent occ_fun = do
 --
 -- See Note [Filter out impossible GADT data constructors]
 getPossibleDataCons :: TyCon -> [Type] -> [DataCon]
-getPossibleDataCons tycon tycon_args = filter (not . dataConCannotMatch tycon_args) $ tyConDataCons tycon
+getPossibleDataCons tycon tycon_args = filter isPossible $ tyConDataCons tycon
+  where
+    isPossible = not . dataConCannotMatch (getTyConArgs tycon tycon_args)
+
+-- | Get the full list of TyCon args, given a partial instantiation.
+--
+-- e.g. Given 'tycon: Foo a b' and 'tycon_args: [Int]', return '[Int, b]'.
+getTyConArgs :: TyCon -> [Type] -> [Type]
+getTyConArgs tycon tycon_args = tycon_args ++ map mkTyVarTy tycon_args_suffix
+  where
+    tycon_args_suffix = drop (length tycon_args) $ tyConTyVars tycon
 
 {-
 Note [Auxiliary binders]
@@ -2747,8 +2757,18 @@ Note [Filter out impossible GADT data constructors]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 
 Some stock-derivable classes will filter out impossible GADT data constructors,
-to rule out problematic constructors when deriving instances. Classes that
-filter constructors:
+to rule out problematic constructors when deriving instances. e.g.
+
+```
+data Foo a where
+  X :: Foo Int
+  Y :: (Bool -> Bool) -> Foo Bool
+```
+
+when deriving an instance on `Foo Int`, `Y` should be treated as if it didn't
+exist in the first place.
+
+Classes that filter constructors:
 
 * Eq
 * Ord
@@ -2765,8 +2785,9 @@ Classes that do not filter constructors:
 * Ix: only makes sense for GADTs with a single constructor
 * Read: `Read a` returns `a` instead of consumes `a`, so filtering data
   constructors would make this function _more_ partial instead of less
-* Data: uses `tagToEnum` to pick the constructor, which could reference
-  the incorrect constructors if we filter out constructors
+* Data: derived implementations of gunfold rely on a constructor-indexing
+  scheme that wouldn't work if certain constructors were filtered out
+* Generic/Generic1: doesn't make sense for GADTs
 
 Classes that do not currently filter constructors may do so in the future, if
 there is a valid use-case and we have requirements for how they should work.


=====================================
compiler/GHC/Tc/Deriv/Infer.hs
=====================================
@@ -260,9 +260,7 @@ inferConstraintsStock (DerivInstTys { dit_cls_tys     = cls_tys
            -- substitute each type variable with its counterpart in the derived
            -- instance. rep_tc_args lists each of these counterpart types in
            -- the same order as the type variables.
-           all_rep_tc_args
-             = rep_tc_args ++ map mkTyVarTy
-                                  (drop (length rep_tc_args) rep_tc_tvs)
+           all_rep_tc_args = getTyConArgs rep_tc rep_tc_args
 
                -- Stupid constraints
            stupid_constraints


=====================================
testsuite/tests/deriving/should_compile/T16341.hs
=====================================
@@ -8,6 +8,8 @@
 
 module T16341 where
 
+import Language.Haskell.TH.Syntax (Lift)
+
 data Foo a where
   Foo1 :: Foo Int
   Foo2 :: (Bool -> Bool) -> Foo Bool



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/58960da7b7bf446035debddd1fc0b64f2afe68e4...700f1868b32a6cf081275941e6a9d7a4911605ec

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/58960da7b7bf446035debddd1fc0b64f2afe68e4...700f1868b32a6cf081275941e6a9d7a4911605ec
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/20200727/270c2e30/attachment-0001.html>


More information about the ghc-commits mailing list