Store a SrcSpan instead of a SrcLoc inside a Name
[ghc-hetmet.git] / compiler / main / PprTyThing.hs
index 2763b05..86c6f4c 100644 (file)
@@ -17,7 +17,10 @@ module PprTyThing (
 #include "HsVersions.h"
 
 import qualified GHC
-import GHC ( TyThing(..), SrcLoc )
+
+import TyCon   ( tyConFamInst_maybe )
+import Type    ( pprTypeApp )
+import GHC     ( TyThing(..), SrcSpan )
 import Outputable
 
 -- -----------------------------------------------------------------------------
@@ -30,7 +33,7 @@ import Outputable
 pprTyThingLoc :: Bool -> TyThing -> SDoc
 pprTyThingLoc exts tyThing 
   = showWithLoc loc (pprTyThing exts tyThing)
-  where loc = GHC.nameSrcLoc (GHC.getName tyThing)
+  where loc = GHC.nameSrcSpan (GHC.getName tyThing)
 
 -- | Pretty-prints a 'TyThing'.
 pprTyThing :: Bool -> TyThing -> SDoc
@@ -43,7 +46,7 @@ pprTyThing exts (AClass cls)       = pprClass      exts cls
 pprTyThingInContextLoc :: Bool -> TyThing -> SDoc
 pprTyThingInContextLoc exts tyThing 
   = showWithLoc loc (pprTyThingInContext exts tyThing)
-  where loc = GHC.nameSrcLoc (GHC.getName tyThing)
+  where loc = GHC.nameSrcSpan (GHC.getName tyThing)
 
 -- | Pretty-prints a 'TyThing' in context: that is, if the entity
 -- is a data constructor, record selector, or class method, then 
@@ -64,8 +67,11 @@ pprTyThingHdr exts (ADataCon dataCon) = pprDataConSig exts dataCon
 pprTyThingHdr exts (ATyCon tyCon)     = pprTyConHdr   exts tyCon
 pprTyThingHdr exts (AClass cls)       = pprClassHdr   exts cls
         
-pprTyConHdr exts tyCon =
-  ptext keyword <+> ppr_bndr tyCon <+> hsep (map ppr vars)
+pprTyConHdr exts tyCon
+  | Just (fam_tc, tys) <- tyConFamInst_maybe tyCon
+  = ptext keyword <+> ptext SLIT("instance") <+> pprTypeApp (ppr_bndr tyCon) tys
+  | otherwise
+  = ptext keyword <+> opt_family <+> ppr_bndr tyCon <+> hsep (map ppr vars)
   where
     vars | GHC.isPrimTyCon tyCon || 
           GHC.isFunTyCon tyCon = take (GHC.tyConArity tyCon) GHC.alphaTyVars
@@ -75,6 +81,10 @@ pprTyConHdr exts tyCon =
             | GHC.isNewTyCon tyCon = SLIT("newtype")
             | otherwise            = SLIT("data")
 
+    opt_family
+      | GHC.isOpenTyCon tyCon = ptext SLIT("family")
+      | otherwise             = empty
+
 pprDataConSig exts dataCon =
   ppr_bndr dataCon <+> dcolon <+> pprType exts (GHC.dataConType dataCon)
 
@@ -107,8 +117,12 @@ pprType False ty = ppr (GHC.dropForAlls ty)
 
 pprTyCon exts tyCon
   | GHC.isSynTyCon tyCon
-  = let rhs_type = GHC.synTyConRhs tyCon
-    in hang (pprTyConHdr exts tyCon <+> equals) 2 (pprType exts rhs_type)
+  = if GHC.isOpenTyCon tyCon
+    then pprTyConHdr exts tyCon <+> dcolon <+> 
+        pprType exts (GHC.synTyConResKind tyCon)
+    else 
+      let rhs_type = GHC.synTyConType tyCon
+      in hang (pprTyConHdr exts tyCon <+> equals) 2 (pprType exts rhs_type)
   | otherwise
   = pprAlgTyCon exts tyCon (const True) (const True)
 
@@ -133,7 +147,8 @@ pprDataConDecl exts gadt_style show_label dataCon
   | otherwise      = ppr_bndr dataCon <+> dcolon <+> 
                        sep [ ppr_tvs, GHC.pprThetaArrow theta, pp_tau ]
   where
-    (tyvars, theta, argTypes, tyCon, res_tys) = GHC.dataConSig dataCon
+    (tyvars, theta, argTypes, res_ty) = GHC.dataConSig dataCon
+    tyCon = GHC.dataConTyCon dataCon
     labels = GHC.dataConFieldLabels dataCon
     qualVars = filter (flip notElem (GHC.tyConTyVars tyCon)) tyvars
     stricts = GHC.dataConStrictMarks dataCon
@@ -145,8 +160,7 @@ pprDataConDecl exts gadt_style show_label dataCon
                                hsep (map ppr qualVars) <> dot
 
        -- printing out the dataCon as a type signature, in GADT style
-    pp_tau = foldr add pp_res_ty tys_w_strs
-    pp_res_ty = ppr_bndr tyCon <+> hsep (map GHC.pprParendType res_tys)
+    pp_tau = foldr add (ppr res_ty) tys_w_strs
     add (str,ty) pp_ty = pprBangTy str ty <+> arrow <+> pp_ty
 
     pprParendBangTy (strict,ty)
@@ -214,7 +228,7 @@ add_bars (c:cs)  = sep ((equals <+> c) : map (char '|' <+>) cs)
 ppr_bndr :: GHC.NamedThing a => a -> SDoc
 ppr_bndr a = GHC.pprParenSymName a
 
-showWithLoc :: SrcLoc -> SDoc -> SDoc
+showWithLoc :: SrcSpan -> SDoc -> SDoc
 showWithLoc loc doc 
     = hang doc 2 (char '\t' <> comment <+> GHC.pprDefnLoc loc)
                -- The tab tries to make them line up a bit