{-# LANGUAGE CPP #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE UnliftedFFITypes #-}
module System.OsString.Internal where
import System.OsString.Internal.Types
import Control.Monad.Catch
( MonadThrow )
import Data.ByteString
( ByteString )
import Data.Char
import Language.Haskell.TH.Quote
( QuasiQuoter (..) )
import Language.Haskell.TH.Syntax
( Lift (..), lift )
import System.IO
( TextEncoding )
import System.OsPath.Encoding ( EncodingException(..) )
import GHC.IO.Encoding.Failure ( CodingFailureMode(..) )
#if defined(mingw32_HOST_OS) || defined(__MINGW32__)
import GHC.IO.Encoding.UTF16 ( mkUTF16le )
import qualified System.OsString.Windows as PF
#else
import GHC.IO.Encoding.UTF8 ( mkUTF8 )
import qualified System.OsString.Posix as PF
#endif
encodeUtf :: MonadThrow m => String -> m OsString
encodeUtf :: forall (m :: * -> *). MonadThrow m => String -> m OsString
encodeUtf = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PlatformString -> OsString
OsString forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *). MonadThrow m => String -> m PlatformString
PF.encodeUtf
encodeWith :: TextEncoding
-> TextEncoding
-> String
-> Either EncodingException OsString
#if defined(mingw32_HOST_OS) || defined(__MINGW32__)
encodeWith _ winEnc str = OsString <$> PF.encodeWith winEnc str
#else
encodeWith :: TextEncoding
-> TextEncoding -> String -> Either EncodingException OsString
encodeWith TextEncoding
unixEnc TextEncoding
_ String
str = PlatformString -> OsString
OsString forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TextEncoding -> String -> Either EncodingException PlatformString
PF.encodeWith TextEncoding
unixEnc String
str
#endif
encodeFS :: String -> IO OsString
encodeFS :: String -> IO OsString
encodeFS = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PlatformString -> OsString
OsString forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> IO PlatformString
PF.encodeFS
decodeUtf :: MonadThrow m => OsString -> m String
decodeUtf :: forall (m :: * -> *). MonadThrow m => OsString -> m String
decodeUtf (OsString PlatformString
x) = forall (m :: * -> *). MonadThrow m => PlatformString -> m String
PF.decodeUtf PlatformString
x
decodeWith :: TextEncoding
-> TextEncoding
-> OsString
-> Either EncodingException String
#if defined(mingw32_HOST_OS) || defined(__MINGW32__)
decodeWith _ winEnc (OsString x) = PF.decodeWith winEnc x
#else
decodeWith :: TextEncoding
-> TextEncoding -> OsString -> Either EncodingException String
decodeWith TextEncoding
unixEnc TextEncoding
_ (OsString PlatformString
x) = TextEncoding -> PlatformString -> Either EncodingException String
PF.decodeWith TextEncoding
unixEnc PlatformString
x
#endif
decodeFS :: OsString -> IO String
decodeFS :: OsString -> IO String
decodeFS (OsString PlatformString
x) = PlatformString -> IO String
PF.decodeFS PlatformString
x
fromBytes :: MonadThrow m
=> ByteString
-> m OsString
fromBytes :: forall (m :: * -> *). MonadThrow m => ByteString -> m OsString
fromBytes = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PlatformString -> OsString
OsString forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *).
MonadThrow m =>
ByteString -> m PlatformString
PF.fromBytes
osstr :: QuasiQuoter
osstr :: QuasiQuoter
osstr =
QuasiQuoter
#if defined(mingw32_HOST_OS) || defined(__MINGW32__)
{ quoteExp = \s -> do
osp <- either (fail . show) (pure . OsString) . PF.encodeWith (mkUTF16le ErrorOnCodingFailure) $ s
lift osp
, quotePat = \_ ->
fail "illegal QuasiQuote (allowed as expression only, used as a pattern)"
, quoteType = \_ ->
fail "illegal QuasiQuote (allowed as expression only, used as a type)"
, quoteDec = \_ ->
fail "illegal QuasiQuote (allowed as expression only, used as a declaration)"
}
#else
{ quoteExp :: String -> Q Exp
quoteExp = \String
s -> do
OsString
osp <- forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (forall (m :: * -> *) a. MonadFail m => String -> m a
fail forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show) (forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. PlatformString -> OsString
OsString) forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextEncoding -> String -> Either EncodingException PlatformString
PF.encodeWith (CodingFailureMode -> TextEncoding
mkUTF8 CodingFailureMode
ErrorOnCodingFailure) forall a b. (a -> b) -> a -> b
$ String
s
forall t (m :: * -> *). (Lift t, Quote m) => t -> m Exp
lift OsString
osp
, quotePat :: String -> Q Pat
quotePat = \String
_ ->
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"illegal QuasiQuote (allowed as expression only, used as a pattern)"
, quoteType :: String -> Q Type
quoteType = \String
_ ->
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"illegal QuasiQuote (allowed as expression only, used as a type)"
, quoteDec :: String -> Q [Dec]
quoteDec = \String
_ ->
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"illegal QuasiQuote (allowed as expression only, used as a declaration)"
}
#endif
unpack :: OsString -> [OsChar]
unpack :: OsString -> [OsChar]
unpack (OsString PlatformString
x) = PlatformChar -> OsChar
OsChar forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> PlatformString -> [PlatformChar]
PF.unpack PlatformString
x
pack :: [OsChar] -> OsString
pack :: [OsChar] -> OsString
pack = PlatformString -> OsString
OsString forall b c a. (b -> c) -> (a -> b) -> a -> c
. [PlatformChar] -> PlatformString
PF.pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(OsChar PlatformChar
x) -> PlatformChar
x)
unsafeFromChar :: Char -> OsChar
unsafeFromChar :: Char -> OsChar
unsafeFromChar = PlatformChar -> OsChar
OsChar forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> PlatformChar
PF.unsafeFromChar
toChar :: OsChar -> Char
#if defined(mingw32_HOST_OS) || defined(__MINGW32__)
toChar (OsChar (WindowsChar w)) = chr $ fromIntegral w
#else
toChar :: OsChar -> Char
toChar (OsChar (PosixChar Word8
w)) = Int -> Char
chr forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
w
#endif