[commit: haddock] master: Create scaffolding of module for associating tokens with AST names. (d275f87)

git at git.haskell.org git at git.haskell.org
Wed Jul 8 08:40:11 UTC 2015


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

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

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

commit d275f87c4cfa1e8da042f70659331121afa9a15c
Author: Łukasz Hanuszczak <lukasz.hanuszczak at gmail.com>
Date:   Sat Jun 6 19:27:37 2015 +0200

    Create scaffolding of module for associating tokens with AST names.


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

d275f87c4cfa1e8da042f70659331121afa9a15c
 haddock-api/haddock-api.cabal                       |  1 +
 haddock-api/src/Haddock/Backends/Hyperlinker/Ast.hs | 20 ++++++++++++++++++++
 2 files changed, 21 insertions(+)

diff --git a/haddock-api/haddock-api.cabal b/haddock-api/haddock-api.cabal
index 6c6dc81..109e5f9 100644
--- a/haddock-api/haddock-api.cabal
+++ b/haddock-api/haddock-api.cabal
@@ -59,6 +59,7 @@ library
     Documentation.Haddock
     Haddock.Backends.Hyperlinker.Parser
     Haddock.Backends.Hyperlinker.Renderer
+    Haddock.Backends.Hyperlinker.Ast
 
   other-modules:
     Haddock
diff --git a/haddock-api/src/Haddock/Backends/Hyperlinker/Ast.hs b/haddock-api/src/Haddock/Backends/Hyperlinker/Ast.hs
new file mode 100644
index 0000000..abd3ca2
--- /dev/null
+++ b/haddock-api/src/Haddock/Backends/Hyperlinker/Ast.hs
@@ -0,0 +1,20 @@
+module Haddock.Backends.Hyperlinker.Ast where
+
+import qualified GHC
+
+import Haddock.Backends.Hyperlinker.Parser
+
+data RichToken = RichToken
+    { rtkToken :: Token
+    , rtkName :: Maybe GHC.Name
+    }
+
+enrich :: GHC.RenamedSource -> [Token] -> [RichToken]
+enrich src =
+    map $ \token -> RichToken
+        { rtkToken = token
+        , rtkName = lookupName src $ tkSpan token
+        }
+
+lookupName :: GHC.RenamedSource -> Span -> Maybe GHC.Name
+lookupName = undefined



More information about the ghc-commits mailing list