%
% (c) The University of Glasgow 2006
% (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
%
\section{Haskell abstract syntax definition}
This module glues together the pieces of the Haskell abstract syntax,
which is declared in the various \tr{Hs*} modules. This module,
therefore, is almost nothing but re-exporting.
\begin{code}
module HsSyn (
module HsBinds,
module HsDecls,
module HsExpr,
module HsImpExp,
module HsLit,
module HsPat,
module HsTypes,
module HsUtils,
module HsDoc,
Fixity,
HsModule(..), HsExtCore(..),
) where
import HsDecls
import HsBinds
import HsExpr
import HsImpExp
import HsLit
import HsPat
import HsTypes
import BasicTypes ( Fixity, WarningTxt )
import HsUtils
import HsDoc
import OccName ( HasOccName )
import IfaceSyn ( IfaceBinding )
import Outputable
import SrcLoc
import Module ( Module, ModuleName )
import FastString
import Data.Data hiding ( Fixity )
\end{code}
\begin{code}
data HsModule name
= HsModule {
hsmodName :: Maybe (Located ModuleName),
hsmodExports :: Maybe [LIE name],
hsmodImports :: [LImportDecl name],
hsmodDecls :: [LHsDecl name],
hsmodDeprecMessage :: Maybe WarningTxt,
hsmodHaddockModHeader :: Maybe LHsDocString
} deriving (Data, Typeable)
data HsExtCore name
= HsExtCore
Module
[TyClDecl name]
[IfaceBinding]
\end{code}
\begin{code}
instance (OutputableBndr name, HasOccName name)
=> Outputable (HsModule name) where
ppr (HsModule Nothing _ imports decls _ mbDoc)
= pp_mb mbDoc $$ pp_nonnull imports $$ pp_nonnull decls
ppr (HsModule (Just name) exports imports decls deprec mbDoc)
= vcat [
pp_mb mbDoc,
case exports of
Nothing -> pp_header (ptext (sLit "where"))
Just es -> vcat [
pp_header lparen,
nest 8 (fsep (punctuate comma (map ppr es))),
nest 4 (ptext (sLit ") where"))
],
pp_nonnull imports,
pp_nonnull decls
]
where
pp_header rest = case deprec of
Nothing -> pp_modname <+> rest
Just d -> vcat [ pp_modname, ppr d, rest ]
pp_modname = ptext (sLit "module") <+> ppr name
pp_mb :: Outputable t => Maybe t -> SDoc
pp_mb (Just x) = ppr x
pp_mb Nothing = empty
pp_nonnull :: Outputable t => [t] -> SDoc
pp_nonnull [] = empty
pp_nonnull xs = vcat (map ppr xs)
\end{code}