[project @ 2001-11-27 10:03:36 by simonpj]
[ghc-hetmet.git] / ghc / compiler / basicTypes / BasicTypes.lhs
index 47ad787..35522d3 100644 (file)
@@ -14,7 +14,7 @@ types that
 
 \begin{code}
 module BasicTypes(
-       Version,
+       Version, bumpVersion, initialVersion, bogusVersion,
 
        Arity, 
 
@@ -29,10 +29,19 @@ module BasicTypes(
 
        TopLevelFlag(..), isTopLevel, isNotTopLevel,
 
-       OccInfo(..), seqOccInfo, isFragileOccInfo,
+       Boxity(..), isBoxed, tupleParens,
+
+       OccInfo(..), seqOccInfo, isFragileOcc, isDeadOcc, isLoopBreaker,
+
        InsideLam, insideLam, notInsideLam,
-       OneBranch, oneBranch, notOneBranch
+       OneBranch, oneBranch, notOneBranch,
+
+        EP(..),
+
+       StrictnessMark(..), isMarkedUnboxed, isMarkedStrict,
 
+       CompilerPhase, pprPhase, 
+       Activation(..), isActive, isNeverActive, isAlwaysActive
    ) where
 
 #include "HsVersions.h"
@@ -75,6 +84,17 @@ type Arity = Int
 
 \begin{code}
 type Version = Int
+
+bogusVersion :: Version        -- Shouldn't look at these
+bogusVersion = error "bogusVersion"
+
+bumpVersion :: Bool -> Version -> Version 
+-- Bump if the predicate (typically equality between old and new) is false
+bumpVersion False v = v+1
+bumpVersion True  v = v
+
+initialVersion :: Version
+initialVersion = 1
 \end{code}
 
 
@@ -121,10 +141,10 @@ negatePrecedence = 6
 data NewOrData
   = NewType    -- "newtype Blah ..."
   | DataType   -- "data Blah ..."
-  | EnumType   -- Enumeration; all constructors are nullary
   deriving( Eq )       -- Needed because Demand derives Eq
 \end{code}
 
+
 %************************************************************************
 %*                                                                     *
 \subsection[Top-level/local]{Top-level/not-top level flag}
@@ -147,6 +167,28 @@ isTopLevel NotTopLevel  = False
 
 %************************************************************************
 %*                                                                     *
+\subsection[Top-level/local]{Top-level/not-top level flag}
+%*                                                                     *
+%************************************************************************
+
+\begin{code}
+data Boxity
+  = Boxed
+  | Unboxed
+  deriving( Eq )
+
+isBoxed :: Boxity -> Bool
+isBoxed Boxed   = True
+isBoxed Unboxed = False
+
+tupleParens :: Boxity -> SDoc -> SDoc
+tupleParens Boxed   p = parens p
+tupleParens Unboxed p = ptext SLIT("(#") <+> p <+> ptext SLIT("#)")
+\end{code}
+
+
+%************************************************************************
+%*                                                                     *
 \subsection[Recursive/Non-Recursive]{Recursive/Non-Recursive flag}
 %*                                                                     *
 %************************************************************************
@@ -164,6 +206,42 @@ isNonRec Recursive    = False
 isNonRec NonRecursive = True
 \end{code}
 
+%************************************************************************
+%*                                                                     *
+\subsection[Generic]{Generic flag}
+%*                                                                     *
+%************************************************************************
+
+This is the "Embedding-Projection pair" datatype, it contains 
+two pieces of code (normally either RenamedHsExpr's or Id's)
+If we have a such a pair (EP from to), the idea is that 'from' and 'to'
+represents functions of type 
+
+       from :: T -> Tring
+       to   :: Tring -> T
+
+And we should have 
+
+       to (from x) = x
+
+T and Tring are arbitrary, but typically T is the 'main' type while
+Tring is the 'representation' type.  (This just helps us remember 
+whether to use 'from' or 'to'.
+
+\begin{code}
+data EP a = EP { fromEP :: a,  -- :: T -> Tring
+                toEP   :: a }  -- :: Tring -> T
+\end{code}
+
+Embedding-projection pairs are used in several places:
+
+First of all, each type constructor has an EP associated with it, the
+code in EP converts (datatype T) from T to Tring and back again.
+
+Secondly, when we are filling in Generic methods (in the typechecker, 
+tcMethodBinds), we are constructing bimaps by induction on the structure
+of the type of the method signature.
+
 
 %************************************************************************
 %*                                                                     *
@@ -205,9 +283,17 @@ type OneBranch = Bool      -- True <=> Occurs in only one case branch
 oneBranch    = True
 notOneBranch = False
 
-isFragileOccInfo :: OccInfo -> Bool
-isFragileOccInfo (OneOcc _ _) = True
-isFragileOccInfo other       = False
+isLoopBreaker :: OccInfo -> Bool
+isLoopBreaker IAmALoopBreaker = True
+isLoopBreaker other          = False
+
+isDeadOcc :: OccInfo -> Bool
+isDeadOcc IAmDead = True
+isDeadOcc other          = False
+
+isFragileOcc :: OccInfo -> Bool
+isFragileOcc (OneOcc _ _) = True
+isFragileOcc other       = False
 \end{code}
 
 \begin{code}
@@ -224,3 +310,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
+
+pprPhase :: CompilerPhase -> SDoc
+pprPhase n = brackets (int n)
+
+data Activation = NeverActive
+               | AlwaysActive
+               | 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 (ActiveAfter n) = pprPhase n
+   ppr NeverActive     = ptext SLIT("NEVER")
+    
+isActive :: CompilerPhase -> Activation -> Bool
+isActive p NeverActive     = False
+isActive p AlwaysActive    = True
+isActive p (ActiveAfter n) = p <= n
+
+isNeverActive, isAlwaysActive :: Activation -> Bool
+isNeverActive NeverActive = True
+isNeverActive act        = False
+
+isAlwaysActive AlwaysActive = True
+isAlwaysActive other       = False
+\end{code}