Skip to content
Snippets Groups Projects
Commit fa67ca4d authored by Simon Peyton Jones's avatar Simon Peyton Jones
Browse files

[project @ 2000-09-28 15:15:48 by simonpj]

Wibbles
parent 861e836e
No related merge requests found
...@@ -30,7 +30,7 @@ import Type ( Type, Kind, PredType(..), UsageAnn(..), ClassContext, ...@@ -30,7 +30,7 @@ import Type ( Type, Kind, PredType(..), UsageAnn(..), ClassContext,
getTyVar_maybe, splitSigmaTy, unUsgTy, boxedTypeKind getTyVar_maybe, splitSigmaTy, unUsgTy, boxedTypeKind
) )
import TypeRep ( Type(..), TyNote(..) ) -- toHsType sees the representation import TypeRep ( Type(..), TyNote(..) ) -- toHsType sees the representation
import TyCon ( isTupleTyCon, tupleTyConBoxity, tyConArity, tyConClass_maybe ) import TyCon ( isTupleTyCon, tupleTyConBoxity, tyConArity )
import RdrName ( RdrName ) import RdrName ( RdrName )
import Name ( toRdrName ) import Name ( toRdrName )
import OccName ( NameSpace ) import OccName ( NameSpace )
......
...@@ -199,9 +199,8 @@ checkPat e [] = case e of ...@@ -199,9 +199,8 @@ checkPat e [] = case e of
ExplicitList es -> mapP (\e -> checkPat e []) es `thenP` \ps -> ExplicitList es -> mapP (\e -> checkPat e []) es `thenP` \ps ->
returnP (ListPatIn ps) returnP (ListPatIn ps)
ExplicitTuple es Boxed -> mapP (\e -> checkPat e []) es `thenP` \ps -> ExplicitTuple es b -> mapP (\e -> checkPat e []) es `thenP` \ps ->
returnP (TuplePatIn ps Boxed) returnP (TuplePatIn ps b)
-- Unboxed tuples are illegal in patterns
RecordCon c fs -> mapP checkPatField fs `thenP` \fs -> RecordCon c fs -> mapP checkPatField fs `thenP` \fs ->
returnP (RecPatIn c fs) returnP (RecPatIn c fs)
......
...@@ -48,7 +48,7 @@ import Name ( nameOccName, isLocallyDefined, isGlobalName, ...@@ -48,7 +48,7 @@ import Name ( nameOccName, isLocallyDefined, isGlobalName,
toRdrName, nameEnvElts, toRdrName, nameEnvElts,
) )
import OccName ( isSysOcc ) import OccName ( isSysOcc )
import TyCon ( TyCon, tyConClass_maybe ) import TyCon ( TyCon, isClassTyCon )
import Class ( Class ) import Class ( Class )
import PrelNames ( mAIN_Name, mainKey ) import PrelNames ( mAIN_Name, mainKey )
import UniqSupply ( UniqSupply ) import UniqSupply ( UniqSupply )
...@@ -162,7 +162,7 @@ tcModule rn_name_supply fixities ...@@ -162,7 +162,7 @@ tcModule rn_name_supply fixities
local_classes = filter isLocallyDefined classes local_classes = filter isLocallyDefined classes
local_tycons = [ tc | tc <- tycons, local_tycons = [ tc | tc <- tycons,
isLocallyDefined tc, isLocallyDefined tc,
Nothing <- [tyConClass_maybe tc] not (isClassTyCon tc)
] ]
-- For local_tycons, filter out the ones derived from classes -- For local_tycons, filter out the ones derived from classes
-- Otherwise the latter show up in interface files -- Otherwise the latter show up in interface files
......
...@@ -34,7 +34,7 @@ module TyCon( ...@@ -34,7 +34,7 @@ module TyCon(
tyConTheta, tyConTheta,
tyConPrimRep, tyConPrimRep,
tyConArity, tyConArity,
tyConClass_maybe, isClassTyCon,
getSynTyConDefn, getSynTyConDefn,
maybeTyConSingleCon, maybeTyConSingleCon,
...@@ -110,10 +110,7 @@ data TyCon ...@@ -110,10 +110,7 @@ data TyCon
algTyConRec :: RecFlag, -- Tells whether the data type is part of algTyConRec :: RecFlag, -- Tells whether the data type is part of
-- a mutually-recursive group or not -- a mutually-recursive group or not
algTyConClass_maybe :: Maybe Class -- Nothing for ordinary types; algTyConClass :: Bool -- True if this tycon comes from a class declaration
-- Just c for the type constructor
-- for dictionaries of class c.
} }
| PrimTyCon { -- Primitive types; cannot be defined in Haskell | PrimTyCon { -- Primitive types; cannot be defined in Haskell
...@@ -232,7 +229,7 @@ mkAlgTyCon name kind tyvars theta argvrcs cons ncons derivs flavour rec ...@@ -232,7 +229,7 @@ mkAlgTyCon name kind tyvars theta argvrcs cons ncons derivs flavour rec
dataCons = cons, dataCons = cons,
noOfDataCons = ncons, noOfDataCons = ncons,
algTyConDerivings = derivs, algTyConDerivings = derivs,
algTyConClass_maybe = Nothing, algTyConClass = False,
algTyConFlavour = flavour, algTyConFlavour = flavour,
algTyConRec = rec algTyConRec = rec
} }
...@@ -249,7 +246,7 @@ mkClassTyCon name kind tyvars argvrcs con clas flavour ...@@ -249,7 +246,7 @@ mkClassTyCon name kind tyvars argvrcs con clas flavour
dataCons = [con], dataCons = [con],
noOfDataCons = 1, noOfDataCons = 1,
algTyConDerivings = [], algTyConDerivings = [],
algTyConClass_maybe = Just clas, algTyConClass = True,
algTyConFlavour = flavour, algTyConFlavour = flavour,
algTyConRec = NonRecursive algTyConRec = NonRecursive
} }
...@@ -429,9 +426,9 @@ maybeTyConSingleCon tc = pprPanic "maybeTyConSingleCon: unexpected tycon " $ ...@@ -429,9 +426,9 @@ maybeTyConSingleCon tc = pprPanic "maybeTyConSingleCon: unexpected tycon " $
\end{code} \end{code}
\begin{code} \begin{code}
tyConClass_maybe :: TyCon -> Maybe Class isClassTyCon :: TyCon -> Bool
tyConClass_maybe (AlgTyCon {algTyConClass_maybe = maybe_cls}) = maybe_cls isClassTyCon (AlgTyCon {algTyConClass = is_class_tycon}) = is_class_tycon
tyConClass_maybe other_tycon = Nothing isClassTyCon other_tycon = False
\end{code} \end{code}
......
...@@ -98,7 +98,7 @@ import TyCon ( TyCon, ...@@ -98,7 +98,7 @@ import TyCon ( TyCon,
isFunTyCon, isDataTyCon, isNewTyCon, newTyConRep, isFunTyCon, isDataTyCon, isNewTyCon, newTyConRep,
isAlgTyCon, isSynTyCon, tyConArity, isAlgTyCon, isSynTyCon, tyConArity,
tyConKind, tyConDataCons, getSynTyConDefn, tyConKind, tyConDataCons, getSynTyConDefn,
tyConPrimRep, tyConClass_maybe tyConPrimRep
) )
-- others -- others
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment