[Git][ghc/ghc][wip/T16341] Minor tweaks

Brandon Chinn gitlab at gitlab.haskell.org
Tue Jul 28 00:37:01 UTC 2020



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


Commits:
91fa5efa by Brandon Chinn at 2020-07-27T17:36:56-07:00
Minor tweaks

- - - - -


2 changed files:

- compiler/GHC/Tc/Deriv/Generate.hs
- compiler/GHC/Tc/Deriv/Infer.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, getTyConArgs
+        getPossibleDataCons, tyConInstArgTys
     ) where
 
 #include "HsVersions.h"
@@ -2518,20 +2518,37 @@ newAuxBinderRdrName loc parent occ_fun = do
   uniq <- newUnique
   pure $ Exact $ mkSystemNameAt uniq (occ_fun (nameOccName parent)) loc
 
--- | If we're deriving an instance for a GADT, e.g. `Eq (Foo Int)`, we should treat any constructors
--- for which it's impossible to match `Foo Int` as not being there at all.
+-- | @getPossibleDataCons tycon tycon_args@ returns the constructors of @tycon@
+-- whose return types match when checked against @tycon_args at .
 --
 -- See Note [Filter out impossible GADT data constructors]
 getPossibleDataCons :: TyCon -> [Type] -> [DataCon]
 getPossibleDataCons tycon tycon_args = filter isPossible $ tyConDataCons tycon
   where
-    isPossible = not . dataConCannotMatch (getTyConArgs tycon tycon_args)
+    isPossible = not . dataConCannotMatch (tyConInstArgTys tycon tycon_args)
 
--- | Get the full list of TyCon args, given a partial instantiation.
+-- | Given a type constructor @tycon@ of arity /n/ and a list of argument types
+-- @tycon_args@ of length /m/,
 --
--- 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
+-- @
+-- tyConInstArgTys tycon tycon_args
+-- @
+--
+-- returns
+--
+-- @
+-- [tycon_arg_{1}, tycon_arg_{2}, ..., tycon_arg_{m}, extra_arg_{m+1}, ..., extra_arg_{n}]
+-- @
+--
+-- where @extra_args@ are distinct type variables.
+--
+-- Examples:
+--
+-- * Given @tycon: Foo a b@ and @tycon_args: [Int, Bool]@, return @[Int, Bool]@.
+--
+-- * Given @tycon: Foo a b@ and @tycon_args: [Int]@, return @[Int, b]@.
+tyConInstArgTys :: TyCon -> [Type] -> [Type]
+tyConInstArgTys tycon tycon_args = chkAppend tycon_args $ map mkTyVarTy tycon_args_suffix
   where
     tycon_args_suffix = drop (length tycon_args) $ tyConTyVars tycon
 
@@ -2766,7 +2783,18 @@ data Foo a where
 ```
 
 when deriving an instance on `Foo Int`, `Y` should be treated as if it didn't
-exist in the first place.
+exist in the first place. For instance, if we write
+
+```
+deriving instance Eq (Foo Int)
+```
+
+it should generate:
+
+```
+instance Eq (Foo Int) where
+  X == X = True
+```
 
 Classes that filter constructors:
 


=====================================
compiler/GHC/Tc/Deriv/Infer.hs
=====================================
@@ -260,7 +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 = getTyConArgs rep_tc rep_tc_args
+           all_rep_tc_args = tyConInstArgTys rep_tc rep_tc_args
 
                -- Stupid constraints
            stupid_constraints



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/91fa5efabb15b2467296791472c169271bbff455

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/91fa5efabb15b2467296791472c169271bbff455
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/5cc98b5c/attachment-0001.html>


More information about the ghc-commits mailing list