@@ -55,6 +55,7 @@ import GHC.Tc.Types
55
55
import GHC.Data.FastString ( unpackFS , bytesFS )
56
56
import GHC.Types.Basic ( StringLiteral (.. ), SourceText (.. ), PromotionFlag (.. ) )
57
57
import qualified GHC.Utils.Outputable as O
58
+ import GHC.HsToCore.Docs hiding (mkMaps )
58
59
59
60
60
61
-- | Use a 'TypecheckedModule' to produce an 'Interface'.
@@ -437,105 +438,6 @@ mkMaps dflags pkgName gre instances decls = do
437
438
-- | Get all subordinate declarations inside a declaration, and their docs.
438
439
-- A subordinate declaration is something like the associate type or data
439
440
-- family of a type class.
440
- subordinates :: InstMap
441
- -> HsDecl GhcRn
442
- -> [(Name , [HsDocString ], Map Int HsDocString )]
443
- subordinates instMap decl = case decl of
444
- InstD _ (ClsInstD _ d) -> do
445
- DataFamInstDecl { dfid_eqn = HsIB { hsib_body =
446
- FamEqn { feqn_tycon = L l _
447
- , feqn_rhs = defn }}} <- unLoc <$> cid_datafam_insts d
448
- [ (n, [] , M. empty) | Just n <- [SrcLoc. lookupSrcSpan l instMap] ] ++ dataSubs defn
449
-
450
- InstD _ (DataFamInstD _ (DataFamInstDecl (HsIB { hsib_body = d })))
451
- -> dataSubs (feqn_rhs d)
452
- TyClD _ d | isClassDecl d -> classSubs d
453
- | isDataDecl d -> dataSubs (tcdDataDefn d)
454
- _ -> []
455
- where
456
- classSubs dd = [ (name, doc, declTypeDocs d) | (L _ d, doc) <- classDecls dd
457
- , name <- getMainDeclBinder d, not (isValD d)
458
- ]
459
- dataSubs :: HsDataDefn GhcRn -> [(Name , [HsDocString ], Map Int HsDocString )]
460
- dataSubs dd = constrs ++ fields ++ derivs
461
- where
462
- cons = map unL $ (dd_cons dd)
463
- constrs = [ (unL cname, maybeToList $ fmap unL $ con_doc c, conArgDocs c)
464
- | c <- cons, cname <- getConNames c ]
465
- fields = [ (extFieldOcc n, maybeToList $ fmap unL doc, M. empty)
466
- | RecCon flds <- map getConArgs cons
467
- , L _ (ConDeclField _ ns _ doc) <- (unLoc flds)
468
- , L _ n <- ns ]
469
- derivs = [ (instName, [unL doc], M. empty)
470
- | (l, doc) <- mapMaybe (extract_deriv_ty . hsib_body) $
471
- concatMap (unLoc . deriv_clause_tys . unLoc) $
472
- unLoc $ dd_derivs dd
473
- , Just instName <- [SrcLoc. lookupSrcSpan l instMap] ]
474
-
475
- extract_deriv_ty :: LHsType GhcRn -> Maybe (SrcSpan , LHsDocString )
476
- extract_deriv_ty (L l ty) =
477
- case ty of
478
- -- deriving (forall a. C a {- ^ Doc comment -})
479
- HsForAllTy { hst_fvf = ForallInvis
480
- , hst_body = L _ (HsDocTy _ _ doc) }
481
- -> Just (l, doc)
482
- -- deriving (C a {- ^ Doc comment -})
483
- HsDocTy _ _ doc -> Just (l, doc)
484
- _ -> Nothing
485
-
486
- -- | Extract constructor argument docs from inside constructor decls.
487
- conArgDocs :: ConDecl GhcRn -> Map Int HsDocString
488
- conArgDocs con = case getConArgs con of
489
- PrefixCon args -> go 0 (map unLoc args ++ ret)
490
- InfixCon arg1 arg2 -> go 0 ([unLoc arg1, unLoc arg2] ++ ret)
491
- RecCon _ -> go 1 ret
492
- where
493
- go n (HsDocTy _ _ (L _ ds) : tys) = M. insert n ds $ go (n+ 1 ) tys
494
- go n (HsBangTy _ _ (L _ (HsDocTy _ _ (L _ ds))) : tys) = M. insert n ds $ go (n+ 1 ) tys
495
- go n (_ : tys) = go (n+ 1 ) tys
496
- go _ [] = M. empty
497
-
498
- ret = case con of
499
- ConDeclGADT { con_res_ty = res_ty } -> [ unLoc res_ty ]
500
- _ -> []
501
-
502
- -- | Extract function argument docs from inside top-level decls.
503
- declTypeDocs :: HsDecl GhcRn -> Map Int HsDocString
504
- declTypeDocs (SigD _ (TypeSig _ _ ty)) = typeDocs (unLoc (hsSigWcType ty))
505
- declTypeDocs (SigD _ (ClassOpSig _ _ _ ty)) = typeDocs (unLoc (hsSigType ty))
506
- declTypeDocs (SigD _ (PatSynSig _ _ ty)) = typeDocs (unLoc (hsSigType ty))
507
- declTypeDocs (ForD _ (ForeignImport _ _ ty _)) = typeDocs (unLoc (hsSigType ty))
508
- declTypeDocs (TyClD _ (SynDecl { tcdRhs = ty })) = typeDocs (unLoc ty)
509
- declTypeDocs _ = M. empty
510
-
511
- -- | Extract function argument docs from inside types.
512
- typeDocs :: HsType GhcRn -> Map Int HsDocString
513
- typeDocs = go 0
514
- where
515
- go n (HsForAllTy { hst_body = ty }) = go n (unLoc ty)
516
- go n (HsQualTy { hst_body = ty }) = go n (unLoc ty)
517
- go n (HsFunTy _ (L _ (HsDocTy _ _ (L _ x))) (L _ ty)) = M. insert n x $ go (n+ 1 ) ty
518
- go n (HsFunTy _ _ ty) = go (n+ 1 ) (unLoc ty)
519
- go n (HsDocTy _ _ (L _ doc)) = M. singleton n doc
520
- go _ _ = M. empty
521
-
522
- -- | All the sub declarations of a class (that we handle), ordered by
523
- -- source location, with documentation attached if it exists.
524
- classDecls :: TyClDecl GhcRn -> [(LHsDecl GhcRn , [HsDocString ])]
525
- classDecls class_ = filterDecls . collectDocs . SrcLoc. sortLocated $ decls
526
- where
527
- decls = docs ++ defs ++ sigs ++ ats
528
- docs = mkDecls tcdDocs (DocD noExtField) class_
529
- defs = mkDecls (bagToList . tcdMeths) (ValD noExtField) class_
530
- sigs = mkDecls tcdSigs (SigD noExtField) class_
531
- ats = mkDecls tcdATs (TyClD noExtField . FamDecl noExtField) class_
532
-
533
-
534
- -- | The top-level declarations of a module that we care about,
535
- -- ordered by source location, with documentation attached if it exists.
536
- topDecls :: HsGroup GhcRn -> [(LHsDecl GhcRn , [HsDocString ])]
537
- topDecls =
538
- filterClasses . filterDecls . collectDocs . SrcLoc. sortLocated . ungroup
539
441
540
442
-- | Extract a map of fixity declarations only
541
443
mkFixMap :: HsGroup GhcRn -> FixMap
@@ -545,86 +447,6 @@ mkFixMap group_ =
545
447
L _ n <- ns ]
546
448
547
449
548
- -- | Take all declarations except pragmas, infix decls, rules from an 'HsGroup'.
549
- ungroup :: HsGroup GhcRn -> [LHsDecl GhcRn ]
550
- ungroup group_ =
551
- mkDecls (tyClGroupTyClDecls . hs_tyclds) (TyClD noExtField) group_ ++
552
- mkDecls hs_derivds (DerivD noExtField) group_ ++
553
- mkDecls hs_defds (DefD noExtField) group_ ++
554
- mkDecls hs_fords (ForD noExtField) group_ ++
555
- mkDecls hs_docs (DocD noExtField) group_ ++
556
- mkDecls (tyClGroupInstDecls . hs_tyclds) (InstD noExtField) group_ ++
557
- mkDecls (typesigs . hs_valds) (SigD noExtField) group_ ++
558
- mkDecls (valbinds . hs_valds) (ValD noExtField) group_
559
- where
560
- typesigs (XValBindsLR (NValBinds _ sigs)) = filter isUserLSig sigs
561
- typesigs _ = error " expected ValBindsOut"
562
-
563
- valbinds (XValBindsLR (NValBinds binds _)) = concatMap bagToList . snd . unzip $ binds
564
- valbinds _ = error " expected ValBindsOut"
565
-
566
-
567
- -- | Take a field of declarations from a data structure and create HsDecls
568
- -- using the given constructor
569
- mkDecls :: (a -> [Located b ]) -> (b -> c ) -> a -> [Located c ]
570
- mkDecls field con struct = [ L loc (con decl) | L loc decl <- field struct ]
571
-
572
- --------------------------------------------------------------------------------
573
- -- Filtering of declarations
574
- --
575
- -- We filter out declarations that we don't intend to handle later.
576
- --------------------------------------------------------------------------------
577
-
578
-
579
- -- | Filter out declarations that we don't handle in Haddock
580
- filterDecls :: [(LHsDecl a , doc )] -> [(LHsDecl a , doc )]
581
- filterDecls = filter (isHandled . unL . fst )
582
- where
583
- isHandled (ForD _ (ForeignImport {})) = True
584
- isHandled (TyClD {}) = True
585
- isHandled (InstD {}) = True
586
- isHandled (DerivD {}) = True
587
- isHandled (SigD _ d) = isUserLSig (reL d)
588
- isHandled (ValD {}) = True
589
- -- we keep doc declarations to be able to get at named docs
590
- isHandled (DocD {}) = True
591
- isHandled _ = False
592
-
593
- -- | Go through all class declarations and filter their sub-declarations
594
- filterClasses :: [(LHsDecl a , doc )] -> [(LHsDecl a , doc )]
595
- filterClasses decls = [ if isClassD d then (L loc (filterClass d), doc) else x
596
- | x@ (L loc d, doc) <- decls ]
597
- where
598
- filterClass (TyClD x c) =
599
- TyClD x $ c { tcdSigs = filter (liftA2 (||) isUserLSig isMinimalLSig) $ tcdSigs c }
600
- filterClass _ = error " expected TyClD"
601
-
602
-
603
- --------------------------------------------------------------------------------
604
- -- Collect docs
605
- --
606
- -- To be able to attach the right Haddock comment to the right declaration,
607
- -- we sort the declarations by their SrcLoc and "collect" the docs for each
608
- -- declaration.
609
- --------------------------------------------------------------------------------
610
-
611
-
612
- -- | Collect docs and attach them to the right declarations.
613
- collectDocs :: [LHsDecl a ] -> [(LHsDecl a , [HsDocString ])]
614
- collectDocs = go Nothing []
615
- where
616
- go Nothing _ [] = []
617
- go (Just prev) docs [] = finished prev docs []
618
- go prev docs (L _ (DocD _ (DocCommentNext str)) : ds)
619
- | Nothing <- prev = go Nothing (str: docs) ds
620
- | Just decl <- prev = finished decl docs (go Nothing [str] ds)
621
- go prev docs (L _ (DocD _ (DocCommentPrev str)) : ds) = go prev (str: docs) ds
622
- go Nothing docs (d: ds) = go (Just d) docs ds
623
- go (Just prev) docs (d: ds) = finished prev docs (go (Just d) [] ds)
624
-
625
- finished decl docs rest = (decl, reverse docs) : rest
626
-
627
-
628
450
-- | Build the list of items that will become the documentation, from the
629
451
-- export list. At this point, the list of ExportItems is in terms of
630
452
-- original names.
0 commit comments