[project @ 2002-11-06 13:10:46 by simonpj]
[ghc-hetmet.git] / ghc / compiler / hsSyn / HsSyn.lhs
index 4a3c1f6..7f5ca52 100644 (file)
@@ -9,23 +9,23 @@ therefore, is almost nothing but re-exporting.
 
 \begin{code}
 module HsSyn (
-
        -- NB: don't reexport HsCore
        -- this module tells about "real Haskell"
 
-       module HsSyn,
        module HsBinds,
        module HsDecls,
        module HsExpr,
        module HsImpExp,
        module HsLit,
-       module HsMatches,
        module HsPat,
        module HsTypes,
        Fixity, NewOrData, 
 
-       collectTopBinders, collectMonoBinders, collectLocatedMonoBinders,
-       hsModuleName, hsModuleImports
+       HsModule(..), hsModule, hsImports,
+       collectStmtsBinders,
+       collectHsBinders,   collectLocatedHsBinders, 
+       collectMonoBinders, collectLocatedMonoBinders,
+       collectSigTysFromHsBinds, collectSigTysFromMonoBinds
      ) where
 
 #include "HsVersions.h"
@@ -36,23 +36,22 @@ import HsBinds
 import HsExpr
 import HsImpExp
 import HsLit
-import HsMatches
 import HsPat
 import HsTypes
 import BasicTypes      ( Fixity, Version, NewOrData )
 
 -- others:
+import Name            ( NamedThing )
 import Outputable
 import SrcLoc          ( SrcLoc )
-import Bag
-import Module          ( ModuleName )
+import Module          ( Module )
 \end{code}
 
 All we actually declare here is the top-level structure for a module.
 \begin{code}
-data HsModule name pat
+data HsModule name
   = HsModule
-       ModuleName              -- module name
+       Module
        (Maybe Version)         -- source interface version number
        (Maybe [IE name])       -- export list; Nothing => export everything
                                -- Just [] => export *nothing* (???)
@@ -61,14 +60,14 @@ data HsModule name pat
                                -- imported interfaces early on, adding that
                                -- info to TyDecls/etc; so this list is
                                -- often empty, downstream.
-       [HsDecl name pat]       -- Type, class, value, and interface signature decls
+       [HsDecl name]   -- Type, class, value, and interface signature decls
        (Maybe DeprecTxt)       -- reason/explanation for deprecation of this module
        SrcLoc
 \end{code}
 
 \begin{code}
-instance (Outputable name, Outputable pat)
-       => Outputable (HsModule name pat) where
+instance (NamedThing name, OutputableBndr name)
+       => Outputable (HsModule name) where
 
     ppr (HsModule name iface_version exports imports
                      decls deprec src_loc)
@@ -93,8 +92,8 @@ instance (Outputable name, Outputable pat)
        pp_nonnull [] = empty
        pp_nonnull xs = vcat (map ppr xs)
 
-hsModuleName    (HsModule mod_name _ _ _ _ _ _) = mod_name
-hsModuleImports (HsModule mod_name vers exports imports decls deprec src_loc) = imports
+hsModule  (HsModule mod _ _ _ _ _ _) = mod
+hsImports (HsModule mod vers exports imports decls deprec src_loc) = imports
 \end{code}
 
 
@@ -118,12 +117,22 @@ where
 it should return @[x, y, f, a, b]@ (remember, order important).
 
 \begin{code}
