-
Notifications
You must be signed in to change notification settings - Fork 83
/
Copy pathInternal.hs
321 lines (293 loc) · 9.86 KB
/
Internal.hs
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ViewPatterns #-}
module Ormolu.Fixity.Internal
( OpName,
pattern OpName,
unOpName,
occOpName,
FixityDirection (..),
FixityInfo (..),
colonFixityInfo,
defaultFixityInfo,
FixityApproximation (..),
defaultFixityApproximation,
HackageInfo (..),
FixityOverrides (..),
defaultFixityOverrides,
ModuleReexports (..),
defaultModuleReexports,
PackageFixityMap (..),
ModuleFixityMap (..),
FixityProvenance (..),
FixityQualification (..),
inferFixity,
)
where
import Control.DeepSeq (NFData)
import Data.Binary (Binary)
import Data.ByteString.Short (ShortByteString)
import Data.ByteString.Short qualified as SBS
import Data.Choice (Choice)
import Data.Choice qualified as Choice
import Data.List.NonEmpty (NonEmpty (..))
import Data.List.NonEmpty qualified as NE
import Data.Map.Strict (Map)
import Data.Map.Strict qualified as Map
import Data.Maybe (fromMaybe)
import Data.String (IsString (..))
import Data.Text (Text)
import Data.Text qualified as T
import Data.Text.Encoding qualified as T
import Debug.Trace (trace)
import Distribution.ModuleName (ModuleName)
import Distribution.Types.PackageName
import GHC.Data.FastString (fs_sbs)
import GHC.Generics (Generic)
import GHC.Types.Name (OccName (occNameFS))
import GHC.Types.Name.Reader (RdrName (..), rdrNameOcc)
import Ormolu.Utils (ghcModuleNameToCabal)
-- | An operator name.
newtype OpName = MkOpName
{ -- | Invariant: UTF-8 encoded
getOpName :: ShortByteString
}
deriving newtype (Eq, Ord, Binary, NFData)
-- | Convert an 'OpName' to 'Text'.
unOpName :: OpName -> Text
unOpName = T.decodeUtf8 . SBS.fromShort . getOpName
pattern OpName :: Text -> OpName
pattern OpName opName <- (unOpName -> opName)
where
OpName = MkOpName . SBS.toShort . T.encodeUtf8
{-# COMPLETE OpName #-}
-- | Convert an 'OccName to an 'OpName'.
occOpName :: OccName -> OpName
occOpName = MkOpName . fs_sbs . occNameFS
instance Show OpName where
show = T.unpack . unOpName
instance IsString OpName where
fromString = OpName . T.pack
-- | Fixity direction.
data FixityDirection
= InfixL
| InfixR
| InfixN
deriving stock (Eq, Ord, Show, Generic)
deriving anyclass (Binary, NFData)
-- | Fixity information about an infix operator. This type provides precise
-- information as opposed to 'FixityApproximation'.
data FixityInfo = FixityInfo
{ -- | Fixity direction
fiDirection :: FixityDirection,
-- | Precedence
fiPrecedence :: Int
}
deriving stock (Eq, Ord, Show, Generic)
deriving anyclass (Binary, NFData)
-- | Fixity info of the built-in colon data constructor.
colonFixityInfo :: FixityInfo
colonFixityInfo = FixityInfo InfixR 5
-- | Fixity that is implicitly assumed if no fixity declaration is present.
defaultFixityInfo :: FixityInfo
defaultFixityInfo = FixityInfo InfixL 9
-- | Approximation of fixity information that takes the uncertainty that can
-- arise from conflicting definitions into account.
data FixityApproximation = FixityApproximation
{ -- | Fixity direction if it is known
faDirection :: Maybe FixityDirection,
-- | Minimum precedence level found in the (maybe conflicting)
-- definitions for the operator (inclusive)
faMinPrecedence :: Int,
-- | Maximum precedence level found in the (maybe conflicting)
-- definitions for the operator (inclusive)
faMaxPrecedence :: Int
}
deriving stock (Eq, Ord, Show, Generic)
deriving anyclass (Binary, NFData)
-- | Gives the ability to merge two (maybe conflicting) definitions for an
-- operator, keeping the higher level of compatible information from both.
instance Semigroup FixityApproximation where
FixityApproximation {faDirection = dir1, faMinPrecedence = min1, faMaxPrecedence = max1}
<> FixityApproximation {faDirection = dir2, faMinPrecedence = min2, faMaxPrecedence = max2} =
FixityApproximation
{ faDirection = dir',
faMinPrecedence = min min1 min2,
faMaxPrecedence = max max1 max2
}
where
dir' = case (dir1, dir2) of
(Just a, Just b) | a == b -> Just a
_ -> Nothing
-- | The lowest level of information we can have about an operator.
defaultFixityApproximation :: FixityApproximation
defaultFixityApproximation = fixityInfoToApproximation defaultFixityInfo
-- | Convert from 'FixityInfo' to 'FixityApproximation'.
fixityInfoToApproximation :: FixityInfo -> FixityApproximation
fixityInfoToApproximation FixityInfo {..} =
FixityApproximation
{ faDirection = Just fiDirection,
faMinPrecedence = fiPrecedence,
faMaxPrecedence = fiPrecedence
}
-- | The map of operators declared by each package grouped by module name.
newtype HackageInfo
= HackageInfo (Map PackageName (Map ModuleName (Map OpName FixityInfo)))
deriving stock (Generic)
deriving anyclass (Binary, NFData)
-- | Map from the operator name to its 'FixityInfo'.
newtype FixityOverrides = FixityOverrides
{ unFixityOverrides :: Map OpName FixityInfo
}
deriving stock (Eq, Show)
-- | Fixity overrides to use by default.
defaultFixityOverrides :: FixityOverrides
defaultFixityOverrides = FixityOverrides Map.empty
-- | Module re-exports
newtype ModuleReexports = ModuleReexports
{ unModuleReexports :: Map ModuleName (NonEmpty (Maybe PackageName, ModuleName))
}
deriving stock (Eq, Show)
-- | Module re-exports to apply by default.
defaultModuleReexports :: ModuleReexports
defaultModuleReexports =
ModuleReexports . Map.fromList $
[ ( "Control.Lens",
l
"lens"
[ "Control.Lens.At",
"Control.Lens.Cons",
"Control.Lens.Each",
"Control.Lens.Empty",
"Control.Lens.Equality",
"Control.Lens.Fold",
"Control.Lens.Getter",
"Control.Lens.Indexed",
"Control.Lens.Iso",
"Control.Lens.Lens",
"Control.Lens.Level",
"Control.Lens.Plated",
"Control.Lens.Prism",
"Control.Lens.Reified",
"Control.Lens.Review",
"Control.Lens.Setter",
"Control.Lens.TH",
"Control.Lens.Traversal",
"Control.Lens.Tuple",
"Control.Lens.Type",
"Control.Lens.Wrapped",
"Control.Lens.Zoom"
]
),
( "Servant",
l
"servant"
[ "Servant.API"
]
),
( "Optics",
l
"optics"
[ "Optics.Fold",
"Optics.Operators",
"Optics.IxAffineFold",
"Optics.IxFold",
"Optics.IxTraversal",
"Optics.Traversal"
]
),
( "Test.Hspec",
l
"hspec-expectations"
[ "Test.Hspec.Expectations"
]
)
]
where
l packageName xs = (Just packageName,) <$> NE.fromList xs
-- | Fixity information that is specific to a package being formatted. It
-- requires module-specific imports in order to be usable.
newtype PackageFixityMap
= PackageFixityMap (Map OpName (NonEmpty (PackageName, ModuleName, FixityInfo)))
deriving stock (Eq, Show)
-- | Fixity map that takes into account imports in a particular module.
newtype ModuleFixityMap
= ModuleFixityMap (Map OpName FixityProvenance)
deriving stock (Eq, Show)
-- | Provenance of fixity info.
data FixityProvenance
= -- | 'FixityInfo' of a built-in operator or provided by a user override.
Given FixityInfo
| -- | 'FixityInfo' to be inferred from module imports.
FromModuleImports (NonEmpty (FixityQualification, FixityInfo))
deriving stock (Eq, Show)
-- | Fixity qualification that determines how 'FixityInfo' matches a
-- particular use of an operator, given whether it is qualified or
-- unqualified and the module name used.
data FixityQualification
= UnqualifiedAndQualified ModuleName
| OnlyQualified ModuleName
deriving stock (Eq, Show)
-- | Get a 'FixityApproximation' of an operator.
inferFixity ::
-- | Whether to print debug info regarding fixity inference
Choice "debug" ->
-- | Operator name
RdrName ->
-- | Module fixity map
ModuleFixityMap ->
-- | The resulting fixity approximation
FixityApproximation
inferFixity debug rdrName (ModuleFixityMap m) =
if Choice.isTrue debug
then
trace
(renderFixityJustification opName moduleName m result)
result
else result
where
result =
case Map.lookup opName m of
Nothing -> defaultFixityApproximation
Just (Given fixityInfo) ->
fixityInfoToApproximation fixityInfo
Just (FromModuleImports xs) ->
let isMatching (provenance, _fixityInfo) =
case provenance of
UnqualifiedAndQualified mn ->
maybe True (== mn) moduleName
OnlyQualified mn ->
maybe False (== mn) moduleName
in fromMaybe defaultFixityApproximation
. foldMap (Just . fixityInfoToApproximation . snd)
$ NE.filter isMatching xs
opName = occOpName (rdrNameOcc rdrName)
moduleName = case rdrName of
Qual x _ -> Just (ghcModuleNameToCabal x)
_ -> Nothing
-- | Render a human-readable account of why a certain 'FixityApproximation'
-- was chosen for an operator.
renderFixityJustification ::
-- | Operator name
OpName ->
-- | Qualification of the operator name
Maybe ModuleName ->
-- | Module fixity map
Map OpName FixityProvenance ->
-- | The chosen fixity approximation
FixityApproximation ->
String
renderFixityJustification opName mqualification m approximation =
concat
[ "FIXITY analysis of ",
show opName,
case mqualification of
Nothing -> ""
Just mn -> " qualified in " ++ show mn,
"\n Provenance: " ++ show (Map.lookup opName m),
"\n Inferred: " ++ show approximation
]