Skip to content

Commit fa72e57

Browse files
author
kokobd
committed
extract OsPath related CPP to a standalone module
1 parent fa6b362 commit fa72e57

File tree

3 files changed

+88
-74
lines changed

3 files changed

+88
-74
lines changed

lsp-types/lsp-types.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -68,6 +68,7 @@ library
6868
, Language.LSP.Types.WorkspaceEdit
6969
, Language.LSP.Types.WorkspaceFolders
7070
, Language.LSP.Types.WorkspaceSymbol
71+
, Language.LSP.Types.OsPath.Compat
7172
-- other-extensions:
7273
ghc-options: -Wall
7374
build-depends: base >= 4.11 && < 5
Lines changed: 78 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,78 @@
1+
{-# LANGUAGE CPP #-}
2+
3+
#if MIN_VERSION_filepath(1,4,100)
4+
#define OS_PATH 1
5+
#endif
6+
7+
module Language.LSP.Types.OsPath.Compat
8+
( OsPath
9+
#ifdef OS_PATH
10+
, module System.OsPath
11+
#else
12+
, module System.FilePath
13+
#endif
14+
, toShortByteString
15+
, fromShortByteString
16+
, toFilePath
17+
, fromFilePath
18+
) where
19+
20+
#ifdef OS_PATH
21+
import qualified System.OsPath as OsPath
22+
import System.OsPath hiding (OsPath)
23+
24+
#if defined(mingw32_HOST_OS) || defined(__MINGW32__)
25+
import System.OsString.Internal.Types (OsString (..),
26+
WindowsString (..))
27+
#else
28+
import System.OsString.Internal.Types (OsString (..),
29+
PosixString (..))
30+
#endif
31+
32+
#else
33+
import qualified Data.ByteString.Short as BS
34+
import qualified Data.Text.Encoding as T
35+
import qualified System.FilePath as OsPath
36+
import System.FilePath hiding (FilePath)
37+
#endif
38+
39+
import Control.Monad.Catch (MonadThrow)
40+
import Data.ByteString.Short (ShortByteString)
41+
42+
type OsPath = OsPath.OsPath
43+
44+
toShortByteString :: OsPath -> ShortByteString
45+
#ifdef OS_PATH
46+
#if defined(mingw32_HOST_OS) || defined(__MINGW32__)
47+
toShortByteString = getWindowsString . getOsString
48+
#else
49+
toShortByteString = getPosixString . getOsString
50+
#endif
51+
#else
52+
toShortByteString = BS.toShort . T.encodeUtf8 . T.pack
53+
#endif
54+
55+
fromShortByteString :: ShortByteString -> OsPath
56+
#ifdef OS_PATH
57+
#if defined(mingw32_HOST_OS) || defined(__MINGW32__)
58+
fromShortByteString = OsString . WindowsString
59+
#else
60+
fromShortByteString = OsString . PosixString
61+
#endif
62+
#else
63+
fromShortByteString = T.unpack . T.decodeUtf8 . BS.fromShort
64+
#endif
65+
66+
toFilePath :: MonadThrow m => OsPath -> m FilePath
67+
#ifdef OS_PATH
68+
toFilePath = decodeUtf
69+
#else
70+
toFilePath = pure
71+
#endif
72+
73+
fromFilePath :: MonadThrow m => FilePath -> m OsPath
74+
#ifdef OS_PATH
75+
fromFilePath = encodeUtf
76+
#else
77+
fromFilePath = pure
78+
#endif

lsp-types/src/Language/LSP/Types/Uri.hs

Lines changed: 9 additions & 74 deletions
Original file line numberDiff line numberDiff line change
@@ -1,13 +1,8 @@
1-
{-# LANGUAGE CPP #-}
21
{-# LANGUAGE DeriveGeneric #-}
32
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
43
{-# LANGUAGE RecordWildCards #-}
54
{-# LANGUAGE TypeSynonymInstances #-}
65

7-
#if MIN_VERSION_filepath(1,4,100)
8-
#define OS_PATH 1
9-
#endif
10-
116
module Language.LSP.Types.Uri
127
( Uri(..)
138
, uriToFilePath
@@ -45,26 +40,8 @@ import qualified System.FilePath as FP
4540
import qualified System.FilePath.Posix as FPP
4641
import qualified System.FilePath.Windows as FPW
4742
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)
6845

6946

7047
newtype Uri = Uri { getUri :: Text }
@@ -184,12 +161,6 @@ platformAdjustToUriPath systemOS srcPath
184161
FPP.addTrailingPathSeparator (init drv)
185162
| otherwise = drv
186163

187-
#ifdef OS_PATH
188-
type OsPath = OsPath.OsPath
189-
#else
190-
type OsPath = FilePath
191-
#endif
192-
193164
-- | Newtype wrapper around FilePath that always has normalized slashes.
194165
-- The NormalizedUri and hash of the FilePath are cached to avoided
195166
-- repeated normalisation when we need to compute them (which is a lot).
@@ -205,52 +176,16 @@ instance Binary NormalizedFilePath where
205176
put (NormalizedFilePath _ fp) = put fp
206177
get = do
207178
v <- Data.Binary.get :: Get ShortByteString
208-
let nuri = internalNormalizedFilePathToUri (wrapOsPath v)
179+
let nuri = internalNormalizedFilePathToUri (OsPath.fromShortByteString v)
209180
return (NormalizedFilePath (fromJust nuri) v)
210181

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-
247182
-- | Internal helper that takes a file path that is assumed to
248183
-- already be normalized to a URI. It is up to the caller
249184
-- to ensure normalization.
250185
internalNormalizedFilePathToUri :: MonadThrow m => OsPath -> m NormalizedUri
251186
internalNormalizedFilePathToUri fp = nuri
252187
where
253-
uriPath = platformAdjustToUriPath System.Info.os <$> decodeUtf fp
188+
uriPath = platformAdjustToUriPath System.Info.os <$> OsPath.toFilePath fp
254189
nuriStr = fmap (T.pack . \p -> fileScheme <> "//" <> p) uriPath
255190
nuri = fmap (\nuriStr' -> NormalizedUri (hash nuriStr') nuriStr') nuriStr
256191

@@ -262,23 +197,23 @@ instance Hashable NormalizedFilePath where
262197
hashWithSalt salt (NormalizedFilePath uri _) = hashWithSalt salt uri
263198

264199
filePathToNormalizedFilePath :: MonadThrow m => FilePath -> m NormalizedFilePath
265-
filePathToNormalizedFilePath fp = encodeUtf fp >>= toNormalizedFilePath
200+
filePathToNormalizedFilePath fp = OsPath.fromFilePath fp >>= toNormalizedFilePath
266201

267202
normalizedFilePathToFilePath :: MonadThrow m => NormalizedFilePath -> m FilePath
268-
normalizedFilePathToFilePath nfp = decodeUtf $ fromNormalizedFilePath nfp
203+
normalizedFilePathToFilePath nfp = OsPath.toFilePath $ fromNormalizedFilePath nfp
269204

270205
toNormalizedFilePath :: MonadThrow m => OsPath -> m NormalizedFilePath
271-
toNormalizedFilePath fp = flip NormalizedFilePath (unwrapOsPath nfp) <$> nuri
206+
toNormalizedFilePath fp = flip NormalizedFilePath (OsPath.toShortByteString nfp) <$> nuri
272207
where
273208
nfp = OsPath.normalise fp
274209
nuri = internalNormalizedFilePathToUri nfp
275210

276211
fromNormalizedFilePath :: NormalizedFilePath -> OsPath
277-
fromNormalizedFilePath (NormalizedFilePath _ fp) = wrapOsPath fp
212+
fromNormalizedFilePath (NormalizedFilePath _ fp) = OsPath.fromShortByteString fp
278213

279214
normalizedFilePathToUri :: NormalizedFilePath -> NormalizedUri
280215
normalizedFilePathToUri (NormalizedFilePath uri _) = uri
281216

282217
uriToNormalizedFilePath :: NormalizedUri -> Maybe NormalizedFilePath
283-
uriToNormalizedFilePath nuri = fmap (NormalizedFilePath nuri . unwrapOsPath) (mbFilePath >>= encodeUtf)
218+
uriToNormalizedFilePath nuri = fmap (NormalizedFilePath nuri . OsPath.toShortByteString) (mbFilePath >>= OsPath.fromFilePath)
284219
where mbFilePath = platformAwareUriToFilePath System.Info.os (fromNormalizedUri nuri)

0 commit comments

Comments
 (0)