-collectTopBinders :: HsBinds name (InPat name) -> Bag (name,SrcLoc)
-collectTopBinders EmptyBinds        = emptyBag
-collectTopBinders (MonoBind b _ _)  = listToBag (collectLocatedMonoBinders b)
-collectTopBinders (ThenBinds b1 b2) = collectTopBinders b1 `unionBags` collectTopBinders b2
-
-collectLocatedMonoBinders :: MonoBinds name (InPat name) -> [(name,SrcLoc)]
+collectLocatedHsBinders :: HsBinds name -> [(name,SrcLoc)]
+-- Used at top level only; so no need for an IPBinds case
+collectLocatedHsBinders EmptyBinds = []
+collectLocatedHsBinders (MonoBind b _ _) 
+ = collectLocatedMonoBinders b
+collectLocatedHsBinders (ThenBinds b1 b2)
+ = collectLocatedHsBinders b1 ++ collectLocatedHsBinders b2
+
+collectHsBinders :: HsBinds name -> [name]
+collectHsBinders EmptyBinds       = []
+collectHsBinders (IPBinds _ _)    = []         -- Implicit parameters don't create
+                                               -- ordinary bindings
+collectHsBinders (MonoBind b _ _)  = collectMonoBinders b
+collectHsBinders (ThenBinds b1 b2) = collectHsBinders b1 ++ collectHsBinders b2
+
+collectLocatedMonoBinders :: MonoBinds name -> [(name,SrcLoc)]
 collectLocatedMonoBinders binds
   = go binds []
   where
@@ -132,7 +141,7 @@ collectLocatedMonoBinders binds
     go (FunMonoBind f _ _ loc) acc = (f,loc) : acc
     go (AndMonoBinds bs1 bs2)  acc = go bs1 (go bs2 acc)
 
-collectMonoBinders :: MonoBinds name (InPat name) -> [name]
+collectMonoBinders :: MonoBinds name -> [name]
 collectMonoBinders binds
   = go binds []
   where
@@ -141,3 +150,52 @@ collectMonoBinders binds
     go (FunMonoBind f _ _ loc) acc = f : acc
     go (AndMonoBinds bs1 bs2)  acc = go bs1 (go bs2 acc)
 \end{code}
+
+
+%************************************************************************
+%*                                                                     *
+\subsection{Getting patterns out of bindings}
+%*                                                                     *
+%************************************************************************
+
+Get all the pattern type signatures out of a bunch of bindings
+
+\begin{code}
+collectSigTysFromHsBinds :: HsBinds name -> [HsType name]
+collectSigTysFromHsBinds EmptyBinds        = [] 
+collectSigTysFromHsBinds (IPBinds _ _)     = [] 
+collectSigTysFromHsBinds (MonoBind b _ _)  = collectSigTysFromMonoBinds b
+collectSigTysFromHsBinds (ThenBinds b1 b2) = collectSigTysFromHsBinds b1 ++
+                                            collectSigTysFromHsBinds b2
+
+collectSigTysFromMonoBinds :: MonoBinds name -> [HsType name]
+collectSigTysFromMonoBinds bind
+  = go bind []
+  where
+    go EmptyMonoBinds           acc = acc
+    go (PatMonoBind pat _ loc)  acc = collectSigTysFromPat pat ++ acc
+    go (FunMonoBind f _ ms loc) acc = go_matches ms acc
+    go (AndMonoBinds bs1 bs2)   acc = go bs1 (go bs2 acc)
+
+       -- A binding like    x :: a = f y
+       -- is parsed as FunMonoBind, but for this purpose we    
+       -- want to treat it as a pattern binding
+    go_matches []                               acc = acc
+    go_matches (Match [] (Just sig) _ : matches) acc = sig : go_matches matches acc
+    go_matches (match                : matches) acc = go_matches matches acc
+\end{code}
+
+\begin{code}
+collectStmtsBinders :: [Stmt id] -> [id]
+collectStmtsBinders = concatMap collectStmtBinders
+
+collectStmtBinders :: Stmt id -> [id]
+  -- Id Binders for a Stmt... [but what about pattern-sig type vars]?
+collectStmtBinders (BindStmt pat _ _) = collectPatBinders pat
+collectStmtBinders (LetStmt binds)    = collectHsBinders binds
+collectStmtBinders (ExprStmt _ _ _)   = []
+collectStmtBinders (ResultStmt _ _)   = []
+collectStmtBinders other              = panic "collectStmtBinders"
+\end{code}
+