Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Types and functions for raw and lexed docstrings.
Synopsis
- type HsDoc = WithHsDocIdentifiers HsDocString
- data WithHsDocIdentifiers a pass = WithHsDocIdentifiers {
- hsDocString :: !a
- hsDocIdentifiers :: ![Located (IdP pass)]
- hsDocIds :: WithHsDocIdentifiers a GhcRn -> NameSet
- type LHsDoc pass = Located (HsDoc pass)
- pprHsDocDebug :: Outputable (IdP name) => HsDoc name -> SDoc
- pprWithDoc :: LHsDoc name -> SDoc -> SDoc
- pprMaybeWithDoc :: Maybe (LHsDoc name) -> SDoc -> SDoc
- module GHC.Hs.DocString
- data ExtractedTHDocs = ExtractedTHDocs {
- ethd_mod_header :: Maybe (HsDoc GhcRn)
- ethd_decl_docs :: UniqMap Name (HsDoc GhcRn)
- ethd_arg_docs :: UniqMap Name (IntMap (HsDoc GhcRn))
- ethd_inst_docs :: UniqMap Name (HsDoc GhcRn)
- data DocStructureItem
- = DsiSectionHeading !Int !(HsDoc GhcRn)
- | DsiDocChunk !(HsDoc GhcRn)
- | DsiNamedChunkRef !String
- | DsiExports !Avails
- | DsiModExport !(NonEmpty ModuleName) !Avails
- type DocStructure = [DocStructureItem]
- data Docs = Docs {}
- emptyDocs :: Docs
Documentation
type HsDoc = WithHsDocIdentifiers HsDocString Source #
A docstring with the (probable) identifiers found in it.
data WithHsDocIdentifiers a pass Source #
Annotate a value with the probable identifiers found in it These will be used by haddock to generate links.
The identifiers are bundled along with their location in the source file. This is useful for tooling to know exactly where they originate.
This type is currently used in two places - for regular documentation comments,
with a
set to HsDocString
, and for adding identifier information to
warnings, where a
is StringLiteral
WithHsDocIdentifiers | |
|
Instances
(Data pass, Data (IdP pass), Data a) => Data (WithHsDocIdentifiers a pass) Source # | |
Defined in GHC.Hs.Doc gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WithHsDocIdentifiers a pass -> c (WithHsDocIdentifiers a pass) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WithHsDocIdentifiers a pass) Source # toConstr :: WithHsDocIdentifiers a pass -> Constr Source # dataTypeOf :: WithHsDocIdentifiers a pass -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WithHsDocIdentifiers a pass)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WithHsDocIdentifiers a pass)) Source # gmapT :: (forall b. Data b => b -> b) -> WithHsDocIdentifiers a pass -> WithHsDocIdentifiers a pass Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WithHsDocIdentifiers a pass -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WithHsDocIdentifiers a pass -> r Source # gmapQ :: (forall d. Data d => d -> u) -> WithHsDocIdentifiers a pass -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> WithHsDocIdentifiers a pass -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> WithHsDocIdentifiers a pass -> m (WithHsDocIdentifiers a pass) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WithHsDocIdentifiers a pass -> m (WithHsDocIdentifiers a pass) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WithHsDocIdentifiers a pass -> m (WithHsDocIdentifiers a pass) Source # | |
(NFData (IdP pass), NFData a) => NFData (WithHsDocIdentifiers a pass) Source # | |
Defined in GHC.Hs.Doc rnf :: WithHsDocIdentifiers a pass -> () Source # | |
Binary a => Binary (WithHsDocIdentifiers a GhcRn) Source # | |
Defined in GHC.Hs.Doc | |
Outputable a => Outputable (WithHsDocIdentifiers a pass) Source # | For compatibility with the existing @-ddump-parsed' output, we only show the docstring. Use |
Defined in GHC.Hs.Doc ppr :: WithHsDocIdentifiers a pass -> SDoc Source # | |
(Eq (IdP pass), Eq a) => Eq (WithHsDocIdentifiers a pass) Source # | |
Defined in GHC.Hs.Doc (==) :: WithHsDocIdentifiers a pass -> WithHsDocIdentifiers a pass -> Bool # (/=) :: WithHsDocIdentifiers a pass -> WithHsDocIdentifiers a pass -> Bool # |
hsDocIds :: WithHsDocIdentifiers a GhcRn -> NameSet Source #
Extract a mapping from the lexed identifiers to the names they may correspond to.
pprHsDocDebug :: Outputable (IdP name) => HsDoc name -> SDoc Source #
Print a doc with its identifiers, useful for debugging
pprWithDoc :: LHsDoc name -> SDoc -> SDoc Source #
Pretty print a thing with its doc The docstring will include the comment decorators '-- |', '{-|' etc and will come either before or after depending on how it was written i.e it will come after the thing if it is a '-- ^' or '{-^' and before otherwise.
module GHC.Hs.DocString
data ExtractedTHDocs Source #
Maps of docs that were added via Template Haskell's putDoc
.
ExtractedTHDocs | |
|
data DocStructureItem Source #
A simplified version of IE
.
DsiSectionHeading !Int !(HsDoc GhcRn) | |
DsiDocChunk !(HsDoc GhcRn) | |
DsiNamedChunkRef !String | |
DsiExports !Avails | |
DsiModExport | |
|
Instances
NFData DocStructureItem Source # | |
Defined in GHC.Hs.Doc rnf :: DocStructureItem -> () Source # | |
Binary DocStructureItem Source # | |
Defined in GHC.Hs.Doc put_ :: BinHandle -> DocStructureItem -> IO () Source # put :: BinHandle -> DocStructureItem -> IO (Bin DocStructureItem) Source # | |
Outputable DocStructureItem Source # | |
Defined in GHC.Hs.Doc ppr :: DocStructureItem -> SDoc Source # |
type DocStructure = [DocStructureItem] Source #
Docs | |
|