Skip to content

Commit

Permalink
wip: add comments
Browse files Browse the repository at this point in the history
  • Loading branch information
kokobd committed Sep 21, 2022
1 parent 88f063f commit 9a67492
Show file tree
Hide file tree
Showing 2 changed files with 16 additions and 8 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -50,7 +50,6 @@ codeActionProvider ideState _pId (CodeActionParams _ _ (TextDocumentIdentifier u
genList :: [Maybe [LHsDecl GhcPs] -> Maybe Anns -> Range -> Maybe (T.Text, TextEdit)]
genList =
[ runGenCommentsSimple genForSig,
-- runGenCommentsSimple genForRecord
runGenComments genForDataDecl
]

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -35,24 +35,33 @@ updateDataAnns decl@(L declLoc (TyClD _ DataDecl {tcdDataDefn = HsDataDefn { dd_
getAnnsT >>= (\anns -> unless (missingSomeHaddock anns cons) (lift Nothing))

-- visit each constructor and field
addHaddockCommentsToList True declLoc cons
addHaddockCommentsToList True declLoc (G AnnVbar) cons
for_ cons $ \case
L conLoc ConDeclH98 { con_args = RecCon (L _ fields) } -> addHaddockCommentsToList False conLoc fields
L conLoc ConDeclH98 { con_args = RecCon (L _ fields) } -> addHaddockCommentsToList False conLoc (G AnnComma) fields
_ -> pure ()
modifyAnnsT $ Map.adjust (\ann -> ann {annPriorComments = []}) (mkAnnKey decl)
updateDataAnns _ = pure ()
updateDataAnns _ = lift Nothing

-- TODO Add explaination to this complex function.
addHaddockCommentsToList :: (Data a, Monad m) => Bool -> SrcSpan -> [Located a] -> TransformT m ()
addHaddockCommentsToList usePrevNodeAsAnchor outerLoc nodes =
-- | Add haddock comments to a list of nodes
addHaddockCommentsToList
:: (Data a, Monad m)
=> Bool -- ^ If true, for each node, use previous node in the list as the anchor. Otherwise, use the outer node
-> SrcSpan -- ^ The outer node
-> KeywordId -- ^ The seperator between adjacent nodes
-> [Located a] -- ^ The list of nodes. Haddock comments will be added to each of them
-> TransformT m ()
addHaddockCommentsToList usePrevNodeAsAnchor outerLoc seperator nodes =
for_ (zip nodes (Nothing: fmap Just nodes)) $ \(node, prevNode) -> do
-- We don't add new ones to nodes with existing haddock comments.
addHaddockCommentToCurrentNode <- fmap (not . fromMaybe True . flip hasHaddock node) getAnnsT
when addHaddockCommentToCurrentNode $ do
-- Check if the start of 'node' is on the end line of 'prevNode'.
-- When this occurs, we do not preserve the indentation. Instead, we move the seperator to the next line
let sameLineAsPrev = maybe False (\prevNode' -> notSeperatedByLineEnding prevNode' node) prevNode
when sameLineAsPrev $ modifyAnnsT $ \anns ->
let updateSepAnn :: Annotation -> Annotation
updateSepAnn ann = ann {annsDP =
Map.toList . Map.adjust (const (DP (1,0))) (G AnnVbar) . Map.fromList $ annsDP ann}
Map.toList . Map.adjust (const (DP (1,0))) seperator . Map.fromList $ annsDP ann}
in flip (maybe anns) prevNode $ \prevNode' -> Map.adjust updateSepAnn (mkAnnKey prevNode') anns
let anchorCol = maybe 0 srcSpanStartCol . realSpan . maybe outerLoc getLoc $
if usePrevNodeAsAnchor then prevNode else Nothing
Expand Down

0 comments on commit 9a67492

Please sign in to comment.