Refactor SrcLoc and SrcSpan
[ghc-hetmet.git] / compiler / hsSyn / HsSyn.lhs
index 45d1ec0..ce748eb 100644 (file)
@@ -9,6 +9,8 @@ which is declared in the various \tr{Hs*} modules.  This module,
 therefore, is almost nothing but re-exporting.
 
 \begin{code}
+{-# LANGUAGE DeriveDataTypeable #-}
+
 module HsSyn (
        module HsBinds,
        module HsDecls,
@@ -22,9 +24,6 @@ module HsSyn (
        Fixity,
 
        HsModule(..), HsExtCore(..),
-
-       HaddockModInfo(..),
-       emptyHaddockModInfo,
 ) where
 
 -- friends:
@@ -42,9 +41,12 @@ import HsDoc
 -- others:
 import IfaceSyn                ( IfaceBinding )
 import Outputable
-import SrcLoc          ( Located(..) )
+import SrcLoc
 import Module          ( Module, ModuleName )
 import FastString
+
+-- libraries:
+import Data.Data hiding ( Fixity )
 \end{code}
 
 \begin{code}
@@ -71,26 +73,9 @@ data HsModule name
         -- ^ Type, class, value, and interface signature decls
       hsmodDeprecMessage :: Maybe WarningTxt,
         -- ^ reason\/explanation for warning/deprecation of this module
-      hsmodHaddockModInfo :: HaddockModInfo name,
-        -- ^ Haddock module info
-      hsmodHaddockModDescr :: Maybe (HsDoc name)
-        -- ^ Haddock module description
-   }
-
-data HaddockModInfo name = HaddockModInfo { 
-       hmi_description :: Maybe (HsDoc name),
-       hmi_portability :: Maybe String,
-       hmi_stability   :: Maybe String,
-       hmi_maintainer  :: Maybe String
-}
-
-emptyHaddockModInfo :: HaddockModInfo a                                                  
-emptyHaddockModInfo = HaddockModInfo {                                                  
-       hmi_description = Nothing,
-       hmi_portability = Nothing,
-       hmi_stability   = Nothing,
-       hmi_maintainer  = Nothing
-}       
+      hsmodHaddockModHeader :: Maybe LHsDocString
+        -- ^ Haddock module info and description, unparsed
+   } deriving (Data, Typeable)
 
 data HsExtCore name    -- Read from Foo.hcr
   = HsExtCore
@@ -108,10 +93,10 @@ instance Outputable Char where
 instance (OutputableBndr name)
        => Outputable (HsModule name) where
 
-    ppr (HsModule Nothing _ imports decls _ _ mbDoc)
+    ppr (HsModule Nothing _ imports decls _ mbDoc)
       = pp_mb mbDoc $$ pp_nonnull imports $$ pp_nonnull decls
 
-    ppr (HsModule (Just name) exports imports decls deprec _ mbDoc)
+    ppr (HsModule (Just name) exports imports decls deprec mbDoc)
       = vcat [
            pp_mb mbDoc,
            case exports of