[project @ 2005-02-04 17:24:01 by simonpj]
[ghc-hetmet.git] / ghc / compiler / basicTypes / BasicTypes.lhs
index ba6663b..bce1fa0 100644 (file)
@@ -14,24 +14,29 @@ types that
 
 \begin{code}
 module BasicTypes(
-       Version, bumpVersion, initialVersion, bogusVersion,
+       Version, bumpVersion, initialVersion,
 
        Arity, 
-
-       Unused, unused,
+       
+       DeprecTxt,
 
        Fixity(..), FixityDirection(..),
-       defaultFixity, maxPrecedence, negateFixity, negatePrecedence,
+       defaultFixity, maxPrecedence, 
+       negateFixity,
+       compareFixity,
 
-       NewOrData(..), 
+       IPName(..), ipNameName, mapIPName,
 
-       RecFlag(..), isRec, isNonRec,
+       RecFlag(..), isRec, isNonRec, boolToRecFlag,
 
        TopLevelFlag(..), isTopLevel, isNotTopLevel,
 
-       Boxity(..), isBoxed, tupleParens,
+       Boxity(..), isBoxed, 
+
+       TupCon(..), tupleParens,
 
-       OccInfo(..), seqOccInfo, isFragileOcc, isDeadOcc, isLoopBreaker,
+       OccInfo(..), seqOccInfo, isFragileOcc, isOneOcc, 
+       isDeadOcc, isLoopBreaker,
 
        InsideLam, insideLam, notInsideLam,
        OneBranch, oneBranch, notOneBranch,
@@ -40,61 +45,84 @@ module BasicTypes(
 
        StrictnessMark(..), isMarkedUnboxed, isMarkedStrict,
 
-       CompilerPhase, pprPhase, 
-       Activation(..), isActive, isNeverActive, isAlwaysActive
+       CompilerPhase, 
+       Activation(..), isActive, isNeverActive, isAlwaysActive,
+
+       SuccessFlag(..), succeeded, failed, successIf
    ) where
 
 #include "HsVersions.h"
 
+import FastString( FastString )
 import Outputable
 \end{code}
 
 %************************************************************************
 %*                                                                     *
-\subsection[Unused]{Unused}
+\subsection[Arity]{Arity}
 %*                                                                     *
 %************************************************************************
 
-Used as a placeholder in types.
-
 \begin{code}
-type Unused = ()
-
-unused :: Unused
-unused = error "Unused is used!"
+type Arity = Int
 \end{code}
 
 
 %************************************************************************
 %*                                                                     *
-\subsection[Arity]{Arity}
+\subsection[Version]{Module and identifier version numbers}
 %*                                                                     *
 %************************************************************************
 
 \begin{code}
-type Arity = Int
+type Version = Int
+
+bumpVersion :: Version -> Version 
+bumpVersion v = v+1
+
+initialVersion :: Version
+initialVersion = 1
 \end{code}
 
+%************************************************************************
+%*                                                                     *
+               Deprecations
+%*                                                                     *
+%************************************************************************
+
+
+\begin{code}
+type DeprecTxt = FastString    -- reason/explanation for deprecation
+\end{code}
 
 %************************************************************************
 %*                                                                     *
-\subsection[Version]{Module and identifier version numbers}
+\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}
-type Version = Int
+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)
 
-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
+ipNameName :: IPName name -> name
+ipNameName (Dupable n) = n
+ipNameName (Linear  n) = n
 
-initialVersion :: Version
-initialVersion = 1
+mapIPName :: (a->b) -> IPName a -> IPName b
+mapIPName f (Dupable n) = Dupable (f n)
+mapIPName f (Linear  n) = Linear  (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
 \end{code}
 
 
@@ -105,21 +133,25 @@ initialVersion = 1
 %************************************************************************
 
 \begin{code}
+------------------------
 data Fixity = Fixity Int FixityDirection
-data FixityDirection = InfixL | InfixR | InfixN 
-                    deriving(Eq)
 
 instance Outputable Fixity where
     ppr (Fixity prec dir) = hcat [ppr dir, space, int prec]
 
+instance Eq Fixity where               -- Used to determine if two fixities conflict
+  (Fixity p1 dir1) == (Fixity p2 dir2) = p1==p2 && dir1 == dir2
+
+------------------------
+data FixityDirection = InfixL | InfixR | InfixN 
+                    deriving(Eq)
+
 instance Outputable FixityDirection where
     ppr InfixL = ptext SLIT("infixl")
     ppr InfixR = ptext SLIT("infixr")
     ppr InfixN = ptext SLIT("infix")
 
-instance Eq Fixity where               -- Used to determine if two fixities conflict
-  (Fixity p1 dir1) == (Fixity p2 dir2) = p1==p2 && dir1 == dir2
-
+------------------------
 maxPrecedence = (9::Int)
 defaultFixity = Fixity maxPrecedence InfixL
 
@@ -130,20 +162,33 @@ negatePrecedence :: Int
 negatePrecedence = 6
 \end{code}
 
+Consider
 
-%************************************************************************
-%*                                                                     *
-\subsection[NewType/DataType]{NewType/DataType flag}
-%*                                                                     *
-%************************************************************************
+\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}
-data NewOrData
-  = NewType    -- "newtype Blah ..."
-  | DataType   -- "data Blah ..."
-  deriving( Eq )       -- Needed because Demand derives Eq
+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}
 
