{-# 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 = fmap toNormalizedFilePath . liftException . decodeWith systemEnc utf16le
normalizedFilePathToOsPath :: MonadThrow m => NormalizedFilePath -> m OsPath
normalizedFilePathToOsPath = liftException . encodeWith systemEnc utf16le . fromNormalizedFilePath
liftException :: (MonadThrow m, Exception e) => Either e a -> m a
liftException (Right x) = pure x
liftException (Left err) = throwM err
systemEnc :: TextEncoding
systemEnc = unsafePerformIO getFileSystemEncoding
#endif