[project @ 2002-05-27 15:28:07 by simonpj]
[ghc-hetmet.git] / ghc / compiler / basicTypes / BasicTypes.lhs
index 820a3b9..62a68a9 100644 (file)
@@ -21,7 +21,11 @@ module BasicTypes(
        Unused, unused,
 
        Fixity(..), FixityDirection(..),
-       defaultFixity, maxPrecedence, negateFixity, negatePrecedence,
+       defaultFixity, maxPrecedence, 
+       arrowFixity, negateFixity, negatePrecedence,
+       compareFixity,
+
+       IPName(..), ipNameName, mapIPName,
 
        NewOrData(..), 
 
@@ -31,12 +35,18 @@ module BasicTypes(
 
        Boxity(..), isBoxed, tupleParens,
 
-       OccInfo(..), seqOccInfo, isFragileOcc, isDeadOcc, isLoopBreaker,
+       OccInfo(..), seqOccInfo, isFragileOcc, isOneOcc, 
+       isDeadOcc, isLoopBreaker,
 
        InsideLam, insideLam, notInsideLam,
        OneBranch, oneBranch, notOneBranch,
 
-        EP(..)
+        EP(..),
+
+       StrictnessMark(..), isMarkedUnboxed, isMarkedStrict,
+
+       CompilerPhase, 
+       Activation(..), isActive, isNeverActive, isAlwaysActive
    ) where
 
 #include "HsVersions.h"
@@ -95,6 +105,33 @@ initialVersion = 1
 
 %************************************************************************
 %*                                                                     *
+\subsection{Implicit parameter identity}
+%*                                                                     *
+%************************************************************************
+
+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
+  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
+
+mapIPName :: (a->b) -> IPName a -> IPName b
+mapIPName f (Dupable n) = Dupable (f n)
+mapIPName f (Linear  n) = Linear  (f n)
+\end{code}
+
+               
+%************************************************************************
+%*                                                                     *
 \subsection[Fixity]{Fixity info}
 %*                                                                     *
 %************************************************************************
@@ -121,10 +158,39 @@ defaultFixity = Fixity maxPrecedence InfixL
 negateFixity :: Fixity
 negateFixity     = Fixity negatePrecedence InfixL      -- Precedence of unary negate is wired in as infixl 6!
 
+arrowFixity :: Fixity  -- Fixity of '->' in types
+arrowFixity = Fixity 0 InfixR
+
 negatePrecedence :: Int
 negatePrecedence = 6
 \end{code}
 
+Consider
+
+\begin{verbatim}
+       a `op1` b `op2` c
+\end{verbatim}
+@(compareFixity op1 op2)@ tells which way to arrange appication, or
+whether there's an error.
+
+\begin{code}
+compareFixity :: Fixity -> Fixity
+             -> (Bool,         -- Error please
+                 Bool)         -- Associate to the right: a op1 (b op2 c)
+compareFixity (Fixity prec1 dir1) (Fixity prec2 dir2)
+  = case prec1 `compare` prec2 of
+       GT -> left
+       LT -> right
+       EQ -> case (dir1, dir2) of
+                       (InfixR, InfixR) -> right
+                       (InfixL, InfixL) -> left
+                       _                -> error_please
+  where
+    right       = (False, True)
+    left         = (False, False)
+    error_please = (True,  False)
+\end{code}
+
 
 %************************************************************************
 %*                                                                     *
@@ -139,6 +205,7 @@ data NewOrData
   deriving( Eq )       -- Needed because Demand derives Eq
 \end{code}
 
+
 %************************************************************************
 %*                                                                     *
 \subsection[Top-level/local]{Top-level/not-top level flag}
@@ -285,9 +352,12 @@ isDeadOcc :: OccInfo -> Bool
 isDeadOcc IAmDead = True
 isDeadOcc other          = False
 
+isOneOcc (OneOcc _ _) = True
+isOneOcc other       = False
+
 isFragileOcc :: OccInfo -> Bool
 isFragileOcc (OneOcc _ _) = True
-isFragileOcc other           = False
+isFragileOcc other       = False
 \end{code}
 
 \begin{code}
@@ -304,3 +374,72 @@ instance Show OccInfo where
   showsPrec p occ = showsPrecSDoc p (ppr occ)
 \end{code}
 
+%************************************************************************
+%*                                                                     *
+\subsection{Strictness indication}
+%*                                                                     *
+%************************************************************************
+
+The strictness annotations on types in data type declarations
+e.g.   data T = MkT !Int !(Bool,Bool)
+
+\begin{code}
+data StrictnessMark
+   = MarkedUserStrict  -- "!"  in a source decl
+   | MarkedStrict      -- "!"  in an interface decl: strict but not unboxed
+   | MarkedUnboxed     -- "!!" in an interface decl: unboxed 
+   | NotMarkedStrict   -- No annotation at all
+   deriving( Eq )
+
+isMarkedUnboxed MarkedUnboxed = True
+isMarkedUnboxed other        = False
+
+isMarkedStrict NotMarkedStrict = False
+isMarkedStrict other          = True   -- All others are strict
+
+instance Outputable StrictnessMark where
+  ppr MarkedUserStrict = ptext SLIT("!u")
+  ppr MarkedStrict     = ptext SLIT("!")
+  ppr MarkedUnboxed    = ptext SLIT("! !")
+  ppr NotMarkedStrict  = empty
+\end{code}
+
+
+%************************************************************************
+%*                                                                     *
+\subsection{Activation}
+%*                                                                     *
+%************************************************************************
+
+When a rule or inlining is active
+
+\begin{code}
+type CompilerPhase = Int       -- Compilation phase
+                               -- Phases decrease towards zero
+                               -- Zero is the last phase
+
+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
+
+instance Outputable Activation where
+   ppr AlwaysActive     = empty                -- The default
+   ppr (ActiveBefore n) = brackets (char '~' <> int n)
+   ppr (ActiveAfter n)  = brackets (int n)
+   ppr NeverActive      = ptext SLIT("NEVER")
+    
+isActive :: CompilerPhase -> Activation -> Bool
+isActive p NeverActive      = False
+isActive p AlwaysActive     = True
+isActive p (ActiveAfter n)  = p <= n
+isActive p (ActiveBefore n) = p >  n
+
+isNeverActive, isAlwaysActive :: Activation -> Bool
+isNeverActive NeverActive = True
+isNeverActive act        = False
+
+isAlwaysActive AlwaysActive = True
+isAlwaysActive other       = False
+\end{code}