+
 %************************************************************************
 %*                                                                     *
 \subsection[Top-level/local]{Top-level/not-top level flag}
@@ -162,8 +207,13 @@ isNotTopLevel TopLevel    = False
 
 isTopLevel TopLevel    = True
 isTopLevel NotTopLevel  = False
+
+instance Outputable TopLevelFlag where
+  ppr TopLevel    = ptext SLIT("<TopLevel>")
+  ppr NotTopLevel = ptext SLIT("<NotTopLevel>")
 \end{code}
 
+
 %************************************************************************
 %*                                                                     *
 \subsection[Top-level/local]{Top-level/not-top level flag}
@@ -179,10 +229,6 @@ data Boxity
 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}
 
 
@@ -195,6 +241,7 @@ tupleParens Unboxed p = ptext SLIT("(#") <+> p <+> ptext SLIT("#)")
 \begin{code} 
 data RecFlag = Recursive 
             | NonRecursive
+            deriving( Eq )
 
 isRec :: RecFlag -> Bool
 isRec Recursive    = True
@@ -203,6 +250,31 @@ isRec NonRecursive = False
 isNonRec :: RecFlag -> Bool
 isNonRec Recursive    = False
 isNonRec NonRecursive = True
+
+boolToRecFlag :: Bool -> RecFlag
+boolToRecFlag True  = Recursive
+boolToRecFlag False = NonRecursive
+
+instance Outputable RecFlag where
+  ppr Recursive    = ptext SLIT("Recursive")
+  ppr NonRecursive = ptext SLIT("NonRecursive")
+\end{code}
+
+%************************************************************************
+%*                                                                     *
+               Tuples
+%*                                                                     *
+%************************************************************************
+
+\begin{code}
+data TupCon = TupCon Boxity Arity
+
+instance Eq TupCon where
+  (TupCon b1 a1) == (TupCon b2 a2) = b1==b2 && a1==a2
+   
+tupleParens :: Boxity -> SDoc -> SDoc
+tupleParens Boxed   p = parens p
+tupleParens Unboxed p = ptext SLIT("(#") <+> p <+> ptext SLIT("#)")
 \end{code}
 
 %************************************************************************
@@ -212,7 +284,7 @@ isNonRec NonRecursive = True
 %************************************************************************
 
 This is the "Embedding-Projection pair" datatype, it contains 
-two pieces of code (normally either RenamedHsExpr's or Id's)
+two pieces of code (normally either RenamedExpr'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 
 
@@ -290,6 +362,9 @@ isDeadOcc :: OccInfo -> Bool
 isDeadOcc IAmDead = True
 isDeadOcc other          = False
 
+isOneOcc (OneOcc _ _) = True
+isOneOcc other       = False
+
 isFragileOcc :: OccInfo -> Bool
 isFragileOcc (OneOcc _ _) = True
 isFragileOcc other       = False
@@ -319,11 +394,10 @@ 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
+data StrictnessMark    -- Used in interface decls only
+   = MarkedStrict      
+   | MarkedUnboxed     
+   | NotMarkedStrict   
    deriving( Eq )
 
 isMarkedUnboxed MarkedUnboxed = True
@@ -333,10 +407,31 @@ 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
+  ppr MarkedUnboxed    = ptext SLIT("!!")
+  ppr NotMarkedStrict  = ptext SLIT("_")
+\end{code}
+
+
+%************************************************************************
+%*                                                                     *
+\subsection{Success flag}
+%*                                                                     *
+%************************************************************************
+
+\begin{code}
+data SuccessFlag = Succeeded | Failed
+
+successIf :: Bool -> SuccessFlag
+successIf True  = Succeeded
+successIf False = Failed
+
+succeeded, failed :: SuccessFlag -> Bool
+succeeded Succeeded = True
+succeeded Failed    = False
+
+failed Succeeded = False
+failed Failed    = True
 \end{code}
 
 
@@ -353,23 +448,23 @@ 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
+               | 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 (ActiveAfter n) = pprPhase n
-   ppr NeverActive     = ptext SLIT("NEVER")
+   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 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
@@ -378,3 +473,4 @@ isNeverActive act     = False
 isAlwaysActive AlwaysActive = True
 isAlwaysActive other       = False
 \end{code}
+