Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Extract docs from the renamer output so they can be serialized.
Synopsis
- extractDocs :: MonadIO m => TcGblEnv -> m (Maybe HsDocString, DeclDocMap, ArgDocMap)
- mkMaps :: [Name] -> [(LHsDecl GhcRn, [HsDocString])] -> (Map Name HsDocString, Map Name (IntMap HsDocString))
- getMainDeclBinder :: (Anno (IdGhcP p) ~ SrcSpanAnnN, CollectPass (GhcPass p)) => HsDecl (GhcPass p) -> [IdP (GhcPass p)]
- sigNameNoLoc :: forall pass. UnXRec pass => Sig pass -> [IdP pass]
- getInstLoc :: Anno (IdGhcP p) ~ SrcSpanAnnN => InstDecl (GhcPass p) -> SrcSpan
- subordinates :: Map RealSrcSpan Name -> HsDecl GhcRn -> [(Name, [HsDocString], IntMap HsDocString)]
- conArgDocs :: ConDecl GhcRn -> IntMap HsDocString
- h98ConArgDocs :: HsConDeclH98Details GhcRn -> IntMap HsDocString
- gadtConArgDocs :: HsConDeclGADTDetails GhcRn -> HsType GhcRn -> IntMap HsDocString
- con_arg_docs :: Int -> [HsType GhcRn] -> IntMap HsDocString
- isValD :: HsDecl a -> Bool
- classDecls :: TyClDecl GhcRn -> [(LHsDecl GhcRn, [HsDocString])]
- declTypeDocs :: HsDecl GhcRn -> IntMap HsDocString
- nubByName :: (a -> Name) -> [a] -> [a]
- typeDocs :: HsType GhcRn -> IntMap HsDocString
- sigTypeDocs :: HsSigType GhcRn -> IntMap HsDocString
- topDecls :: HsGroup GhcRn -> [(LHsDecl GhcRn, [HsDocString])]
- ungroup :: HsGroup GhcRn -> [LHsDecl GhcRn]
- collectDocs :: forall p. UnXRec p => [LHsDecl p] -> [(LHsDecl p, [HsDocString])]
- filterDecls :: forall p doc. UnXRec p => [(LHsDecl p, doc)] -> [(LHsDecl p, doc)]
- filterClasses :: forall p doc. IsPass p => [(LHsDecl (GhcPass p), doc)] -> [(LHsDecl (GhcPass p), doc)]
- isUserSig :: Sig name -> Bool
- mkDecls :: (struct -> [GenLocated l decl]) -> (decl -> hsDecl) -> struct -> [GenLocated l hsDecl]
- extractTHDocs :: THDocs -> ExtractedTHDocs
- unionArgMaps :: Map Name (IntMap b) -> Map Name (IntMap b) -> Map Name (IntMap b)
Documentation
:: MonadIO m | |
=> TcGblEnv | |
-> m (Maybe HsDocString, DeclDocMap, ArgDocMap) |
|
Extract docs from renamer output.
This is monadic since we need to be able to read documentation added from
Template Haskell's putDoc
, which is stored in tcg_th_docs
.
mkMaps :: [Name] -> [(LHsDecl GhcRn, [HsDocString])] -> (Map Name HsDocString, Map Name (IntMap HsDocString)) Source #
Create decl and arg doc-maps by looping through the declarations. For each declaration, find its names, its subordinates, and its doc strings.
getMainDeclBinder :: (Anno (IdGhcP p) ~ SrcSpanAnnN, CollectPass (GhcPass p)) => HsDecl (GhcPass p) -> [IdP (GhcPass p)] Source #
getInstLoc :: Anno (IdGhcP p) ~ SrcSpanAnnN => InstDecl (GhcPass p) -> SrcSpan Source #
subordinates :: Map RealSrcSpan Name -> HsDecl GhcRn -> [(Name, [HsDocString], IntMap HsDocString)] Source #
Get all subordinate declarations inside a declaration, and their docs. A subordinate declaration is something like the associate type or data family of a type class.
conArgDocs :: ConDecl GhcRn -> IntMap HsDocString Source #
Extract constructor argument docs from inside constructor decls.
con_arg_docs :: Int -> [HsType GhcRn] -> IntMap HsDocString Source #
classDecls :: TyClDecl GhcRn -> [(LHsDecl GhcRn, [HsDocString])] Source #
All the sub declarations of a class (that we handle), ordered by source location, with documentation attached if it exists.
declTypeDocs :: HsDecl GhcRn -> IntMap HsDocString Source #
Extract function argument docs from inside top-level decls.
typeDocs :: HsType GhcRn -> IntMap HsDocString Source #
Extract function argument docs from inside types.
sigTypeDocs :: HsSigType GhcRn -> IntMap HsDocString Source #
Extract function argument docs from inside types.
topDecls :: HsGroup GhcRn -> [(LHsDecl GhcRn, [HsDocString])] Source #
The top-level declarations of a module that we care about, ordered by source location, with documentation attached if it exists.
ungroup :: HsGroup GhcRn -> [LHsDecl GhcRn] Source #
Take all declarations except pragmas, infix decls, rules from an HsGroup
.
collectDocs :: forall p. UnXRec p => [LHsDecl p] -> [(LHsDecl p, [HsDocString])] Source #
Collect docs and attach them to the right declarations.
A declaration may have multiple doc strings attached to it.
This is an example.
filterDecls :: forall p doc. UnXRec p => [(LHsDecl p, doc)] -> [(LHsDecl p, doc)] Source #
Filter out declarations that we don't handle in Haddock
filterClasses :: forall p doc. IsPass p => [(LHsDecl (GhcPass p), doc)] -> [(LHsDecl (GhcPass p), doc)] Source #
Go through all class declarations and filter their sub-declarations
mkDecls :: (struct -> [GenLocated l decl]) -> (decl -> hsDecl) -> struct -> [GenLocated l hsDecl] Source #
Take a field of declarations from a data structure and create HsDecls using the given constructor
extractTHDocs :: THDocs -> ExtractedTHDocs Source #
Extracts out individual maps of documentation added via Template Haskell's
putDoc
.