diff options
Diffstat (limited to 'haddock-api')
| -rw-r--r-- | haddock-api/src/Haddock/Backends/Hoogle.hs | 4 | ||||
| -rw-r--r-- | haddock-api/src/Haddock/Backends/LaTeX.hs | 4 | ||||
| -rw-r--r-- | haddock-api/src/Haddock/Backends/Xhtml/Decl.hs | 6 | ||||
| -rw-r--r-- | haddock-api/src/Haddock/GhcUtils.hs | 4 | ||||
| -rw-r--r-- | haddock-api/src/Haddock/Interface/Create.hs | 4 | 
5 files changed, 11 insertions, 11 deletions
| diff --git a/haddock-api/src/Haddock/Backends/Hoogle.hs b/haddock-api/src/Haddock/Backends/Hoogle.hs index 3f913e09..38d378e2 100644 --- a/haddock-api/src/Haddock/Backends/Hoogle.hs +++ b/haddock-api/src/Haddock/Backends/Hoogle.hs @@ -247,8 +247,8 @@ ppCtor dflags dat subdocs con@ConDeclH98 { con_args = con_args' }          f (PrefixCon _ args) = [typeSig name $ (map hsScaledThing args) ++ [resType]]          f (InfixCon a1 a2) = f $ PrefixCon [] [a1,a2]          f (RecCon (L _ recs)) = f (PrefixCon [] $ map (hsLinear . cd_fld_type . unLoc) recs) ++ concat -                          [(concatMap (lookupCon dflags subdocs . noLocA . extFieldOcc . unLoc) (cd_fld_names r)) ++ -                           [out dflags (map (extFieldOcc . unLoc) $ cd_fld_names r) `typeSig` [resType, cd_fld_type r]] +                          [(concatMap (lookupCon dflags subdocs . noLocA . foExt . unLoc) (cd_fld_names r)) ++ +                           [out dflags (map (foExt . unLoc) $ cd_fld_names r) `typeSig` [resType, cd_fld_type r]]                            | r <- map unLoc recs]          funs = foldr1 (\x y -> reL $ HsFunTy noAnn (HsUnrestrictedArrow NormalSyntax) x y) diff --git a/haddock-api/src/Haddock/Backends/LaTeX.hs b/haddock-api/src/Haddock/Backends/LaTeX.hs index fbae13a3..c7ba5a80 100644 --- a/haddock-api/src/Haddock/Backends/LaTeX.hs +++ b/haddock-api/src/Haddock/Backends/LaTeX.hs @@ -887,12 +887,12 @@ ppSideBySideConstr subdocs unicode leader (L _ con) =  -- | Pretty-print a record field  ppSideBySideField :: [(DocName, DocForDecl DocName)] -> Bool -> ConDeclField DocNameI ->  LaTeX  ppSideBySideField subdocs unicode (ConDeclField _ names ltype _) = -  decltt (cat (punctuate comma (map (ppBinder . rdrNameOcc . unLoc . rdrNameFieldOcc . unLoc) names)) +  decltt (cat (punctuate comma (map (ppBinder . rdrNameOcc . unLoc . foLabel . unLoc) names))      <+> dcolon unicode <+> ppLType unicode ltype) <-> rDoc mbDoc    where      -- don't use cd_fld_doc for same reason we don't use con_doc above      -- Where there is more than one name, they all have the same documentation -    mbDoc = lookup (extFieldOcc $ unLoc $ head names) subdocs >>= fmap _doc . combineDocumentation . fst +    mbDoc = lookup (foExt $ unLoc $ head names) subdocs >>= fmap _doc . combineDocumentation . fst  -- | Pretty-print a bundled pattern synonym diff --git a/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs b/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs index 8ac1ac81..994b5d0d 100644 --- a/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs +++ b/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs @@ -1027,7 +1027,7 @@ ppSideBySideField :: [(DocName, DocForDecl DocName)] -> Unicode -> Qualification  ppSideBySideField subdocs unicode qual (ConDeclField _ names ltype _) =    ( hsep (punctuate comma [ ppBinder False (rdrNameOcc field)                            | L _ name <- names -                          , let field = (unLoc . rdrNameFieldOcc) name +                          , let field = (unLoc . foLabel) name                            ])        <+> dcolon unicode        <+> ppLType unicode qual HideEmptyContexts ltype @@ -1037,12 +1037,12 @@ ppSideBySideField subdocs unicode qual (ConDeclField _ names ltype _) =    where      -- don't use cd_fld_doc for same reason we don't use con_doc above      -- Where there is more than one name, they all have the same documentation -    mbDoc = lookup (extFieldOcc $ unLoc $ head names) subdocs >>= combineDocumentation . fst +    mbDoc = lookup (foExt $ unLoc $ head names) subdocs >>= combineDocumentation . fst  ppShortField :: Bool -> Unicode -> Qualification -> ConDeclField DocNameI -> Html  ppShortField summary unicode qual (ConDeclField _ names ltype _) -  = hsep (punctuate comma (map ((ppBinder summary) . rdrNameOcc . unLoc . rdrNameFieldOcc . unLoc) names)) +  = hsep (punctuate comma (map ((ppBinder summary) . rdrNameOcc . unLoc . foLabel . unLoc) names))      <+> dcolon unicode <+> ppLType unicode qual HideEmptyContexts ltype diff --git a/haddock-api/src/Haddock/GhcUtils.hs b/haddock-api/src/Haddock/GhcUtils.hs index 9353708a..fa567da8 100644 --- a/haddock-api/src/Haddock/GhcUtils.hs +++ b/haddock-api/src/Haddock/GhcUtils.hs @@ -290,7 +290,7 @@ restrictCons names decls = [ L p d | L p (Just d) <- map (fmap keep) decls ]        where          field_avail :: LConDeclField GhcRn -> Bool          field_avail (L _ (ConDeclField _ fs _ _)) -            = all (\f -> extFieldOcc (unLoc f) `elem` names) fs +            = all (\f -> foExt (unLoc f) `elem` names) fs          field_types flds = [ hsUnrestricted t | L _ (ConDeclField _ _ t _) <- flds ] @@ -466,7 +466,7 @@ instance Parent (ConDecl GhcRn) where    children con =      case getRecConArgs_maybe con of        Nothing -> [] -      Just flds -> map (extFieldOcc . unLoc) $ concatMap (cd_fld_names . unLoc) (unLoc flds) +      Just flds -> map (foExt . unLoc) $ concatMap (cd_fld_names . unLoc) (unLoc flds)  instance Parent (TyClDecl GhcRn) where    children d diff --git a/haddock-api/src/Haddock/Interface/Create.hs b/haddock-api/src/Haddock/Interface/Create.hs index 4f689532..2d79bb97 100644 --- a/haddock-api/src/Haddock/Interface/Create.hs +++ b/haddock-api/src/Haddock/Interface/Create.hs @@ -1113,7 +1113,7 @@ extractDecl declMap name decl                                 , Just rec <- map (getRecConArgs_maybe . unLoc) (dd_cons (feqn_rhs d))                                 , ConDeclField { cd_fld_names = ns } <- map unLoc (unLoc rec)                                 , L _ n <- ns -                               , extFieldOcc n == name +                               , foExt n == name                            ]              in case matches of                [d0] -> extractDecl declMap name (noLocA . InstD noExtField $ DataFamInstD noExtField d0) @@ -1174,7 +1174,7 @@ extractRecSel nm t tvs (L _ con : rest) =   where    matching_fields :: [LConDeclField GhcRn] -> [(SrcSpan, LConDeclField GhcRn)]    matching_fields flds = [ (l,f) | f@(L _ (ConDeclField _ ns _ _)) <- flds -                                 , L l n <- ns, extFieldOcc n == nm ] +                                 , L l n <- ns, foExt n == nm ]    data_ty      -- ResTyGADT _ ty <- con_res con = ty      | ConDeclGADT{} <- con = con_res_ty con | 
