Refactor (again) the handling of default methods
[ghc-hetmet.git] / compiler / basicTypes / BasicTypes.lhs
index 849d507..022a8fc 100644 (file)
@@ -14,12 +14,14 @@ types that
 \end{itemize}
 
 \begin{code}
+{-# LANGUAGE DeriveDataTypeable #-}
+
 module BasicTypes(
        Version, bumpVersion, initialVersion,
 
        Arity, 
 
-    FunctionOrData(..),
+        FunctionOrData(..),
        
        WarningTxt(..),
 
@@ -52,13 +54,16 @@ module BasicTypes(
 
         EP(..),
 
-       StrictnessMark(..), isMarkedUnboxed, isMarkedStrict,
+       HsBang(..), isBanged, isMarkedUnboxed, 
+        StrictnessMark(..), isMarkedStrict,
+
+       DefMethSpec(..),
 
        CompilerPhase, 
        Activation(..), isActive, isNeverActive, isAlwaysActive, isEarlyActive,
         RuleMatchInfo(..), isConLike, isFunLike, 
-        InlinePragma(..), defaultInlinePragma, neverInlinePragma, dfunInlinePragma,
-       isDefaultInlinePragma, isInlinePragma,
+        InlinePragma(..), defaultInlinePragma, alwaysInlinePragma, neverInlinePragma, dfunInlinePragma,
+       isDefaultInlinePragma, isInlinePragma, inlinePragmaSat,
         inlinePragmaActivation, inlinePragmaRuleMatchInfo,
         setInlinePragmaActivation, setInlinePragmaRuleMatchInfo,
 
@@ -67,6 +72,8 @@ module BasicTypes(
 
 import FastString
 import Outputable
+
+import Data.Data hiding (Fixity)
 \end{code}
 
 %************************************************************************
@@ -87,7 +94,7 @@ type Arity = Int
 
 \begin{code}
 data FunctionOrData = IsFunction | IsData
-    deriving (Eq, Ord)
+    deriving (Eq, Ord, Data, Typeable)
 
 instance Outputable FunctionOrData where
     ppr IsFunction = text "(function)"
@@ -122,7 +129,7 @@ initialVersion = 1
 -- reason/explanation from a WARNING or DEPRECATED pragma
 data WarningTxt = WarningTxt [FastString]
                 | DeprecatedTxt [FastString]
-    deriving Eq
+    deriving (Eq, Data, Typeable)
 
 instance Outputable WarningTxt where
     ppr (WarningTxt    ws) = doubleQuotes (vcat (map ftext ws))
@@ -141,8 +148,9 @@ early in the hierarchy), but also in HsSyn.
 
 \begin{code}
 newtype IPName name = IPName name      -- ?x
-  deriving( Eq, Ord )  -- Ord is used in the IP name cache finite map
-                       --      (used in HscTypes.OrigIParamCache)
+  deriving( Eq, Ord, Data, Typeable )
+  -- Ord is used in the IP name cache finite map
+  -- (used in HscTypes.OrigIParamCache)
 
 ipNameName :: IPName name -> name
 ipNameName (IPName n) = n
@@ -173,6 +181,7 @@ type RuleName = FastString
 \begin{code}
 ------------------------
 data Fixity = Fixity Int FixityDirection
+  deriving (Data, Typeable)
 
 instance Outputable Fixity where
     ppr (Fixity prec dir) = hcat [ppr dir, space, int prec]
@@ -182,7 +191,7 @@ instance Eq Fixity where            -- Used to determine if two fixities conflict
 
 ------------------------
 data FixityDirection = InfixL | InfixR | InfixN 
-                    deriving(Eq)
+                    deriving (Eq, Data, Typeable)
 
 instance Outputable FixityDirection where
     ppr InfixL = ptext (sLit "infixl")
@@ -263,7 +272,7 @@ instance Outputable TopLevelFlag where
 data Boxity
   = Boxed
   | Unboxed
-  deriving( Eq )
+  deriving( Eq, Data, Typeable )
 
 isBoxed :: Boxity -> Bool
 isBoxed Boxed   = True
@@ -280,7 +289,7 @@ isBoxed Unboxed = False
 \begin{code}
 data RecFlag = Recursive 
             | NonRecursive
-            deriving( Eq )
+            deriving( Eq, Data, Typeable )
 
 isRec :: RecFlag -> Bool
 isRec Recursive    = True
@@ -515,7 +524,7 @@ instance Show OccInfo where
 
 %************************************************************************
 %*                                                                     *
-\subsection{Strictness indication}
+               Strictness indication
 %*                                                                     *
 %************************************************************************
 
@@ -523,29 +532,73 @@ The strictness annotations on types in data type declarations
 e.g.   data T = MkT !Int !(Bool,Bool)
 
 \begin{code}
-data StrictnessMark    -- Used in interface decls only
-   = MarkedStrict      
-   | MarkedUnboxed     
-   | NotMarkedStrict   
-   deriving( Eq )
+-------------------------
+-- HsBang describes what the *programmer* wrote
+-- This info is retained in the DataCon.dcStrictMarks field
+data HsBang = HsNoBang 
 
-isMarkedUnboxed :: StrictnessMark -> Bool
-isMarkedUnboxed MarkedUnboxed = True
-isMarkedUnboxed _             = False
+           | HsStrict  
 
-isMarkedStrict :: StrictnessMark -> Bool
-isMarkedStrict NotMarkedStrict = False
-isMarkedStrict _               = True   -- All others are strict
+           | HsUnpack         -- {-# UNPACK #-} ! (GHC extension, meaning "unbox")
+
+           | HsUnpackFailed   -- An UNPACK pragma that we could not make 
+                              -- use of, because the type isn't unboxable; 
+                               -- equivalant to HsStrict except for checkValidDataCon
+  deriving (Eq, Data, Typeable)
+
+instance Outputable HsBang where
+    ppr HsNoBang       = empty
+    ppr HsStrict       = char '!'
+    ppr HsUnpack       = ptext (sLit "{-# UNPACK #-} !")
+    ppr HsUnpackFailed = ptext (sLit "{-# UNPACK (failed) #-} !")
+
+isBanged :: HsBang -> Bool
+isBanged HsNoBang = False
+isBanged _        = True
+
+isMarkedUnboxed :: HsBang -> Bool
+isMarkedUnboxed HsUnpack = True
+isMarkedUnboxed _        = False
+
+-------------------------
+-- StrictnessMark is internal only, used to indicate strictness 
+-- of the DataCon *worker* fields
+data StrictnessMark = MarkedStrict | NotMarkedStrict   
 
 instance Outputable StrictnessMark where
   ppr MarkedStrict     = ptext (sLit "!")
-  ppr MarkedUnboxed    = ptext (sLit "!!")
-  ppr NotMarkedStrict  = ptext (sLit "_")
+  ppr NotMarkedStrict  = empty
+
+isMarkedStrict :: StrictnessMark -> Bool
+isMarkedStrict NotMarkedStrict = False
+isMarkedStrict _               = True   -- All others are strict
 \end{code}
 
 
 %************************************************************************
 %*                                                                     *
+               Default method specfication
+%*                                                                     *
+%************************************************************************
+
+The DefMethSpec enumeration just indicates what sort of default method
+is used for a class. It is generated from source code, and present in 
+interface files; it is converted to Class.DefMeth before begin put in a 
+Class object.
+
+\begin{code}
+data DefMethSpec = NoDM        -- No default method
+                 | VanillaDM   -- Default method given with polymorphic code
+                 | GenericDM   -- Default method given with generic code
+
+instance Outputable DefMethSpec where
+  ppr NoDM      = empty
+  ppr VanillaDM = ptext (sLit "{- Has default method -}")
+  ppr GenericDM = ptext (sLit "{- Has generic default method -}")
+\end{code}
+
+%************************************************************************
+%*                                                                     *
 \subsection{Success flag}
 %*                                                                     *
 %************************************************************************
@@ -587,19 +640,28 @@ data Activation = NeverActive
                | AlwaysActive
                | ActiveBefore CompilerPhase    -- Active only *before* this phase
                | ActiveAfter CompilerPhase     -- Active in this phase and later
-               deriving( Eq )                  -- Eq used in comparing rules in HsDecls
+               deriving( Eq, Data, Typeable )                  -- Eq used in comparing rules in HsDecls
 
 data RuleMatchInfo = ConLike                   -- See Note [CONLIKE pragma]
                    | FunLike
-                   deriving( Eq )
+                   deriving( Eq, Data, Typeable )
 
 data InlinePragma           -- Note [InlinePragma]
   = InlinePragma
       { inl_inline :: Bool           -- True <=> INLINE, 
                                     -- False <=> no pragma at all, or NOINLINE
+
+      , inl_sat    :: Maybe Arity    -- Just n <=> Inline only when applied to n 
+                                    --            explicit (non-type, non-dictionary) args
+                                    --   That is, inl_sat describes the number of *source-code*
+                                     --   arguments the thing must be applied to.  We add on the 
+                                     --   number of implicit, dictionary arguments when making
+                                    --   the InlineRule, and don't look at inl_sat further
+
       , inl_act    :: Activation     -- Says during which phases inlining is allowed
+
       , inl_rule   :: RuleMatchInfo  -- Should the function be treated like a constructor?
-    } deriving( Eq )
+    } deriving( Eq, Data, Typeable )
 \end{code}
 
 Note [InlinePragma]
@@ -615,6 +677,8 @@ If you write nothing at all, you get defaultInlinePragma:
 It's not possible to get that combination by *writing* something, so 
 if an Id has defaultInlinePragma it means the user didn't specify anything.
 
+If inl_inline = True, then the Id should have an InlineRule unfolding.
+
 Note [CONLIKE pragma]
 ~~~~~~~~~~~~~~~~~~~~~
 The ConLike constructor of a RuleMatchInfo is aimed at the following.
@@ -660,14 +724,22 @@ isFunLike :: RuleMatchInfo -> Bool
 isFunLike FunLike = True
 isFunLike _            = False
 
-defaultInlinePragma, neverInlinePragma, dfunInlinePragma :: InlinePragma
-defaultInlinePragma 
-  = InlinePragma { inl_act = AlwaysActive, inl_rule = FunLike, inl_inline = False }
-neverInlinePragma   
-   = InlinePragma { inl_act = NeverActive, inl_rule = FunLike, inl_inline = False }
-dfunInlinePragma   
-   = InlinePragma { inl_act = AlwaysActive, inl_rule = ConLike, inl_inline = False }
-                                    
+defaultInlinePragma, alwaysInlinePragma, neverInlinePragma, dfunInlinePragma
+  :: InlinePragma
+defaultInlinePragma = InlinePragma { inl_act = AlwaysActive
+                                   , inl_rule = FunLike
+                                   , inl_inline = False
+                                   , inl_sat = Nothing }
+
+alwaysInlinePragma = defaultInlinePragma { inl_inline = True }
+neverInlinePragma  = defaultInlinePragma { inl_act    = NeverActive }
+
+-- A DFun has an always-active inline activation so that 
+-- exprIsConApp_maybe can "see" its unfolding
+-- (However, its actual Unfolding is a DFunUnfolding, which is
+--  never inlined other than via exprIsConApp_maybe.)
+dfunInlinePragma   = defaultInlinePragma { inl_act  = AlwaysActive
+                                         , inl_rule = ConLike }
 
 isDefaultInlinePragma :: InlinePragma -> Bool
 isDefaultInlinePragma (InlinePragma { inl_act = activation
@@ -678,6 +750,9 @@ isDefaultInlinePragma (InlinePragma { inl_act = activation
 isInlinePragma :: InlinePragma -> Bool
 isInlinePragma prag = inl_inline prag
 
+inlinePragmaSat :: InlinePragma -> Maybe Arity
+inlinePragmaSat = inl_sat
+
 inlinePragmaActivation :: InlinePragma -> Activation
 inlinePragmaActivation (InlinePragma { inl_act = activation }) = activation
 
@@ -691,8 +766,8 @@ setInlinePragmaRuleMatchInfo :: InlinePragma -> RuleMatchInfo -> InlinePragma
 setInlinePragmaRuleMatchInfo prag info = prag { inl_rule = info }
 
 instance Outputable Activation where
-   ppr AlwaysActive     = ptext (sLit "ALWAYS")
-   ppr NeverActive      = ptext (sLit "NEVER")
+   ppr AlwaysActive     = brackets (ptext (sLit "ALWAYS"))
+   ppr NeverActive      = brackets (ptext (sLit "NEVER"))
    ppr (ActiveBefore n) = brackets (char '~' <> int n)
    ppr (ActiveAfter n)  = brackets (int n)
 
@@ -701,17 +776,20 @@ instance Outputable RuleMatchInfo where
    ppr FunLike = ptext (sLit "FUNLIKE")
 
 instance Outputable InlinePragma where
-  ppr (InlinePragma { inl_inline = inline, inl_act = activation, inl_rule = info })
-    = pp_inline <+> pp_info <+> pp_activation
+  ppr (InlinePragma { inl_inline = inline, inl_act = activation
+                    , inl_rule = info, inl_sat = mb_arity })
+    = pp_inl_act (inline, activation) <+> pp_sat <+> pp_info 
     where
-      pp_inline | inline    = ptext (sLit "INLINE")
-                | otherwise = ptext (sLit "NOINLINE")
+      pp_inl_act (False, AlwaysActive)  = empty        -- defaultInlinePragma
+      pp_inl_act (False, NeverActive)   = ptext (sLit "NOINLINE")
+      pp_inl_act (False, act)           = ptext (sLit "NOINLINE") <> ppr act
+      pp_inl_act (True,  AlwaysActive)  = ptext (sLit "INLINE")
+      pp_inl_act (True,  act)           = ptext (sLit "INLINE") <> ppr act
+
+      pp_sat | Just ar <- mb_arity = parens (ptext (sLit "sat-args=") <> int ar)
+             | otherwise           = empty
       pp_info | isFunLike info = empty
               | otherwise      = ppr info
-      pp_activation 
-        | inline     && isAlwaysActive activation = empty
-        | not inline && isNeverActive  activation = empty
-        | otherwise                               = ppr activation    
 
 isActive :: CompilerPhase -> Activation -> Bool
 isActive _ NeverActive      = False