[project @ 2002-03-29 21:39:36 by sof]
[ghc-hetmet.git] / ghc / compiler / hsSyn / HsBinds.lhs
index d30ff27..b5456d2 100644 (file)
@@ -24,7 +24,7 @@ import PprCore                ( {- instance Outputable (Expr a) -} )
 import Name            ( Name )
 import PrelNames       ( isUnboundName )
 import NameSet         ( NameSet, elemNameSet, nameSetToList )
-import BasicTypes      ( RecFlag(..), Fixity, Activation(..), pprPhase )
+import BasicTypes      ( RecFlag(..), Fixity, Activation(..) )
 import Outputable      
 import SrcLoc          ( SrcLoc )
 import Var             ( TyVar )
@@ -109,6 +109,10 @@ data MonoBinds id pat
                                -- and variables                f = \x -> e
                                -- Reason: the Match stuff lets us have an optional
                                --         result type sig      f :: a->a = ...mentions a...
+                               --
+                               -- This also means that instance decls can only have
+                               -- FunMonoBinds, so if you change this, you'll need to
+                               -- change e.g. rnMethodBinds
                    Bool                -- True => infix declaration
                    [Match id pat]
                    SrcLoc
@@ -331,12 +335,9 @@ ppr_sig (Sig var ty _)
       = sep [ppr var <+> dcolon, nest 4 (ppr ty)]
 
 ppr_sig (ClassOpSig var dm ty _)
-      = getPprStyle $ \ sty ->
-        if ifaceStyle sty 
-          then sep [ ppr var <+> pp_dm <+> dcolon, nest 4 (ppr ty) ]
-          else sep [ ppr_var var <+> dcolon, 
-                     nest 4 (ppr ty),
-                     nest 4 (pp_dm_comment) ]
+      = sep [ ppr_var var <+> dcolon, 
+             nest 4 (ppr ty),
+             nest 4 (pp_dm_comment) ]
       where
        pp_dm = case dm of 
                  DefMeth _  -> equals  -- Default method indicator
@@ -356,11 +357,7 @@ ppr_sig (InlineSig True var phase _)
       = hsep [text "{-# INLINE", ppr phase, ppr var, text "#-}"]
 
 ppr_sig (InlineSig False var phase _)
-      = hsep [text "{-# NOINLINE", pp_phase phase, ppr var, text "#-}"]
-      where
-       pp_phase NeverActive     = empty                -- NOINLINE f
-       pp_phase (ActiveAfter n) = pprPhase n           -- NOINLINE [2] f
-       pp_phase AlwaysActive    = text "ALWAYS?"       -- Unexpected
+      = hsep [text "{-# NOINLINE", ppr phase, ppr var, text "#-}"]
 
 ppr_sig (SpecInstSig ty _)
       = hsep [text "{-# SPECIALIZE instance", ppr ty, text "#-}"]