aboutsummaryrefslogtreecommitdiff
path: root/haddock-api/src/Haddock/Backends/Hoogle.hs
diff options
context:
space:
mode:
Diffstat (limited to 'haddock-api/src/Haddock/Backends/Hoogle.hs')
-rw-r--r--haddock-api/src/Haddock/Backends/Hoogle.hs17
1 files changed, 8 insertions, 9 deletions
diff --git a/haddock-api/src/Haddock/Backends/Hoogle.hs b/haddock-api/src/Haddock/Backends/Hoogle.hs
index c5a0f772..c114e84d 100644
--- a/haddock-api/src/Haddock/Backends/Hoogle.hs
+++ b/haddock-api/src/Haddock/Backends/Hoogle.hs
@@ -1,5 +1,6 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeFamilies #-}
+{-# OPTIONS_GHC -Wno-incomplete-record-updates #-}
-----------------------------------------------------------------------------
-- |
-- Module : Haddock.Backends.Hoogle
@@ -37,8 +38,6 @@ import Data.Version
import System.Directory
import System.FilePath
-import GHC.Core.Multiplicity
-
prefix :: [String]
prefix = ["-- Hoogle documentation, generated by Haddock"
,"-- See Hoogle, http://www.haskell.org/hoogle/"
@@ -85,7 +84,7 @@ dropHsDocTy = f
f (HsOpTy x a b c) = HsOpTy x (g a) b (g c)
f (HsParTy x a) = HsParTy x (g a)
f (HsKindSig x a b) = HsKindSig x (g a) b
- f (HsDocTy _ a _) = f $ unL a
+ f (HsDocTy _ a _) = f $ unLoc a
f x = x
outHsType :: (OutputableBndrId p)
@@ -217,7 +216,7 @@ ppSynonym dflags x = [out dflags x]
ppData :: DynFlags -> TyClDecl GhcRn -> [(Name, DocForDecl Name)] -> [String]
ppData dflags decl@(DataDecl { tcdDataDefn = defn }) subdocs
= showData decl{ tcdDataDefn = defn { dd_cons=[],dd_derivs=noLoc [] }} :
- concatMap (ppCtor dflags decl subdocs . unL) (dd_cons defn)
+ concatMap (ppCtor dflags decl subdocs . unLoc) (dd_cons defn)
where
-- GHC gives out "data Bar =", we want to delete the equals.
@@ -253,7 +252,7 @@ ppCtor dflags dat subdocs con@ConDeclH98 {}
-- We print the constructors as comma-separated list. See GHC
-- docs for con_names on why it is a list to begin with.
- name = commaSeparate dflags . map unL $ getConNames con
+ name = commaSeparate dflags . map unLoc $ getConNames con
tyVarArg (UserTyVar _ _ n) = HsTyVar noExtField NotPromoted n
tyVarArg (KindedTyVar _ _ n lty) = HsKindSig noExtField (reL (HsTyVar noExtField NotPromoted n)) lty
@@ -268,8 +267,8 @@ ppCtor dflags _dat subdocs con@(ConDeclGADT { })
where
f = [typeSig name (getGADTConTypeG con)]
- typeSig nm ty = operator nm ++ " :: " ++ outHsType dflags (unL ty)
- name = out dflags $ map unL $ getConNames con
+ typeSig nm ty = operator nm ++ " :: " ++ outHsType dflags (unLoc ty)
+ name = out dflags $ map unLoc $ getConNames con
ppFixity :: DynFlags -> (Name, Fixity) -> [String]
ppFixity dflags (name, fixity) = [out dflags ((FixitySig noExtField [noLoc name] fixity) :: FixitySig GhcRn)]
@@ -298,7 +297,7 @@ docWith dflags header d
mkSubdoc :: DynFlags -> Located Name -> [(Name, DocForDecl Name)] -> [String] -> [String]
mkSubdoc dflags n subdocs s = concatMap (ppDocumentation dflags) getDoc ++ s
where
- getDoc = maybe [] (return . fst) (lookup (unL n) subdocs)
+ getDoc = maybe [] (return . fst) (lookup (unLoc n) subdocs)
data Tag = TagL Char [Tags] | TagP Tags | TagPre Tags | TagInline String Tags | Str String
deriving Show
@@ -325,7 +324,7 @@ markupTag dflags = Markup {
markupString = str,
markupAppend = (++),
markupIdentifier = box (TagInline "a") . str . out dflags,
- markupIdentifierUnchecked = box (TagInline "a") . str . out dflags . snd,
+ markupIdentifierUnchecked = box (TagInline "a") . str . showWrapped (out dflags . snd),
markupModule = box (TagInline "a") . str,
markupWarning = box (TagInline "i"),
markupEmphasis = box (TagInline "i"),