{-
(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 {
      HsModule pass -> Maybe (Located ModuleName)
hsmodName :: Maybe (Located ModuleName),
        -- ^ @Nothing@: \"module X where\" is omitted (in which case the next
        --     field is Nothing too)
      HsModule pass -> Maybe (Located [LIE pass])
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
      HsModule pass -> [LImportDecl pass]
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.
      HsModule pass -> [LHsDecl pass]
hsmodDecls :: [LHsDecl pass],
        -- ^ Type, class, value, and interface signature decls
      HsModule pass -> Maybe (Located WarningTxt)
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
      HsModule pass -> Maybe LHsDocString
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 (OutputableBndrId p) => Outputable (HsModule (GhcPass p)) where

    ppr :: HsModule (GhcPass p) -> SDoc
ppr (HsModule Maybe (Located ModuleName)
Nothing Maybe (Located [LIE (GhcPass p)])
_ [LImportDecl (GhcPass p)]
imports [LHsDecl (GhcPass p)]
decls Maybe (Located WarningTxt)
_ Maybe LHsDocString
mbDoc)
      = Maybe LHsDocString -> SDoc
forall t. Outputable t => Maybe t -> SDoc
pp_mb Maybe LHsDocString
mbDoc SDoc -> SDoc -> SDoc
$$ [LImportDecl (GhcPass p)] -> SDoc
forall t. Outputable t => [t] -> SDoc
pp_nonnull [LImportDecl (GhcPass p)]
imports
                    SDoc -> SDoc -> SDoc
$$ [LHsDecl (GhcPass p)] -> SDoc
forall t. Outputable t => [t] -> SDoc
pp_nonnull [LHsDecl (GhcPass p)]
decls

    ppr (HsModule (Just Located ModuleName
name) Maybe (Located [LIE (GhcPass p)])
exports [LImportDecl (GhcPass p)]
imports [LHsDecl (GhcPass p)]
decls Maybe (Located WarningTxt)
deprec Maybe LHsDocString
mbDoc)
      = [SDoc] -> SDoc
vcat [
            Maybe LHsDocString -> SDoc
forall t. Outputable t => Maybe t -> SDoc
pp_mb Maybe LHsDocString
mbDoc,
            case Maybe (Located [LIE (GhcPass p)])
exports of
              Maybe (Located [LIE (GhcPass p)])
Nothing -> SDoc -> SDoc
pp_header (String -> SDoc
text String
"where")
              Just Located [LIE (GhcPass p)]
es -> [SDoc] -> SDoc
vcat [
                           SDoc -> SDoc
pp_header SDoc
lparen,
                           Int -> SDoc -> SDoc
nest Int
8 ([SDoc] -> SDoc
fsep (SDoc -> [SDoc] -> [SDoc]
punctuate SDoc
comma ((LIE (GhcPass p) -> SDoc) -> [LIE (GhcPass p)] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map LIE (GhcPass p) -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Located [LIE (GhcPass p)]
-> SrcSpanLess (Located [LIE (GhcPass p)])
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc Located [LIE (GhcPass p)]
es)))),
                           Int -> SDoc -> SDoc
nest Int
4 (String -> SDoc
text String
") where")
                          ],
            [LImportDecl (GhcPass p)] -> SDoc
forall t. Outputable t => [t] -> SDoc
pp_nonnull [LImportDecl (GhcPass p)]
imports,
            [LHsDecl (GhcPass p)] -> SDoc
forall t. Outputable t => [t] -> SDoc
pp_nonnull [LHsDecl (GhcPass p)]
decls
          ]
      where
        pp_header :: SDoc -> SDoc
pp_header SDoc
rest = case Maybe (Located WarningTxt)
deprec of
           Maybe (Located WarningTxt)
Nothing -> SDoc
pp_modname SDoc -> SDoc -> SDoc
<+> SDoc
rest
           Just Located WarningTxt
d -> [SDoc] -> SDoc
vcat [ SDoc
pp_modname, Located WarningTxt -> SDoc
forall a. Outputable a => a -> SDoc
ppr Located WarningTxt
d, SDoc
rest ]

        pp_modname :: SDoc
pp_modname = String -> SDoc
text String
"module" SDoc -> SDoc -> SDoc
<+> Located ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
ppr Located ModuleName
name

pp_mb :: Outputable t => Maybe t -> SDoc
pp_mb :: Maybe t -> SDoc
pp_mb (Just t
x) = t -> SDoc
forall a. Outputable a => a -> SDoc
ppr t
x
pp_mb Maybe t
Nothing  = SDoc
empty

pp_nonnull :: Outputable t => [t] -> SDoc
pp_nonnull :: [t] -> SDoc
pp_nonnull [] = SDoc
empty
pp_nonnull [t]
xs = [SDoc] -> SDoc
vcat ((t -> SDoc) -> [t] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map t -> SDoc
forall a. Outputable a => a -> SDoc
ppr [t]
xs)