summaryrefslogtreecommitdiff
path: root/ghc/compiler/hsSyn/HsDecls.lhs
diff options
context:
space:
mode:
authorsimonpj <unknown>2004-03-17 13:59:19 +0000
committersimonpj <unknown>2004-03-17 13:59:19 +0000
commitaf5a215172aa3b964ece212f229bfee9f7c6b6b2 (patch)
tree275a2f4e3615cb5093d7d38ea70a9b86dbfde98b /ghc/compiler/hsSyn/HsDecls.lhs
parenta34e79f1eb35d135e7d82a700cc77b40f9eb2b88 (diff)
downloadhaskell-af5a215172aa3b964ece212f229bfee9f7c6b6b2.tar.gz
[project @ 2004-03-17 13:59:06 by simonpj]
------------------------ More newtype clearing up ------------------------ * Change the representation of TyCons so that it accurately reflects * data (0 or more constrs) * newtype (1 constr) * abstract (unknown) Replaces DataConDetails and AlgTyConFlavour with AlgTyConRhs * Add IfaceSyn.IfaceConDecls, a kind of stripped-down analogue of AlgTyConRhs * Move NewOrData from BasicTypes to HsDecl (it's now an HsSyn thing) * Arrange that Type.newTypeRep and splitRecNewType_maybe unwrap just one layer of new-type-ness, leaving the caller to recurse. This still leaves typeRep and repType in Type.lhs; these functions are still vaguely disturbing and probably should get some attention. Lots of knock-on changes. Fixes bug in ds054.
Diffstat (limited to 'ghc/compiler/hsSyn/HsDecls.lhs')
-rw-r--r--ghc/compiler/hsSyn/HsDecls.lhs13
1 files changed, 11 insertions, 2 deletions
diff --git a/ghc/compiler/hsSyn/HsDecls.lhs b/ghc/compiler/hsSyn/HsDecls.lhs
index 474131a10d..930dcdcea5 100644
--- a/ghc/compiler/hsSyn/HsDecls.lhs
+++ b/ghc/compiler/hsSyn/HsDecls.lhs
@@ -9,7 +9,7 @@ Definitions for: @TyDecl@ and @oCnDecl@, @ClassDecl@,
\begin{code}
module HsDecls (
HsDecl(..), LHsDecl, TyClDecl(..), LTyClDecl,
- InstDecl(..), LInstDecl,
+ InstDecl(..), LInstDecl, NewOrData(..),
RuleDecl(..), LRuleDecl, RuleBndr(..),
DefaultDecl(..), LDefaultDecl, HsGroup(..), SpliceDecl(..),
ForeignDecl(..), LForeignDecl, ForeignImport(..), ForeignExport(..),
@@ -38,7 +38,7 @@ import HsImpExp ( pprHsVar )
import HsTypes
import HscTypes ( DeprecTxt )
import CoreSyn ( RuleName )
-import BasicTypes ( NewOrData(..), Activation(..) )
+import BasicTypes ( Activation(..) )
import ForeignCall ( CCallTarget(..), DNCallSpec, CCallConv, Safety,
CExportSpec(..))
@@ -323,6 +323,11 @@ data TyClDecl name
tcdSigs :: [LSig name], -- Methods' signatures
tcdMeths :: LHsBinds name -- Default methods
}
+
+data NewOrData
+ = NewType -- "newtype Blah ..."
+ | DataType -- "data Blah ..."
+ deriving( Eq ) -- Needed because Demand derives Eq
\end{code}
Simple classifiers
@@ -431,6 +436,10 @@ pp_tydecl pp_head pp_decl_rhs derivings
Just ds -> hsep [ptext SLIT("deriving"),
ppr_hs_context (unLoc ds)]
])
+
+instance Outputable NewOrData where
+ ppr NewType = ptext SLIT("newtype")
+ ppr DataType = ptext SLIT("data")
\end{code}