[commit: ghc] master: Fix Read for empty data types (again; Trac #7931) (30059bd)

Simon Peyton Jones simonpj at microsoft.com
Thu May 30 16:12:57 CEST 2013


Repository : http://darcs.haskell.org/ghc.git/

On branch  : master

https://github.com/ghc/ghc/commit/30059bd8c19f510114075bc5918509b75c98ab06

>---------------------------------------------------------------

commit 30059bd8c19f510114075bc5918509b75c98ab06
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Thu May 30 15:12:12 2013 +0100

    Fix Read for empty data types (again; Trac #7931)

>---------------------------------------------------------------

 compiler/prelude/PrelNames.lhs    |  3 ++-
 compiler/typecheck/TcGenDeriv.lhs | 20 +++++++++++++++++++-
 2 files changed, 21 insertions(+), 2 deletions(-)

diff --git a/compiler/prelude/PrelNames.lhs b/compiler/prelude/PrelNames.lhs
index 09835fb..fe1e8b1 100644
--- a/compiler/prelude/PrelNames.lhs
+++ b/compiler/prelude/PrelNames.lhs
@@ -617,11 +617,12 @@ punc_RDR                = dataQual_RDR lEX (fsLit "Punc")
 ident_RDR               = dataQual_RDR lEX (fsLit "Ident")
 symbol_RDR              = dataQual_RDR lEX (fsLit "Symbol")
 
-step_RDR, alt_RDR, reset_RDR, prec_RDR :: RdrName
+step_RDR, alt_RDR, reset_RDR, prec_RDR, pfail_RDR :: RdrName
 step_RDR                = varQual_RDR  rEAD_PREC (fsLit "step")
 alt_RDR                 = varQual_RDR  rEAD_PREC (fsLit "+++")
 reset_RDR               = varQual_RDR  rEAD_PREC (fsLit "reset")
 prec_RDR                = varQual_RDR  rEAD_PREC (fsLit "prec")
+pfail_RDR               = varQual_RDR  rEAD_PREC (fsLit "pfail")
 
 showList_RDR, showList___RDR, showsPrec_RDR, showString_RDR,
     showSpace_RDR, showParen_RDR :: RdrName
diff --git a/compiler/typecheck/TcGenDeriv.lhs b/compiler/typecheck/TcGenDeriv.lhs
index b8c7c8c..5647562 100644
--- a/compiler/typecheck/TcGenDeriv.lhs
+++ b/compiler/typecheck/TcGenDeriv.lhs
@@ -882,6 +882,24 @@ string, and this can be very voluminous. The former is much more
 compact.  Cf Trac #7258, although that also concerned non-linearity in
 the occurrence analyser, a separate issue.
 
+Note [Read for empty data types]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+What should we get for this?  (Trac #7931)
+   data Emp deriving( Read )   -- No data constructors
+
+Here we want
+  read "[]" :: [Emp]   to succeed, returning []
+So we do NOT want 
+   instance Read Emp where
+     readPrec = error "urk"
+Rather we want
+   instance Read Emp where
+     readPred = pfail   -- Same as choose []
+
+Because 'pfail' allows the parser to backtrack, but 'error' doesn't.
+These instances are also useful for Read (Either Int Emp), where 
+we want to be able to parse (Left 3) just fine.
+
 \begin{code}
 gen_Read_binds :: FixityEnv -> SrcSpan -> TyCon -> (LHsBinds RdrName, BagDerivStuff)
 
@@ -902,7 +920,7 @@ gen_Read_binds get_fixity loc tycon
     read_prec = mkHsVarBind loc readPrec_RDR
                               (nlHsApp (nlHsVar parens_RDR) read_cons)
 
-    read_cons | null data_cons = error_Expr "Derived Read on empty data type" -- Trac #7931
+    read_cons | null data_cons = nlHsVar pfail_RDR  -- See Note [Read for empty data types]
               | otherwise      = foldr1 mk_alt (read_nullary_cons ++ read_non_nullary_cons)
     read_non_nullary_cons = map read_non_nullary_con non_nullary_cons
 





More information about the ghc-commits mailing list