[project @ 2000-11-01 17:15:28 by simonpj]
[ghc-hetmet.git] / ghc / compiler / basicTypes / BasicTypes.lhs
index ded171f..820a3b9 100644 (file)
@@ -14,13 +14,29 @@ types that
 
 \begin{code}
 module BasicTypes(
-       Version, Arity, 
+       Version, bumpVersion, initialVersion, bogusVersion,
+
+       Arity, 
+
        Unused, unused,
+
        Fixity(..), FixityDirection(..),
        defaultFixity, maxPrecedence, negateFixity, negatePrecedence,
+
        NewOrData(..), 
+
        RecFlag(..), isRec, isNonRec,
-       TopLevelFlag(..), isTopLevel, isNotTopLevel
+
+       TopLevelFlag(..), isTopLevel, isNotTopLevel,
+
+       Boxity(..), isBoxed, tupleParens,
+
+       OccInfo(..), seqOccInfo, isFragileOcc, isDeadOcc, isLoopBreaker,
+
+       InsideLam, insideLam, notInsideLam,
+       OneBranch, oneBranch, notOneBranch,
+
+        EP(..)
    ) where
 
 #include "HsVersions.h"
@@ -63,6 +79,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}
 
 
@@ -109,7 +136,6 @@ 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}
 
@@ -135,6 +161,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}
 %*                                                                     *
 %************************************************************************
@@ -151,3 +199,108 @@ isNonRec :: RecFlag -> Bool
 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.
+
+
+%************************************************************************
+%*                                                                     *
+\subsection{Occurrence information}
+%*                                                                     *
+%************************************************************************
+
+This data type is used exclusively by the simplifier, but it appears in a
+SubstResult, which is currently defined in VarEnv, which is pretty near
+the base of the module hierarchy.  So it seemed simpler to put the
+defn of OccInfo here, safely at the bottom
+
+\begin{code}
+data OccInfo 
+  = NoOccInfo
+
+  | IAmDead            -- Marks unused variables.  Sometimes useful for
+                       -- lambda and case-bound variables.
+
+  | OneOcc InsideLam
+
+          OneBranch
+
+  | IAmALoopBreaker    -- Used by the occurrence analyser to mark loop-breakers
+                       -- in a group of recursive definitions
+
+seqOccInfo :: OccInfo -> ()
+seqOccInfo (OneOcc in_lam once) = in_lam `seq` once `seq` ()
+seqOccInfo occ                 = ()
+
+type InsideLam = Bool  -- True <=> Occurs inside a non-linear lambda
+                       -- Substituting a redex for this occurrence is
+                       -- dangerous because it might duplicate work.
+insideLam    = True
+notInsideLam = False
+
+type OneBranch = Bool  -- True <=> Occurs in only one case branch
+                       --      so no code-duplication issue to worry about
+oneBranch    = True
+notOneBranch = 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}
+instance Outputable OccInfo where
+  -- only used for debugging; never parsed.  KSW 1999-07
+  ppr NoOccInfo                                  = empty
+  ppr IAmALoopBreaker                            = ptext SLIT("_Kx")
+  ppr IAmDead                                    = ptext SLIT("_Kd")
+  ppr (OneOcc inside_lam one_branch) | inside_lam = ptext SLIT("_Kl")
+                                    | one_branch = ptext SLIT("_Ks")
+                                    | otherwise  = ptext SLIT("_Ks*")
+
+instance Show OccInfo where
+  showsPrec p occ = showsPrecSDoc p (ppr occ)
+\end{code}
+