1
- {-# LANGUAGE CPP #-}
2
1
{-# LANGUAGE DeriveGeneric #-}
3
2
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
4
3
{-# LANGUAGE RecordWildCards #-}
5
4
{-# LANGUAGE TypeSynonymInstances #-}
6
5
7
- #if MIN_VERSION_filepath(1,4,100)
8
- #define OS_PATH 1
9
- #endif
10
-
11
6
module Language.LSP.Types.Uri
12
7
( Uri (.. )
13
8
, uriToFilePath
@@ -45,26 +40,8 @@ import qualified System.FilePath as FP
45
40
import qualified System.FilePath.Posix as FPP
46
41
import qualified System.FilePath.Windows as FPW
47
42
import qualified System.Info
48
-
49
- #ifndef OS_PATH
50
- import qualified Data.Text.Encoding as T
51
- #endif
52
-
53
- #ifdef OS_PATH
54
- import qualified System.OsPath as OsPath
55
-
56
- #if defined(mingw32_HOST_OS) || defined(__MINGW32__)
57
- import System.OsString.Internal.Types (OsString (.. ),
58
- WindowsString (.. ))
59
- #else
60
- import System.OsString.Internal.Types (OsString (.. ),
61
- PosixString (.. ))
62
- #endif
63
-
64
- #else
65
- import qualified Data.ByteString.Short as BS
66
- import qualified System.FilePath as OsPath
67
- #endif
43
+ import qualified Language.LSP.Types.OsPath.Compat as OsPath
44
+ import Language.LSP.Types.OsPath.Compat (OsPath )
68
45
69
46
70
47
newtype Uri = Uri { getUri :: Text }
@@ -184,12 +161,6 @@ platformAdjustToUriPath systemOS srcPath
184
161
FPP. addTrailingPathSeparator (init drv)
185
162
| otherwise = drv
186
163
187
- #ifdef OS_PATH
188
- type OsPath = OsPath. OsPath
189
- #else
190
- type OsPath = FilePath
191
- #endif
192
-
193
164
-- | Newtype wrapper around FilePath that always has normalized slashes.
194
165
-- The NormalizedUri and hash of the FilePath are cached to avoided
195
166
-- repeated normalisation when we need to compute them (which is a lot).
@@ -205,52 +176,16 @@ instance Binary NormalizedFilePath where
205
176
put (NormalizedFilePath _ fp) = put fp
206
177
get = do
207
178
v <- Data.Binary. get :: Get ShortByteString
208
- let nuri = internalNormalizedFilePathToUri (wrapOsPath v)
179
+ let nuri = internalNormalizedFilePathToUri (OsPath. fromShortByteString v)
209
180
return (NormalizedFilePath (fromJust nuri) v)
210
181
211
- unwrapOsPath :: OsPath -> ShortByteString
212
- #ifdef OS_PATH
213
- #if defined(mingw32_HOST_OS) || defined(__MINGW32__)
214
- unwrapOsPath = getWindowsString . getOsString
215
- #else
216
- unwrapOsPath = getPosixString . getOsString
217
- #endif
218
- #else
219
- unwrapOsPath = BS. toShort . T. encodeUtf8 . T. pack
220
- #endif
221
-
222
- wrapOsPath :: ShortByteString -> OsPath
223
- #ifdef OS_PATH
224
- #if defined(mingw32_HOST_OS) || defined(__MINGW32__)
225
- wrapOsPath = OsString . WindowsString
226
- #else
227
- wrapOsPath = OsString . PosixString
228
- #endif
229
- #else
230
- wrapOsPath = T. unpack . T. decodeUtf8 . BS. fromShort
231
- #endif
232
-
233
- decodeUtf :: MonadThrow m => OsPath -> m FilePath
234
- #ifdef OS_PATH
235
- decodeUtf = OsPath. decodeUtf
236
- #else
237
- decodeUtf = pure
238
- #endif
239
-
240
- encodeUtf :: MonadThrow m => FilePath -> m OsPath
241
- #ifdef OS_PATH
242
- encodeUtf = OsPath. encodeUtf
243
- #else
244
- encodeUtf = pure
245
- #endif
246
-
247
182
-- | Internal helper that takes a file path that is assumed to
248
183
-- already be normalized to a URI. It is up to the caller
249
184
-- to ensure normalization.
250
185
internalNormalizedFilePathToUri :: MonadThrow m => OsPath -> m NormalizedUri
251
186
internalNormalizedFilePathToUri fp = nuri
252
187
where
253
- uriPath = platformAdjustToUriPath System.Info. os <$> decodeUtf fp
188
+ uriPath = platformAdjustToUriPath System.Info. os <$> OsPath. toFilePath fp
254
189
nuriStr = fmap (T. pack . \ p -> fileScheme <> " //" <> p) uriPath
255
190
nuri = fmap (\ nuriStr' -> NormalizedUri (hash nuriStr') nuriStr') nuriStr
256
191
@@ -262,23 +197,23 @@ instance Hashable NormalizedFilePath where
262
197
hashWithSalt salt (NormalizedFilePath uri _) = hashWithSalt salt uri
263
198
264
199
filePathToNormalizedFilePath :: MonadThrow m => FilePath -> m NormalizedFilePath
265
- filePathToNormalizedFilePath fp = encodeUtf fp >>= toNormalizedFilePath
200
+ filePathToNormalizedFilePath fp = OsPath. fromFilePath fp >>= toNormalizedFilePath
266
201
267
202
normalizedFilePathToFilePath :: MonadThrow m => NormalizedFilePath -> m FilePath
268
- normalizedFilePathToFilePath nfp = decodeUtf $ fromNormalizedFilePath nfp
203
+ normalizedFilePathToFilePath nfp = OsPath. toFilePath $ fromNormalizedFilePath nfp
269
204
270
205
toNormalizedFilePath :: MonadThrow m => OsPath -> m NormalizedFilePath
271
- toNormalizedFilePath fp = flip NormalizedFilePath (unwrapOsPath nfp) <$> nuri
206
+ toNormalizedFilePath fp = flip NormalizedFilePath (OsPath. toShortByteString nfp) <$> nuri
272
207
where
273
208
nfp = OsPath. normalise fp
274
209
nuri = internalNormalizedFilePathToUri nfp
275
210
276
211
fromNormalizedFilePath :: NormalizedFilePath -> OsPath
277
- fromNormalizedFilePath (NormalizedFilePath _ fp) = wrapOsPath fp
212
+ fromNormalizedFilePath (NormalizedFilePath _ fp) = OsPath. fromShortByteString fp
278
213
279
214
normalizedFilePathToUri :: NormalizedFilePath -> NormalizedUri
280
215
normalizedFilePathToUri (NormalizedFilePath uri _) = uri
281
216
282
217
uriToNormalizedFilePath :: NormalizedUri -> Maybe NormalizedFilePath
283
- uriToNormalizedFilePath nuri = fmap (NormalizedFilePath nuri . unwrapOsPath ) (mbFilePath >>= encodeUtf )
218
+ uriToNormalizedFilePath nuri = fmap (NormalizedFilePath nuri . OsPath. toShortByteString ) (mbFilePath >>= OsPath. fromFilePath )
284
219
where mbFilePath = platformAwareUriToFilePath System.Info. os (fromNormalizedUri nuri)
0 commit comments