[commit: haddock] wip/orf-reboot: Move PostRn/PostTc family instances for DocName into Haddock.Types (0f08cc2)
git at git.haskell.org
git at git.haskell.org
Wed Jul 8 08:38:04 UTC 2015
Repository : ssh://git@git.haskell.org/haddock
On branch : wip/orf-reboot
Link : http://git.haskell.org/haddock.git/commitdiff/0f08cc2e1d4f3fb52a7b21829eb168462ef5c20a
>---------------------------------------------------------------
commit 0f08cc2e1d4f3fb52a7b21829eb168462ef5c20a
Author: Adam Gundry <adam at well-typed.com>
Date: Fri Mar 27 15:26:52 2015 +0000
Move PostRn/PostTc family instances for DocName into Haddock.Types
>---------------------------------------------------------------
0f08cc2e1d4f3fb52a7b21829eb168462ef5c20a
haddock-api/src/Haddock/Interface/Rename.hs | 12 ------------
haddock-api/src/Haddock/Types.hs | 12 ++++++++++++
2 files changed, 12 insertions(+), 12 deletions(-)
diff --git a/haddock-api/src/Haddock/Interface/Rename.hs b/haddock-api/src/Haddock/Interface/Rename.hs
index 1234d05..74a11e3 100644
--- a/haddock-api/src/Haddock/Interface/Rename.hs
+++ b/haddock-api/src/Haddock/Interface/Rename.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE TypeFamilies #-}
----------------------------------------------------------------------------
-- |
-- Module : Haddock.Interface.Rename
@@ -21,8 +20,6 @@ import Haddock.Types
import Bag (emptyBag)
import GHC hiding (NoLink)
import Name
-import NameSet
-import Coercion
import Control.Applicative
import Control.Monad hiding (mapM)
@@ -517,12 +514,3 @@ renameSub (n,doc) = do
n' <- rename n
doc' <- renameDocForDecl doc
return (n', doc')
-
-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
diff --git a/haddock-api/src/Haddock/Types.hs b/haddock-api/src/Haddock/Types.hs
index e93294a..8e0ae19 100644
--- a/haddock-api/src/Haddock/Types.hs
+++ b/haddock-api/src/Haddock/Types.hs
@@ -1,4 +1,5 @@
{-# LANGUAGE DeriveDataTypeable, DeriveFunctor, DeriveFoldable, DeriveTraversable, StandaloneDeriving #-}
+{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
-----------------------------------------------------------------------------
-- |
@@ -34,6 +35,8 @@ import GHC hiding (NoLink)
import DynFlags (ExtensionFlag, Language)
import OccName
import Outputable
+import NameSet (NameSet)
+import Coercion (Coercion)
import Control.Applicative (Applicative(..))
import Control.Monad (ap)
@@ -279,6 +282,15 @@ data DocName
-- 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
More information about the ghc-commits
mailing list