Don't import FastString in HsVersions.h
[ghc-hetmet.git] / compiler / basicTypes / BasicTypes.lhs
index ab6d463..d60321a 100644 (file)
@@ -1,4 +1,5 @@
 %
+% (c) The University of Glasgow 2006
 % (c) The GRASP/AQUA Project, Glasgow University, 1997-1998
 %
 \section[BasicTypes]{Miscellanous types}
@@ -38,7 +39,7 @@ module BasicTypes(
        TupCon(..), tupleParens,
 
        OccInfo(..), seqOccInfo, isFragileOcc, isOneOcc, 
-       isDeadOcc, isLoopBreaker, isNoOcc,
+       isDeadOcc, isLoopBreaker, isNonRuleLoopBreaker, isNoOcc,
 
        InsideLam, insideLam, notInsideLam,
        OneBranch, oneBranch, notOneBranch,
@@ -57,7 +58,7 @@ module BasicTypes(
 
 #include "HsVersions.h"
 
-import FastString( FastString )
+import FastString
 import Outputable
 \end{code}
 
@@ -109,24 +110,18 @@ The @IPName@ type is here because it is used in TypeRep (i.e. very
 early in the hierarchy), but also in HsSyn.
 
 \begin{code}
-data IPName name
-  = Dupable   name     -- ?x: you can freely duplicate this implicit parameter
-  | Linear name                -- %x: you must use the splitting function to duplicate it
+newtype IPName name = IPName name      -- ?x
   deriving( Eq, Ord )  -- Ord is used in the IP name cache finite map
                        --      (used in HscTypes.OrigIParamCache)
 
-
 ipNameName :: IPName name -> name
-ipNameName (Dupable n) = n
-ipNameName (Linear  n) = n
+ipNameName (IPName n) = n
 
 mapIPName :: (a->b) -> IPName a -> IPName b
-mapIPName f (Dupable n) = Dupable (f n)
-mapIPName f (Linear  n) = Linear  (f n)
+mapIPName f (IPName n) = IPName (f n)
 
 instance Outputable name => Outputable (IPName name) where
-    ppr (Dupable n) = char '?' <> ppr n -- Ordinary implicit parameters
-    ppr (Linear  n) = char '%' <> ppr n -- Splittable implicit parameters
+    ppr (IPName n) = char '?' <> ppr n -- Ordinary implicit parameters
 \end{code}
 
 
@@ -156,7 +151,9 @@ instance Outputable FixityDirection where
     ppr InfixN = ptext SLIT("infix")
 
 ------------------------
-maxPrecedence = (9::Int)
+maxPrecedence :: Int
+maxPrecedence = 9
+defaultFixity :: Fixity
 defaultFixity = Fixity maxPrecedence InfixL
 
 negateFixity, funTyFixity :: Fixity
@@ -241,7 +238,7 @@ isBoxed Unboxed = False
 %*                                                                     *
 %************************************************************************
 
-\begin{code} 
+\begin{code}
 data RecFlag = Recursive 
             | NonRecursive
             deriving( Eq )
@@ -295,6 +292,7 @@ data OverlapFlag
                -- Without the Incoherent flag, we'd complain that
                -- instantiating 'b' would change which instance 
                -- was chosen
+  deriving( Eq )
 
 instance Outputable OverlapFlag where
    ppr NoOverlap  = empty
@@ -370,21 +368,29 @@ defn of OccInfo here, safely at the bottom
 
 \begin{code}
 data OccInfo 
-  = NoOccInfo
+  = NoOccInfo          -- Many occurrences, or unknown
 
   | IAmDead            -- Marks unused variables.  Sometimes useful for
                        -- lambda and case-bound variables.
 
-  | OneOcc !InsideLam
-          !OneBranch
-          !InterestingCxt
+  | OneOcc             -- Occurs exactly once, not inside a rule
+       !InsideLam
+       !OneBranch
+       !InterestingCxt
 
   | IAmALoopBreaker    -- Used by the occurrence analyser to mark loop-breakers
                        -- in a group of recursive definitions
+       !RulesOnly      -- True <=> This is a weak or rules-only loop breaker
+                       --  See OccurAnal Note [Weak loop breakers]
+
+type RulesOnly = Bool
+\end{code}
+
 
+\begin{code}
 isNoOcc :: OccInfo -> Bool
 isNoOcc NoOccInfo = True
-isNoOcc other     = False
+isNoOcc _         = False
 
 seqOccInfo :: OccInfo -> ()
 seqOccInfo occ = occ `seq` ()
@@ -398,37 +404,44 @@ type InterestingCxt = Bool        -- True <=> Function: is applied
 type InsideLam = Bool  -- True <=> Occurs inside a non-linear lambda
                        -- Substituting a redex for this occurrence is
                        -- dangerous because it might duplicate work.
+insideLam, notInsideLam :: InsideLam
 insideLam    = True
 notInsideLam = False
 
 -----------------
 type OneBranch = Bool  -- True <=> Occurs in only one case branch
                        --      so no code-duplication issue to worry about
+oneBranch, notOneBranch :: OneBranch
 oneBranch    = True
 notOneBranch = False
 
 isLoopBreaker :: OccInfo -> Bool
-isLoopBreaker IAmALoopBreaker = True
-isLoopBreaker other          = False
+isLoopBreaker (IAmALoopBreaker _) = True
+isLoopBreaker _                   = False
+
+isNonRuleLoopBreaker :: OccInfo -> Bool
+isNonRuleLoopBreaker (IAmALoopBreaker False) = True   -- Loop-breaker that breaks a non-rule cycle
+isNonRuleLoopBreaker _                       = False
 
 isDeadOcc :: OccInfo -> Bool
 isDeadOcc IAmDead = True
-isDeadOcc other          = False
+isDeadOcc _       = False
 
+isOneOcc :: OccInfo -> Bool
 isOneOcc (OneOcc _ _ _) = True
-isOneOcc other         = False
+isOneOcc _              = False
 
 isFragileOcc :: OccInfo -> Bool
 isFragileOcc (OneOcc _ _ _) = True
-isFragileOcc other         = False
+isFragileOcc _              = False
 \end{code}
 
 \begin{code}
 instance Outputable OccInfo where
   -- only used for debugging; never parsed.  KSW 1999-07
-  ppr NoOccInfo                                  = empty
-  ppr IAmALoopBreaker                            = ptext SLIT("LoopBreaker")
-  ppr IAmDead                                    = ptext SLIT("Dead")
+  ppr NoOccInfo           = empty
+  ppr (IAmALoopBreaker ro) = ptext SLIT("LoopBreaker") <> if ro then char '!' else empty
+  ppr IAmDead             = ptext SLIT("Dead")
   ppr (OneOcc inside_lam one_branch int_cxt)
        = ptext SLIT("Once") <> pp_lam <> pp_br <> pp_args
        where
@@ -459,11 +472,13 @@ data StrictnessMark       -- Used in interface decls only
    | NotMarkedStrict   
    deriving( Eq )
 
+isMarkedUnboxed :: StrictnessMark -> Bool
 isMarkedUnboxed MarkedUnboxed = True
-isMarkedUnboxed other        = False
+isMarkedUnboxed _             = False
 
+isMarkedStrict :: StrictnessMark -> Bool
 isMarkedStrict NotMarkedStrict = False
-isMarkedStrict other          = True   -- All others are strict
+isMarkedStrict _               = True   -- All others are strict
 
 instance Outputable StrictnessMark where
   ppr MarkedStrict     = ptext SLIT("!")
@@ -481,6 +496,10 @@ instance Outputable StrictnessMark where
 \begin{code}
 data SuccessFlag = Succeeded | Failed
 
+instance Outputable SuccessFlag where
+    ppr Succeeded = ptext SLIT("Succeeded")
+    ppr Failed    = ptext SLIT("Failed")
+
 successIf :: Bool -> SuccessFlag
 successIf True  = Succeeded
 successIf False = Failed
@@ -520,31 +539,40 @@ data InlineSpec
                        --          is enabled, it will definitely actually happen
   deriving( Eq )
 
+defaultInlineSpec, alwaysInlineSpec, neverInlineSpec :: InlineSpec
+
 defaultInlineSpec = Inline AlwaysActive False  -- Inlining is OK, but not forced
 alwaysInlineSpec  = Inline AlwaysActive True   -- INLINE always
 neverInlineSpec   = Inline NeverActive  False  -- NOINLINE 
 
 instance Outputable Activation where
-   ppr AlwaysActive     = empty                -- The default
+   ppr NeverActive      = ptext SLIT("NEVER")
+   ppr AlwaysActive     = ptext SLIT("ALWAYS")
    ppr (ActiveBefore n) = brackets (char '~' <> int n)
    ppr (ActiveAfter n)  = brackets (int n)
-   ppr NeverActive      = ptext SLIT("NEVER")
     
 instance Outputable InlineSpec where
-   ppr (Inline act True)  = ptext SLIT("INLINE") <> ppr act
-   ppr (Inline act False) = ptext SLIT("NOINLINE") <> ppr act
+   ppr (Inline act is_inline)  
+       | is_inline = ptext SLIT("INLINE")
+                     <> case act of
+                           AlwaysActive -> empty
+                           _            -> ppr act
+       | otherwise = ptext SLIT("NOINLINE")
+                     <> case act of
+                           NeverActive  -> empty
+                           _            -> ppr act
 
 isActive :: CompilerPhase -> Activation -> Bool
-isActive p NeverActive      = False
-isActive p AlwaysActive     = True
+isActive _ NeverActive      = False
+isActive _ AlwaysActive     = True
 isActive p (ActiveAfter n)  = p <= n
 isActive p (ActiveBefore n) = p >  n
 
 isNeverActive, isAlwaysActive :: Activation -> Bool
 isNeverActive NeverActive = True
-isNeverActive act        = False
+isNeverActive _           = False
 
 isAlwaysActive AlwaysActive = True
-isAlwaysActive other       = False
+isAlwaysActive _            = False
 \end{code}