[commit: haddock] master: Move source paths types to hyperlinker types module. (1325460)

git at git.haskell.org git at git.haskell.org
Wed Jul 8 08:43:02 UTC 2015


Repository : ssh://git@git.haskell.org/haddock

On branch  : master
Link       : http://git.haskell.org/haddock.git/commitdiff/13254609062a16e010d1c5a24e571dfe98ab6f69

>---------------------------------------------------------------

commit 13254609062a16e010d1c5a24e571dfe98ab6f69
Author: Łukasz Hanuszczak <lukasz.hanuszczak at gmail.com>
Date:   Mon Jul 6 16:52:13 2015 +0200

    Move source paths types to hyperlinker types module.


>---------------------------------------------------------------

13254609062a16e010d1c5a24e571dfe98ab6f69
 haddock-api/src/Haddock/Backends/Hyperlinker.hs          |  2 ++
 haddock-api/src/Haddock/Backends/Hyperlinker/Renderer.hs |  1 -
 haddock-api/src/Haddock/Backends/Hyperlinker/Types.hs    | 13 +++++++++++++
 haddock-api/src/Haddock/Types.hs                         |  9 ---------
 4 files changed, 15 insertions(+), 10 deletions(-)

diff --git a/haddock-api/src/Haddock/Backends/Hyperlinker.hs b/haddock-api/src/Haddock/Backends/Hyperlinker.hs
index 4b58190..248a8a5 100644
--- a/haddock-api/src/Haddock/Backends/Hyperlinker.hs
+++ b/haddock-api/src/Haddock/Backends/Hyperlinker.hs
@@ -1,11 +1,13 @@
 module Haddock.Backends.Hyperlinker
     ( ppHyperlinkedSource
+    , module Haddock.Backends.Hyperlinker.Types
     , module Haddock.Backends.Hyperlinker.Utils
     ) where
 
 
 import Haddock.Types
 import Haddock.Backends.Hyperlinker.Renderer
+import Haddock.Backends.Hyperlinker.Types
 import Haddock.Backends.Hyperlinker.Utils
 
 import Text.XHtml hiding ((</>))
diff --git a/haddock-api/src/Haddock/Backends/Hyperlinker/Renderer.hs b/haddock-api/src/Haddock/Backends/Hyperlinker/Renderer.hs
index add1465..1065897 100644
--- a/haddock-api/src/Haddock/Backends/Hyperlinker/Renderer.hs
+++ b/haddock-api/src/Haddock/Backends/Hyperlinker/Renderer.hs
@@ -1,7 +1,6 @@
 module Haddock.Backends.Hyperlinker.Renderer (render) where
 
 
-import Haddock.Types
 import Haddock.Backends.Hyperlinker.Types
 import Haddock.Backends.Hyperlinker.Utils
 
diff --git a/haddock-api/src/Haddock/Backends/Hyperlinker/Types.hs b/haddock-api/src/Haddock/Backends/Hyperlinker/Types.hs
index 19cc528..ecb51a0 100644
--- a/haddock-api/src/Haddock/Backends/Hyperlinker/Types.hs
+++ b/haddock-api/src/Haddock/Backends/Hyperlinker/Types.hs
@@ -3,6 +3,8 @@ module Haddock.Backends.Hyperlinker.Types where
 
 import qualified GHC
 
+import Data.Map (Map)
+
 
 data Token = Token
     { tkType :: TokenType
@@ -57,3 +59,14 @@ rtkName (RtkType name) = Left name
 rtkName (RtkBind name) = Left name
 rtkName (RtkDecl name) = Left name
 rtkName (RtkModule name) = Right name
+
+
+-- | Path for making cross-package hyperlinks in generated sources.
+--
+-- Used in 'SrcMap' to determine whether module originates in current package
+-- or in an external package.
+data SrcPath
+  = SrcExternal FilePath
+  | SrcLocal
+
+type SrcMap = Map GHC.Module SrcPath
diff --git a/haddock-api/src/Haddock/Types.hs b/haddock-api/src/Haddock/Types.hs
index 90dbb4d..6dd6450 100644
--- a/haddock-api/src/Haddock/Types.hs
+++ b/haddock-api/src/Haddock/Types.hs
@@ -51,7 +51,6 @@ type SubMap        = Map Name [Name]
 type DeclMap       = Map Name [LHsDecl Name]
 type InstMap       = Map SrcSpan Name
 type FixMap        = Map Name Fixity
-type SrcMap        = Map Module SrcPath
 type DocPaths      = (FilePath, Maybe FilePath) -- paths to HTML and sources
 
 
@@ -272,14 +271,6 @@ unrenameDocForDecl (doc, fnArgsDoc) =
 -- | Type of environment used to cross-reference identifiers in the syntax.
 type LinkEnv = Map Name Module
 
--- | Path for making cross-package hyperlinks in generated sources.
---
--- Used in 'SrcMap' to determine whether module originates in current package
--- or in an external package.
-data SrcPath
-  = SrcExternal FilePath
-  | SrcLocal
-
 -- | Extends 'Name' with cross-reference information.
 data DocName
   = Documented Name Module



More information about the ghc-commits mailing list