Skip to content

Commit

Permalink
Checkpoint while compiling. Need Simon's input on design.
Browse files Browse the repository at this point in the history
  • Loading branch information
Richard Eisenberg committed Jun 14, 2013
1 parent 3343182 commit 725a16b
Show file tree
Hide file tree
Showing 5 changed files with 27 additions and 10 deletions.
6 changes: 3 additions & 3 deletions compiler/hsSyn/HsDecls.lhs
Expand Up @@ -480,7 +480,7 @@ data FamilyInfo name
= DataFamily
| OpenTypeFamily
| ClosedTypeFamily [LTyFamInstEqn name]
deriving( Data, Typeable, Eq )
deriving( Data, Typeable )
\end{code}

Expand Down Expand Up @@ -611,9 +611,9 @@ instance (OutputableBndr name) => Outputable (FamilyDecl name) where
(pp_where, pp_eqns) = case info of
ClosedTypeFamily eqns -> ( ptext (sLit "where")
, vcat $ map ppr eqns )
_ -> (empty, emtpy)
_ -> (empty, empty)
pprFlavour :: FamilyInfo -> SDoc
pprFlavour :: FamilyInfo name -> SDoc
pprFlavour DataFamily = ptext (sLit "data family")
pprFlavour OpenTypeFamily = ptext (sLit "type family")
pprFlavour (ClosedTypeFamily {}) = ptext (sLit "type family")
Expand Down
7 changes: 6 additions & 1 deletion compiler/iface/IfaceSyn.lhs
Expand Up @@ -503,10 +503,15 @@ pprIfaceDecl (IfaceSyn {ifName = tycon,
4 (vcat [equals <+> ppr mono_ty])
pprIfaceDecl (IfaceSyn {ifName = tycon, ifTyVars = tyvars,
ifSynRhs = SynFamilyTyCon {}, ifSynKind = kind })
ifSynRhs = OpenSynFamilyTyCon {}, ifSynKind = kind })
= hang (ptext (sLit "type family") <+> pprIfaceDeclHead [] tycon tyvars)
4 (dcolon <+> ppr kind)
pprIfaceDecl (IfaceSyn {ifName = tycon, ifTyVars = tyvars,
ifSynRhs = ClosedSynFamilyTyCon {}, ifSynKind = kind })
= hang (ptext (sLit "closed type family") <+> pprIfaceDeclHead [] tycon tyvars)
4 (dcolon <+> ppr kind)
pprIfaceDecl (IfaceData {ifName = tycon, ifCType = cType,
ifCtxt = context,
ifTyVars = tyvars, ifCons = condecls,
Expand Down
2 changes: 1 addition & 1 deletion compiler/parser/Parser.y.pp
Expand Up @@ -711,7 +711,7 @@
-- Note the use of type for the head; this allows
-- infix type constructors and type patterns
{% do { eqn <- mkTyFamInstEqn $1 $3
; return (LL eqn) }
; return (LL eqn) } }

-- Associated type family declarations
--
Expand Down
9 changes: 9 additions & 0 deletions compiler/types/FamInstEnv.lhs-boot
@@ -0,0 +1,9 @@
\begin{code}

module FamInstEnv where

data FamInst br

-- RAE: Remove this.

\end{code}
13 changes: 8 additions & 5 deletions compiler/types/TyCon.lhs
Expand Up @@ -88,6 +88,7 @@ module TyCon(
import {-# SOURCE #-} TypeRep ( Kind, Type, PredType )
import {-# SOURCE #-} DataCon ( DataCon, isVanillaDataCon )
import {-# SOURCE #-} FamInstEnv ( FamInst ) -- RAE Remove!!
import Var
import Class
Expand Down Expand Up @@ -1151,19 +1152,21 @@ isEnumerationTyCon (AlgTyCon {algTcRhs = DataTyCon { is_enum = res }}) = res
isEnumerationTyCon (TupleTyCon {tyConArity = arity}) = arity == 0
isEnumerationTyCon _ = False
-- | Is this a 'TyCon', synonym or otherwise, that may have further instances appear?
-- | Is this a 'TyCon', synonym or otherwise, that defines a family?
isFamilyTyCon :: TyCon -> Bool
isFamilyTyCon (SynTyCon {synTcRhs = SynFamilyTyCon {}}) = True
isFamilyTyCon (AlgTyCon {algTcRhs = DataFamilyTyCon {}}) = True
isFamilyTyCon (SynTyCon {synTcRhs = OpenSynFamilyTyCon }) = True
isFamilyTyCon (SynTyCon {synTcRhs = ClosedSynFamilyTyCon {} }) = True
isFamilyTyCon (AlgTyCon {algTcRhs = DataFamilyTyCon {}}) = True
isFamilyTyCon _ = False
-- | Is this a synonym 'TyCon' that can have may have further instances appear?
isSynFamilyTyCon :: TyCon -> Bool
isSynFamilyTyCon (SynTyCon {synTcRhs = SynFamilyTyCon {}}) = True
isSynFamilyTyCon (SynTyCon {synTcRhs = OpenSynFamilyTyCon {}}) = True
isSynFamilyTyCon (SynTyCon {synTcRhs = ClosedSynFamilyTyCon {}}) = True
isSynFamilyTyCon _ = False
isOpenSynFamilyTyCon :: TyCon -> Bool
isOpenSynFamilyTyCon (SynTyCon {synTcRhs = SynFamilyTyCon { synf_open = is_open } }) = is_open
isOpenSynFamilyTyCon (SynTyCon {synTcRhs = OpenSynFamilyTyCon }) = True
isOpenSynFamilyTyCon _ = False
-- | Is this a synonym 'TyCon' that can have may have further instances appear?
Expand Down

0 comments on commit 725a16b

Please sign in to comment.