Safe Haskell | None |
---|---|
Language | Haskell2010 |
Extract docs from the renamer output so they can be serialized.
Synopsis
- extractDocs :: TcGblEnv -> (Maybe HsDocString, DeclDocMap, ArgDocMap)
- mkMaps :: [Name] -> [(LHsDecl GhcRn, [HsDocString])] -> (Map Name HsDocString, Map Name (Map Int HsDocString))
- getMainDeclBinder :: CollectPass (GhcPass p) => HsDecl (GhcPass p) -> [IdP (GhcPass p)]
- sigNameNoLoc :: Sig pass -> [IdP pass]
- getInstLoc :: InstDecl (GhcPass p) -> SrcSpan
- subordinates :: Map RealSrcSpan Name -> HsDecl GhcRn -> [(Name, [HsDocString], Map Int HsDocString)]
- conArgDocs :: ConDecl GhcRn -> Map Int HsDocString
- isValD :: HsDecl a -> Bool
- classDecls :: TyClDecl GhcRn -> [(LHsDecl GhcRn, [HsDocString])]
- declTypeDocs :: HsDecl GhcRn -> Map Int HsDocString
- nubByName :: (a -> Name) -> [a] -> [a]
- typeDocs :: HsType GhcRn -> Map Int HsDocString
- topDecls :: HsGroup GhcRn -> [(LHsDecl GhcRn, [HsDocString])]
- ungroup :: HsGroup GhcRn -> [LHsDecl GhcRn]
- collectDocs :: [LHsDecl pass] -> [(LHsDecl pass, [HsDocString])]
- filterDecls :: [(LHsDecl a, doc)] -> [(LHsDecl a, doc)]
- filterClasses :: [(LHsDecl a, doc)] -> [(LHsDecl a, doc)]
- isUserSig :: Sig name -> Bool
- mkDecls :: (struct -> [Located decl]) -> (decl -> hsDecl) -> struct -> [Located hsDecl]
Documentation
:: TcGblEnv | |
-> (Maybe HsDocString, DeclDocMap, ArgDocMap) |
|
Extract docs from renamer output.
mkMaps :: [Name] -> [(LHsDecl GhcRn, [HsDocString])] -> (Map Name HsDocString, Map Name (Map Int 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 :: CollectPass (GhcPass p) => HsDecl (GhcPass p) -> [IdP (GhcPass p)] Source #
sigNameNoLoc :: Sig pass -> [IdP pass] Source #
subordinates :: Map RealSrcSpan Name -> HsDecl GhcRn -> [(Name, [HsDocString], Map Int 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 -> Map Int HsDocString Source #
Extract constructor argument docs from inside constructor decls.
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 -> Map Int HsDocString Source #
Extract function argument docs from inside top-level decls.
typeDocs :: HsType GhcRn -> Map Int 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 :: [LHsDecl pass] -> [(LHsDecl pass, [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 :: [(LHsDecl a, doc)] -> [(LHsDecl a, doc)] Source #
Filter out declarations that we don't handle in Haddock
filterClasses :: [(LHsDecl a, doc)] -> [(LHsDecl a, doc)] Source #
Go through all class declarations and filter their sub-declarations