[commit: haddock] wip/orf-reboot: Merge remote-tracking branch 'github/ghc-head' into wip/orf-reboot (637b695)
git at git.haskell.org
git at git.haskell.org
Wed Jul 8 08:39:26 UTC 2015
Repository : ssh://git@git.haskell.org/haddock
On branch : wip/orf-reboot
Link : http://git.haskell.org/haddock.git/commitdiff/637b695e6a72083d81748af56c667b8e83d977fd
>---------------------------------------------------------------
commit 637b695e6a72083d81748af56c667b8e83d977fd
Merge: d137dae 553c719
Author: Adam Gundry <adam at well-typed.com>
Date: Mon Jun 15 16:59:56 2015 +0100
Merge remote-tracking branch 'github/ghc-head' into wip/orf-reboot
Conflicts:
haddock-api/src/Haddock/Types.hs
>---------------------------------------------------------------
637b695e6a72083d81748af56c667b8e83d977fd
haddock-api/src/Haddock/Backends/LaTeX.hs | 12 +++++---
haddock-api/src/Haddock/Backends/Xhtml.hs | 4 +--
haddock-api/src/Haddock/Backends/Xhtml/Decl.hs | 16 +++++-----
haddock-api/src/Haddock/Convert.hs | 21 ++++++++-----
haddock-api/src/Haddock/Interface/Create.hs | 6 ++--
haddock-api/src/Haddock/Interface/LexParseRn.hs | 3 +-
haddock-api/src/Haddock/Interface/Rename.hs | 9 ++++--
haddock-api/src/Haddock/ModuleTree.hs | 41 +++++++++++++------------
haddock-api/src/Haddock/Types.hs | 28 +++++++++--------
9 files changed, 80 insertions(+), 60 deletions(-)
diff --cc haddock-api/src/Haddock/Backends/LaTeX.hs
index 08f94db,e1090a0..6b4c541
--- a/haddock-api/src/Haddock/Backends/LaTeX.hs
+++ b/haddock-api/src/Haddock/Backends/LaTeX.hs
@@@ -898,9 -898,11 +898,11 @@@ ppr_mono_ty :: Int -> HsType DocName -
ppr_mono_ty ctxt_prec (HsForAllTy expl extra tvs ctxt ty) unicode
= maybeParen ctxt_prec pREC_FUN $
hsep [ppForAll expl tvs ctxt' unicode, ppr_mono_lty pREC_TOP ty unicode]
- where ctxt' = case extra of
- Just loc -> (++ [L loc HsWildcardTy]) `fmap` ctxt
- Nothing -> ctxt
+ where
- anonWC = HsWildCardTy (AnonWildCard PlaceHolder)
++ anonWC = HsWildCardTy (AnonWildCard (error "ppr_mono_ty: anonWC")) -- AMG TODO is this okay?
+ ctxt'
+ | Just loc <- extra = (++ [L loc anonWC]) `fmap` ctxt
+ | otherwise = ctxt
ppr_mono_ty _ (HsBangTy b ty) u = ppBang b <> ppLParendType u ty
ppr_mono_ty _ (HsTyVar name) _ = ppDocName name
diff --cc haddock-api/src/Haddock/Backends/Xhtml/Decl.hs
index aadfd7a,c0be973..fd3f534
--- a/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs
+++ b/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs
@@@ -852,9 -852,11 +852,11 @@@ ppr_mono_ty :: Int -> HsType DocName -
ppr_mono_ty ctxt_prec (HsForAllTy expl extra tvs ctxt ty) unicode qual
= maybeParen ctxt_prec pREC_FUN $ ppForAllCon expl tvs ctxt' unicode qual
<+> ppr_mono_lty pREC_TOP ty unicode qual
- where ctxt' = case extra of
- Just loc -> (++ [L loc HsWildcardTy]) `fmap` ctxt
- Nothing -> ctxt
+ where
- anonWC = HsWildCardTy (AnonWildCard PlaceHolder)
++ anonWC = HsWildCardTy (AnonWildCard (error "ppr_mono_ty: anonWC")) -- AMG TODO ?
+ ctxt'
+ | Just loc <- extra = (++ [L loc anonWC]) `fmap` ctxt
+ | otherwise = ctxt
-- UnicodeSyntax alternatives
ppr_mono_ty _ (HsTyVar name) True _
diff --cc haddock-api/src/Haddock/Interface/Rename.hs
index 5b1788f,2b50ce9..1b01b71
--- a/haddock-api/src/Haddock/Interface/Rename.hs
+++ b/haddock-api/src/Haddock/Interface/Rename.hs
@@@ -254,6 -253,10 +253,10 @@@ renameLContext (L loc context) = d
context' <- mapM renameLType context
return (L loc context')
+ renameWildCardInfo :: HsWildCardInfo Name -> RnM (HsWildCardInfo DocName)
-renameWildCardInfo (AnonWildCard _) = pure (AnonWildCard PlaceHolder)
++renameWildCardInfo (AnonWildCard name) = AnonWildCard <$> rename name
+ renameWildCardInfo (NamedWildCard name) = NamedWildCard <$> rename name
+
renameInstHead :: InstHead Name -> RnM (InstHead DocName)
renameInstHead (className, k, types, rest) = do
className' <- rename className
diff --cc haddock-api/src/Haddock/Types.hs
index 8e0ae19,847320a..63dd666
--- a/haddock-api/src/Haddock/Types.hs
+++ b/haddock-api/src/Haddock/Types.hs
@@@ -282,16 -281,7 +281,6 @@@ data DocNam
-- documentation, as far as Haddock knows.
deriving Eq
- type instance PostRn DocName Name = DocName
- type instance PostRn DocName NameSet = PlaceHolder
- type instance PostRn DocName Fixity = PlaceHolder
- type instance PostRn DocName Bool = PlaceHolder
- type instance PostRn DocName [Name] = PlaceHolder
-
- type instance PostTc DocName Kind = PlaceHolder
- type instance PostTc DocName Type = PlaceHolder
- type instance PostTc DocName Coercion = PlaceHolder
--
instance NamedThing DocName where
getName (Documented name _) = name
getName (Undocumented name) = name
@@@ -563,3 -553,18 +552,18 @@@ instance Monad ErrMsgGhc wher
return a = WriterGhc (return (a, []))
m >>= k = WriterGhc $ runWriterGhc m >>= \ (a, msgs1) ->
fmap (second (msgs1 ++)) (runWriterGhc (k a))
+
+
+ -----------------------------------------------------------------------------
+ -- * Pass sensitive types
+ -----------------------------------------------------------------------------
+
+ type instance PostRn DocName NameSet = PlaceHolder
+ type instance PostRn DocName Fixity = PlaceHolder
+ type instance PostRn DocName Bool = PlaceHolder
-type instance PostRn DocName Name = PlaceHolder
++type instance PostRn DocName Name = DocName
+ type instance PostRn DocName [Name] = PlaceHolder
+
+ type instance PostTc DocName Kind = PlaceHolder
+ type instance PostTc DocName Type = PlaceHolder
+ type instance PostTc DocName Coercion = PlaceHolder
More information about the ghc-commits
mailing list