{-# LANGUAGE CPP #-}
{-# LANGUAGE ScopedTypeVariables #-}
#if MIN_VERSION_filepath(1,4,100)
#define OS_PATH 1
#endif
module Language.LSP.Types.Uri.OsPath
(
#ifdef OS_PATH
osPathToNormalizedFilePath
, normalizedFilePathToOsPath
, EncodingException
#endif
) where
#ifdef OS_PATH
import Control.Exception hiding (try)
import Control.Monad.Catch
import GHC.IO.Encoding (getFileSystemEncoding)
import Language.LSP.Types.Uri
import System.IO
import System.IO.Unsafe (unsafePerformIO)
import System.OsPath
import System.OsPath.Encoding (EncodingException)
osPathToNormalizedFilePath :: MonadThrow m => OsPath -> m NormalizedFilePath
osPathToNormalizedFilePath :: forall (m :: * -> *).
MonadThrow m =>
OsPath -> m NormalizedFilePath
osPathToNormalizedFilePath = (FilePath -> NormalizedFilePath)
-> m FilePath -> m NormalizedFilePath
forall a b. (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap FilePath -> NormalizedFilePath
toNormalizedFilePath (m FilePath -> m NormalizedFilePath)
-> (OsPath -> m FilePath) -> OsPath -> m NormalizedFilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either EncodingException FilePath -> m FilePath
forall (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
Either e a -> m a
liftException (Either EncodingException FilePath -> m FilePath)
-> (OsPath -> Either EncodingException FilePath)
-> OsPath
-> m FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextEncoding
-> TextEncoding -> OsPath -> Either EncodingException FilePath
decodeWith TextEncoding
systemEnc TextEncoding
utf16le
normalizedFilePathToOsPath :: MonadThrow m => NormalizedFilePath -> m OsPath
normalizedFilePathToOsPath :: forall (m :: * -> *).
MonadThrow m =>
NormalizedFilePath -> m OsPath
normalizedFilePathToOsPath = Either EncodingException OsPath -> m OsPath
forall (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
Either e a -> m a
liftException (Either EncodingException OsPath -> m OsPath)
-> (NormalizedFilePath -> Either EncodingException OsPath)
-> NormalizedFilePath
-> m OsPath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextEncoding
-> TextEncoding -> FilePath -> Either EncodingException OsPath
encodeWith TextEncoding
systemEnc TextEncoding
utf16le (FilePath -> Either EncodingException OsPath)
-> (NormalizedFilePath -> FilePath)
-> NormalizedFilePath
-> Either EncodingException OsPath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NormalizedFilePath -> FilePath
fromNormalizedFilePath
liftException :: (MonadThrow m, Exception e) => Either e a -> m a
liftException :: forall (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
Either e a -> m a
liftException (Right a
x) = a -> m a
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
x
liftException (Left e
err) = e -> m a
forall e a. (HasCallStack, Exception e) => e -> m a
forall (m :: * -> *) e a.
(MonadThrow m, HasCallStack, Exception e) =>
e -> m a
throwM e
err
systemEnc :: TextEncoding
systemEnc :: TextEncoding
systemEnc = IO TextEncoding -> TextEncoding
forall a. IO a -> a
unsafePerformIO IO TextEncoding
getFileSystemEncoding
#endif