| Safe Haskell | None |
|---|---|
| Language | GHC2021 |
GHC.Hs
Contents
Synopsis
- module Language.Haskell.Syntax
- module GHC.Hs.Basic
- 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
- data HsModule p
- = HsModule {
- hsmodExt :: XCModule p
- hsmodName :: Maybe (XRec p ModuleName)
- hsmodExports :: Maybe (XRec p [LIE p])
- hsmodImports :: [LImportDecl p]
- hsmodDecls :: [LHsDecl p]
- | XModule !(XXModule p)
- = HsModule {
- data AnnsModule = AnnsModule {
- am_sig :: EpToken "signature"
- am_mod :: EpToken "module"
- am_where :: EpToken "where"
- am_decls :: [TrailingAnn]
- am_cs :: [LEpaComment]
- am_eof :: Maybe (RealSrcSpan, RealSrcSpan)
- data HsParsedModule = HsParsedModule {
- hpm_module :: Located (HsModule GhcPs)
- hpm_src_files :: [FilePath]
- data XModulePs = XModulePs {}
Documentation
module Language.Haskell.Syntax
module GHC.Hs.Basic
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
Haskell Module
All we actually declare here is the top-level structure for a module.
Constructors
| HsModule | |
Fields
| |
| XModule !(XXModule p) | |
Instances
| Outputable (HsModule GhcPs) Source # | |
| Data (HsModule GhcPs) Source # | |
Defined in GHC.Hs Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsModule GhcPs -> c (HsModule GhcPs) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsModule GhcPs) Source # toConstr :: HsModule GhcPs -> Constr Source # dataTypeOf :: HsModule GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsModule GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsModule GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> HsModule GhcPs -> HsModule GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsModule GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsModule GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsModule GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsModule GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsModule GhcPs -> m (HsModule GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsModule GhcPs -> m (HsModule GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsModule GhcPs -> m (HsModule GhcPs) Source # | |
data AnnsModule Source #
Constructors
| AnnsModule | |
Fields
| |
Instances
| NoAnn AnnsModule Source # | |
Defined in GHC.Hs Methods noAnn :: AnnsModule Source # | |
| Eq AnnsModule Source # | |
Defined in GHC.Hs Methods (==) :: AnnsModule -> AnnsModule -> Bool Source # (/=) :: AnnsModule -> AnnsModule -> Bool Source # | |
| Data AnnsModule Source # | |
Defined in GHC.Hs Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnnsModule -> c AnnsModule Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AnnsModule Source # toConstr :: AnnsModule -> Constr Source # dataTypeOf :: AnnsModule -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AnnsModule) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnnsModule) Source # gmapT :: (forall b. Data b => b -> b) -> AnnsModule -> AnnsModule Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnsModule -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnsModule -> r Source # gmapQ :: (forall d. Data d => d -> u) -> AnnsModule -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnsModule -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnsModule -> m AnnsModule Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnsModule -> m AnnsModule Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnsModule -> m AnnsModule Source # | |
data HsParsedModule Source #
Constructors
| HsParsedModule | |
Fields
| |
Haskell Module extension point: GHC specific
Constructors
| XModulePs | |
Fields
| |
Instances
| Data XModulePs Source # | |
Defined in GHC.Hs Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> XModulePs -> c XModulePs Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c XModulePs Source # toConstr :: XModulePs -> Constr Source # dataTypeOf :: XModulePs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c XModulePs) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c XModulePs) Source # gmapT :: (forall b. Data b => b -> b) -> XModulePs -> XModulePs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> XModulePs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> XModulePs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> XModulePs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> XModulePs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> XModulePs -> m XModulePs Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> XModulePs -> m XModulePs Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> XModulePs -> m XModulePs Source # | |
Orphan instances
| Outputable (HsModule GhcPs) Source # | |
| Data (HsModule GhcPs) Source # | |
Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsModule GhcPs -> c (HsModule GhcPs) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsModule GhcPs) Source # toConstr :: HsModule GhcPs -> Constr Source # dataTypeOf :: HsModule GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsModule GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsModule GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> HsModule GhcPs -> HsModule GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsModule GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsModule GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsModule GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsModule GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsModule GhcPs -> m (HsModule GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsModule GhcPs -> m (HsModule GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsModule GhcPs -> m (HsModule GhcPs) Source # | |