[Git][ghc/ghc][wip/T16341] 2 commits: Remove from Read, fix test suite
Brandon Chinn
gitlab at gitlab.haskell.org
Sun Jul 26 17:20:52 UTC 2020
Brandon Chinn pushed to branch wip/T16341 at Glasgow Haskell Compiler / GHC
Commits:
fcaed721 by Brandon Chinn at 2020-07-26T10:08:59-07:00
Remove from Read, fix test suite
- - - - -
58960da7 by Brandon Chinn at 2020-07-26T10:20:48-07:00
Added note
- - - - -
2 changed files:
- compiler/GHC/Tc/Deriv/Generate.hs
- testsuite/tests/deriving/should_compile/T16341.hs
Changes:
=====================================
compiler/GHC/Tc/Deriv/Generate.hs
=====================================
@@ -1033,7 +1033,7 @@ we want to be able to parse (Left 3) just fine.
gen_Read_binds :: (Name -> Fixity) -> SrcSpan -> TyCon -> [Type]
-> (LHsBinds GhcPs, BagDerivStuff)
-gen_Read_binds get_fixity loc tycon tycon_args
+gen_Read_binds get_fixity loc tycon _
= (listToBag [read_prec, default_readlist, default_readlistprec], emptyBag)
where
-----------------------------------------------------------------------
@@ -1044,7 +1044,7 @@ gen_Read_binds get_fixity loc tycon tycon_args
= mkHsVarBind loc readListPrec_RDR (nlHsVar readListPrecDefault_RDR)
-----------------------------------------------------------------------
- data_cons = getPossibleDataCons tycon tycon_args
+ data_cons = tyConDataCons tycon
(nullary_cons, non_nullary_cons) = partition isNullarySrcDataCon data_cons
read_prec = mkHsVarBind loc readPrec_RDR rhs
@@ -1406,7 +1406,7 @@ gen_Data_binds loc rep_tc _
data_cons dataC_RDRs )
) }
where
- data_cons = tyConDataCons rep_tc
+ data_cons = tyConDataCons rep_tc
n_cons = length data_cons
one_constr = n_cons == 1
@@ -2521,7 +2521,7 @@ newAuxBinderRdrName loc parent occ_fun = do
-- | 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.
--
--- See #16341 and the T16341.hs test case.
+-- See Note [Filter out impossible GADT data constructors]
getPossibleDataCons :: TyCon -> [Type] -> [DataCon]
getPossibleDataCons tycon tycon_args = filter (not . dataConCannotMatch tycon_args) $ tyConDataCons tycon
@@ -2742,4 +2742,34 @@ derived instances within the same module, not separated by any TH splices.
(This is the case described in "Wrinkle: Reducing code duplication".) In
situation (1), we can at least fall back on GHC's simplifier to pick up
genAuxBinds' slack.
+
+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:
+
+* Eq
+* Ord
+* Show
+* Lift
+* Functor
+* Foldable
+* Traversable
+
+Classes that do not filter constructors:
+
+* Enum: doesn't make sense for GADTs in the first place
+* Bounded: only makes sense for GADTs with a single constructor
+* 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
+
+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.
+
+See #16341 and the T16341.hs test case.
-}
=====================================
testsuite/tests/deriving/should_compile/T16341.hs
=====================================
@@ -1,12 +1,13 @@
-{-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE DeriveFunctor #-}
+{-# LANGUAGE DeriveFoldable #-}
+{-# LANGUAGE DeriveLift #-}
+{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE StandaloneDeriving #-}
module T16341 where
-import Data.Data (Data)
-
data Foo a where
Foo1 :: Foo Int
Foo2 :: (Bool -> Bool) -> Foo Bool
@@ -15,7 +16,6 @@ data Foo a where
-- `Foo`, because the `Foo Int` designation precludes `Foo2` from being
-- a reachable constructor
deriving instance Show (Foo Int)
-deriving instance Read (Foo Int)
deriving instance Eq (Foo Int)
deriving instance Ord (Foo Int)
deriving instance Lift (Foo Int)
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a03e1c0efe4d34d9dc45aee7d6fbd6d9e9bb1c4d...58960da7b7bf446035debddd1fc0b64f2afe68e4
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a03e1c0efe4d34d9dc45aee7d6fbd6d9e9bb1c4d...58960da7b7bf446035debddd1fc0b64f2afe68e4
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/20200726/74940e14/attachment-0001.html>
More information about the ghc-commits
mailing list