1
+ {-# LANGUAGE BangPatterns #-}
1
2
{-# LANGUAGE RankNTypes #-}
2
3
{-# LANGUAGE ScopedTypeVariables #-}
3
4
{-# LANGUAGE RecordWildCards #-}
@@ -13,9 +14,13 @@ import Haddock.Backends.Hyperlinker.Types
13
14
import qualified GHC
14
15
15
16
import Control.Applicative
17
+ import Control.Monad (guard )
16
18
import Data.Data
19
+ import qualified Data.Map.Strict as Map
17
20
import Data.Maybe
18
21
22
+ import Prelude hiding (span )
23
+
19
24
everythingInRenamedSource :: (Alternative f , Data x )
20
25
=> (forall a . Data a => a -> f r ) -> x -> f r
21
26
everythingInRenamedSource f = Syb. everythingButType @ GHC. Name (<|>) f
@@ -28,33 +33,53 @@ enrich src =
28
33
, rtkDetails = enrichToken token detailsMap
29
34
}
30
35
where
31
- detailsMap = concatMap ($ src)
32
- [ variables
33
- , types
34
- , decls
35
- , binds
36
- , imports
37
- ]
36
+ detailsMap =
37
+ mkDetailsMap (concatMap ($ src)
38
+ [ variables
39
+ , types
40
+ , decls
41
+ , binds
42
+ , imports
43
+ ])
44
+
45
+ type LTokenDetails = [(GHC. SrcSpan , TokenDetails )]
38
46
39
47
-- | A map containing association between source locations and "details" of
40
48
-- this location.
41
49
--
42
- -- For the time being, it is just a list of pairs. However, looking up things
43
- -- in such structure has linear complexity. We cannot use any hashmap-like
44
- -- stuff because source locations are not ordered. In the future, this should
45
- -- be replaced with interval tree data structure.
46
- type DetailsMap = [(GHC. SrcSpan , TokenDetails )]
50
+ type DetailsMap = Map. Map Position (Span , TokenDetails )
51
+
52
+ mkDetailsMap :: [(GHC. SrcSpan , TokenDetails )] -> DetailsMap
53
+ mkDetailsMap xs =
54
+ Map. fromListWith select_details [ (start, (token_span, token_details))
55
+ | (ghc_span, token_details) <- xs
56
+ , Just ! token_span <- [ghcSrcSpanToSpan ghc_span]
57
+ , let start = spStart token_span
58
+ ]
59
+ where
60
+ -- favour token details which appear earlier in the list
61
+ select_details _new old = old
47
62
48
63
lookupBySpan :: Span -> DetailsMap -> Maybe TokenDetails
49
- lookupBySpan tspan = listToMaybe . map snd . filter (matches tspan . fst )
64
+ lookupBySpan span details = do
65
+ (_, (tok_span, tok_details)) <- Map. lookupLE (spStart span ) details
66
+ guard (tok_span `containsSpan` span )
67
+ return tok_details
68
+
69
+ ghcSrcSpanToSpan :: GHC. SrcSpan -> Maybe Span
70
+ ghcSrcSpanToSpan (GHC. RealSrcSpan span ) =
71
+ Just (Span { spStart = Position (GHC. srcSpanStartLine span ) (GHC. srcSpanStartCol span )
72
+ , spEnd = Position (GHC. srcSpanEndLine span ) (GHC. srcSpanEndCol span )
73
+ })
74
+ ghcSrcSpanToSpan _ = Nothing
50
75
51
76
enrichToken :: Token -> DetailsMap -> Maybe TokenDetails
52
77
enrichToken (Token typ _ spn) dm
53
78
| typ `elem` [TkIdentifier , TkOperator ] = lookupBySpan spn dm
54
79
enrichToken _ _ = Nothing
55
80
56
81
-- | Obtain details map for variables ("normally" used identifiers).
57
- variables :: GHC. RenamedSource -> DetailsMap
82
+ variables :: GHC. RenamedSource -> LTokenDetails
58
83
variables =
59
84
everythingInRenamedSource (var `Syb.combine` rec )
60
85
where
@@ -70,7 +95,7 @@ variables =
70
95
_ -> empty
71
96
72
97
-- | Obtain details map for types.
73
- types :: GHC. RenamedSource -> DetailsMap
98
+ types :: GHC. RenamedSource -> LTokenDetails
74
99
types = everythingInRenamedSource ty
75
100
where
76
101
ty term = case cast term of
@@ -84,7 +109,7 @@ types = everythingInRenamedSource ty
84
109
-- ordinary assignment (in top-level declarations, let-expressions and where
85
110
-- clauses).
86
111
87
- binds :: GHC. RenamedSource -> DetailsMap
112
+ binds :: GHC. RenamedSource -> LTokenDetails
88
113
binds = everythingInRenamedSource
89
114
(fun `Syb.combine` pat `Syb.combine` tvar)
90
115
where
@@ -112,7 +137,7 @@ binds = everythingInRenamedSource
112
137
_ -> empty
113
138
114
139
-- | Obtain details map for top-level declarations.
115
- decls :: GHC. RenamedSource -> DetailsMap
140
+ decls :: GHC. RenamedSource -> LTokenDetails
116
141
decls (group, _, _, _) = concatMap ($ group)
117
142
[ concat . map typ . concat . map GHC. group_tyclds . GHC. hs_tyclds
118
143
, everythingInRenamedSource fun . GHC. hs_valds
@@ -151,7 +176,7 @@ decls (group, _, _, _) = concatMap ($ group)
151
176
--
152
177
-- This map also includes type and variable details for items in export and
153
178
-- import lists.
154
- imports :: GHC. RenamedSource -> DetailsMap
179
+ imports :: GHC. RenamedSource -> LTokenDetails
155
180
imports src@ (_, imps, _, _) =
156
181
everythingInRenamedSource ie src ++ mapMaybe (imp . GHC. unLoc) imps
157
182
where
@@ -168,22 +193,3 @@ imports src@(_, imps, _, _) =
168
193
let (GHC. L sspan name) = GHC. ideclName idecl
169
194
in Just (sspan, RtkModule name)
170
195
imp _ = Nothing
171
-
172
- -- | Check whether token stream span matches GHC source span.
173
- --
174
- -- Currently, it is implemented as checking whether "our" span is contained
175
- -- in GHC span. The reason for that is because GHC span are generally wider
176
- -- and may spread across couple tokens. For example, @(>>=)@ consists of three
177
- -- tokens: @(@, @>>=@, @)@, but GHC source span associated with @>>=@ variable
178
- -- contains @(@ and @)@. Similarly, qualified identifiers like @Foo.Bar.quux@
179
- -- are tokenized as @Foo@, @.@, @Bar@, @.@, @quux@ but GHC source span
180
- -- associated with @quux@ contains all five elements.
181
- matches :: Span -> GHC. SrcSpan -> Bool
182
- matches tspan (GHC. RealSrcSpan aspan)
183
- | saspan <= stspan && etspan <= easpan = True
184
- where
185
- stspan = (posRow . spStart $ tspan, posCol . spStart $ tspan)
186
- etspan = (posRow . spEnd $ tspan, posCol . spEnd $ tspan)
187
- saspan = (GHC. srcSpanStartLine aspan, GHC. srcSpanStartCol aspan)
188
- easpan = (GHC. srcSpanEndLine aspan, GHC. srcSpanEndCol aspan)
189
- matches _ _ = False
0 commit comments