diff options
author | Sylvain Henry <sylvain@haskus.fr> | 2019-09-11 21:19:39 +0200 |
---|---|---|
committer | Marge Bot <ben+marge-bot@smart-cactus.org> | 2019-09-20 05:14:34 -0400 |
commit | 5119296440e6846c553c72b8a93afc5ecfa576f0 (patch) | |
tree | ff508560a4996afffb24bf3af5dfa9c56a7e5c77 /compiler/GHC/Hs.hs | |
parent | 4853d962289db1b32886ec73e824cd37c9c5c002 (diff) | |
download | haskell-5119296440e6846c553c72b8a93afc5ecfa576f0.tar.gz |
Module hierarchy: Hs (#13009)
Add GHC.Hs module hierarchy replacing hsSyn.
Metric Increase:
haddock.compiler
Diffstat (limited to 'compiler/GHC/Hs.hs')
-rw-r--r-- | compiler/GHC/Hs.hs | 153 |
1 files changed, 153 insertions, 0 deletions
diff --git a/compiler/GHC/Hs.hs b/compiler/GHC/Hs.hs new file mode 100644 index 0000000000..aa345f1476 --- /dev/null +++ b/compiler/GHC/Hs.hs @@ -0,0 +1,153 @@ +{- +(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. +-} + +{-# LANGUAGE DeriveDataTypeable #-} +{-# LANGUAGE StandaloneDeriving #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE UndecidableInstances #-} -- Note [Pass sensitive types] + -- in module GHC.Hs.PlaceHolder +{-# LANGUAGE ConstraintKinds #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE FlexibleInstances #-} -- For deriving instance Data + +module GHC.Hs ( + module GHC.Hs.Binds, + module GHC.Hs.Decls, + module GHC.Hs.Expr, + module GHC.Hs.ImpExp, + module GHC.Hs.Lit, + module GHC.Hs.Pat, + module GHC.Hs.Types, + module GHC.Hs.Utils, + module GHC.Hs.Doc, + module GHC.Hs.PlaceHolder, + module GHC.Hs.Extension, + Fixity, + + HsModule(..), +) where + +-- friends: +import GhcPrelude + +import GHC.Hs.Decls +import GHC.Hs.Binds +import GHC.Hs.Expr +import GHC.Hs.ImpExp +import GHC.Hs.Lit +import GHC.Hs.PlaceHolder +import GHC.Hs.Extension +import GHC.Hs.Pat +import GHC.Hs.Types +import BasicTypes ( Fixity, WarningTxt ) +import GHC.Hs.Utils +import GHC.Hs.Doc +import GHC.Hs.Instances () -- For Data instances + +-- others: +import Outputable +import SrcLoc +import Module ( ModuleName ) + +-- libraries: +import Data.Data hiding ( Fixity ) + +-- | Haskell Module +-- +-- All we actually declare here is the top-level structure for a module. +data HsModule pass + = HsModule { + hsmodName :: Maybe (Located ModuleName), + -- ^ @Nothing@: \"module X where\" is omitted (in which case the next + -- field is Nothing too) + hsmodExports :: Maybe (Located [LIE pass]), + -- ^ Export list + -- + -- - @Nothing@: export list omitted, so export everything + -- + -- - @Just []@: export /nothing/ + -- + -- - @Just [...]@: as you would expect... + -- + -- + -- - 'ApiAnnotation.AnnKeywordId's : 'ApiAnnotation.AnnOpen' + -- ,'ApiAnnotation.AnnClose' + + -- For details on above see note [Api annotations] in ApiAnnotation + hsmodImports :: [LImportDecl pass], + -- ^ We snaffle interesting stuff out of the imported interfaces early + -- on, adding that info to TyDecls/etc; so this list is often empty, + -- downstream. + hsmodDecls :: [LHsDecl pass], + -- ^ Type, class, value, and interface signature decls + hsmodDeprecMessage :: Maybe (Located WarningTxt), + -- ^ reason\/explanation for warning/deprecation of this module + -- + -- - 'ApiAnnotation.AnnKeywordId's : 'ApiAnnotation.AnnOpen' + -- ,'ApiAnnotation.AnnClose' + -- + + -- For details on above see note [Api annotations] in ApiAnnotation + hsmodHaddockModHeader :: Maybe LHsDocString + -- ^ Haddock module info and description, unparsed + -- + -- - 'ApiAnnotation.AnnKeywordId's : 'ApiAnnotation.AnnOpen' + -- ,'ApiAnnotation.AnnClose' + + -- For details on above see note [Api annotations] in ApiAnnotation + } + -- ^ 'ApiAnnotation.AnnKeywordId's + -- + -- - 'ApiAnnotation.AnnModule','ApiAnnotation.AnnWhere' + -- + -- - 'ApiAnnotation.AnnOpen','ApiAnnotation.AnnSemi', + -- 'ApiAnnotation.AnnClose' for explicit braces and semi around + -- hsmodImports,hsmodDecls if this style is used. + + -- For details on above see note [Api annotations] in ApiAnnotation +-- deriving instance (DataIdLR name name) => Data (HsModule name) +deriving instance Data (HsModule GhcPs) +deriving instance Data (HsModule GhcRn) +deriving instance Data (HsModule GhcTc) + +instance (p ~ GhcPass pass, OutputableBndrId p) => Outputable (HsModule p) 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 (text "where") + Just es -> vcat [ + pp_header lparen, + nest 8 (fsep (punctuate comma (map ppr (unLoc es)))), + nest 4 (text ") 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 = text "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) |