{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleInstances #-}
module GHC.Hs (
module Language.Haskell.Syntax,
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.Type,
module GHC.Hs.Utils,
module GHC.Hs.Doc,
module GHC.Hs.Extension,
module GHC.Parser.Annotation,
Fixity,
HsModule(..), AnnsModule(..),
HsParsedModule(..)
) where
import GHC.Prelude
import GHC.Hs.Decls
import GHC.Hs.Binds
import GHC.Hs.Expr
import GHC.Hs.ImpExp
import GHC.Hs.Lit
import Language.Haskell.Syntax
import GHC.Hs.Extension
import GHC.Parser.Annotation
import GHC.Hs.Pat
import GHC.Hs.Type
import GHC.Hs.Utils
import GHC.Hs.Doc
import GHC.Hs.Instances ()
import GHC.Utils.Outputable
import GHC.Types.Fixity ( Fixity )
import GHC.Types.SrcLoc
import GHC.Unit.Module ( ModuleName )
import GHC.Unit.Module.Warnings ( WarningTxt )
import Data.Data hiding ( Fixity )
data HsModule
= HsModule {
HsModule -> EpAnn AnnsModule
hsmodAnn :: EpAnn AnnsModule,
HsModule -> LayoutInfo
hsmodLayout :: LayoutInfo,
HsModule -> Maybe (LocatedA ModuleName)
hsmodName :: Maybe (LocatedA ModuleName),
HsModule -> Maybe (LocatedL [LIE GhcPs])
hsmodExports :: Maybe (LocatedL [LIE GhcPs]),
HsModule -> [LImportDecl GhcPs]
hsmodImports :: [LImportDecl GhcPs],
HsModule -> [LHsDecl GhcPs]
hsmodDecls :: [LHsDecl GhcPs],
HsModule -> Maybe (LocatedP WarningTxt)
hsmodDeprecMessage :: Maybe (LocatedP WarningTxt),
:: Maybe LHsDocString
}
deriving instance Data HsModule
data AnnsModule
= AnnsModule {
AnnsModule -> [AddEpAnn]
am_main :: [AddEpAnn],
AnnsModule -> AnnList
am_decls :: AnnList
} deriving (Typeable AnnsModule
Typeable AnnsModule
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AnnsModule -> c AnnsModule)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AnnsModule)
-> (AnnsModule -> Constr)
-> (AnnsModule -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c AnnsModule))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c AnnsModule))
-> ((forall b. Data b => b -> b) -> AnnsModule -> AnnsModule)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AnnsModule -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AnnsModule -> r)
-> (forall u. (forall d. Data d => d -> u) -> AnnsModule -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> AnnsModule -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> AnnsModule -> m AnnsModule)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> AnnsModule -> m AnnsModule)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> AnnsModule -> m AnnsModule)
-> Data AnnsModule
AnnsModule -> DataType
AnnsModule -> Constr
(forall b. Data b => b -> b) -> AnnsModule -> AnnsModule
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> AnnsModule -> u
forall u. (forall d. Data d => d -> u) -> AnnsModule -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AnnsModule -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AnnsModule -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> AnnsModule -> m AnnsModule
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> AnnsModule -> m AnnsModule
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AnnsModule
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AnnsModule -> c AnnsModule
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c AnnsModule)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnnsModule)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> AnnsModule -> m AnnsModule
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> AnnsModule -> m AnnsModule
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> AnnsModule -> m AnnsModule
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> AnnsModule -> m AnnsModule
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> AnnsModule -> m AnnsModule
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> AnnsModule -> m AnnsModule
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> AnnsModule -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> AnnsModule -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> AnnsModule -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> AnnsModule -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AnnsModule -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> AnnsModule -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AnnsModule -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> AnnsModule -> r
gmapT :: (forall b. Data b => b -> b) -> AnnsModule -> AnnsModule
$cgmapT :: (forall b. Data b => b -> b) -> AnnsModule -> AnnsModule
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnnsModule)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnnsModule)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c AnnsModule)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c AnnsModule)
dataTypeOf :: AnnsModule -> DataType
$cdataTypeOf :: AnnsModule -> DataType
toConstr :: AnnsModule -> Constr
$ctoConstr :: AnnsModule -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AnnsModule
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c AnnsModule
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AnnsModule -> c AnnsModule
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> AnnsModule -> c AnnsModule
Data, AnnsModule -> AnnsModule -> Bool
(AnnsModule -> AnnsModule -> Bool)
-> (AnnsModule -> AnnsModule -> Bool) -> Eq AnnsModule
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AnnsModule -> AnnsModule -> Bool
$c/= :: AnnsModule -> AnnsModule -> Bool
== :: AnnsModule -> AnnsModule -> Bool
$c== :: AnnsModule -> AnnsModule -> Bool
Eq)
instance Outputable HsModule where
ppr :: HsModule -> SDoc
ppr (HsModule EpAnn AnnsModule
_ LayoutInfo
_ Maybe (LocatedA ModuleName)
Nothing Maybe (LocatedL [LIE GhcPs])
_ [LImportDecl GhcPs]
imports [LHsDecl GhcPs]
decls Maybe (LocatedP WarningTxt)
_ Maybe LHsDocString
mbDoc)
= Maybe LHsDocString -> SDoc
forall t. Outputable t => Maybe t -> SDoc
pp_mb Maybe LHsDocString
mbDoc SDoc -> SDoc -> SDoc
$$ [GenLocated SrcSpanAnnA (ImportDecl GhcPs)] -> SDoc
forall t. Outputable t => [t] -> SDoc
pp_nonnull [GenLocated SrcSpanAnnA (ImportDecl GhcPs)]
[LImportDecl GhcPs]
imports
SDoc -> SDoc -> SDoc
$$ [GenLocated SrcSpanAnnA (HsDecl GhcPs)] -> SDoc
forall t. Outputable t => [t] -> SDoc
pp_nonnull [GenLocated SrcSpanAnnA (HsDecl GhcPs)]
[LHsDecl GhcPs]
decls
ppr (HsModule EpAnn AnnsModule
_ LayoutInfo
_ (Just LocatedA ModuleName
name) Maybe (LocatedL [LIE GhcPs])
exports [LImportDecl GhcPs]
imports [LHsDecl GhcPs]
decls Maybe (LocatedP 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 (LocatedL [LIE GhcPs])
exports of
Maybe (LocatedL [LIE GhcPs])
Nothing -> SDoc -> SDoc
pp_header (String -> SDoc
text String
"where")
Just LocatedL [LIE GhcPs]
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 ((GenLocated SrcSpanAnnA (IE GhcPs) -> SDoc)
-> [GenLocated SrcSpanAnnA (IE GhcPs)] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map GenLocated SrcSpanAnnA (IE GhcPs) -> SDoc
forall a. Outputable a => a -> SDoc
ppr (LocatedL [GenLocated SrcSpanAnnA (IE GhcPs)]
-> [GenLocated SrcSpanAnnA (IE GhcPs)]
forall l e. GenLocated l e -> e
unLoc LocatedL [GenLocated SrcSpanAnnA (IE GhcPs)]
LocatedL [LIE GhcPs]
es)))),
Int -> SDoc -> SDoc
nest Int
4 (String -> SDoc
text String
") where")
],
[GenLocated SrcSpanAnnA (ImportDecl GhcPs)] -> SDoc
forall t. Outputable t => [t] -> SDoc
pp_nonnull [GenLocated SrcSpanAnnA (ImportDecl GhcPs)]
[LImportDecl GhcPs]
imports,
[GenLocated SrcSpanAnnA (HsDecl GhcPs)] -> SDoc
forall t. Outputable t => [t] -> SDoc
pp_nonnull [GenLocated SrcSpanAnnA (HsDecl GhcPs)]
[LHsDecl GhcPs]
decls
]
where
pp_header :: SDoc -> SDoc
pp_header SDoc
rest = case Maybe (LocatedP WarningTxt)
deprec of
Maybe (LocatedP WarningTxt)
Nothing -> SDoc
pp_modname SDoc -> SDoc -> SDoc
<+> SDoc
rest
Just LocatedP WarningTxt
d -> [SDoc] -> SDoc
vcat [ SDoc
pp_modname, LocatedP WarningTxt -> SDoc
forall a. Outputable a => a -> SDoc
ppr LocatedP WarningTxt
d, SDoc
rest ]
pp_modname :: SDoc
pp_modname = String -> SDoc
text String
"module" SDoc -> SDoc -> SDoc
<+> LocatedA ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
ppr LocatedA ModuleName
name
pp_mb :: Outputable t => Maybe t -> SDoc
pp_mb :: forall t. Outputable t => 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 :: forall t. Outputable t => [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)
data HsParsedModule = HsParsedModule {
HsParsedModule -> Located HsModule
hpm_module :: Located HsModule,
HsParsedModule -> [String]
hpm_src_files :: [FilePath]
}