Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- toOsStringUtf :: MonadThrow m => String -> m OsString
- toOsStringEnc :: TextEncoding -> TextEncoding -> String -> Either EncodingException OsString
- toOsStringFS :: String -> IO OsString
- fromOsStringUtf :: MonadThrow m => OsString -> m String
- fromOsStringEnc :: TextEncoding -> TextEncoding -> OsString -> Either EncodingException String
- fromOsStringFS :: OsString -> IO String
- bytesToOsString :: MonadThrow m => ByteString -> m OsString
- qq :: (ByteString -> Q Exp) -> QuasiQuoter
- mkOsString :: ByteString -> Q Exp
- osstr :: QuasiQuoter
- unpackOsString :: OsString -> [OsChar]
- packOsString :: [OsChar] -> OsString
- unsafeFromChar :: Char -> OsChar
- toChar :: OsChar -> Char
Documentation
toOsStringUtf :: MonadThrow m => String -> m OsString Source #
Convert a String.
On windows this encodes as UTF16-LE, which is a pretty good guess. On unix this encodes as UTF8, which is a good guess.
Throws a EncodingException
if encoding fails.
:: TextEncoding | unix text encoding |
-> TextEncoding | windows text encoding |
-> String | |
-> Either EncodingException OsString |
Like toOsStringUtf
, except allows to provide encodings.
toOsStringFS :: String -> IO OsString Source #
Like toOsStringUtf
, except on unix this uses the current
filesystem locale for encoding instead of always UTF8.
Looking up the locale requires IO. If you're not worried about calls
to setFileSystemEncoding
, then unsafePerformIO
may be feasible (make sure
to deeply evaluate the result to catch exceptions).
Throws a EncodingException
if decoding fails.
fromOsStringUtf :: MonadThrow m => OsString -> m String Source #
Partial unicode friendly decoding.
On windows this decodes as UTF16-LE (which is the expected filename encoding). On unix this decodes as UTF8 (which is a good guess). Note that filenames on unix are encoding agnostic char arrays.
Throws a EncodingException
if decoding fails.
:: TextEncoding | unix text encoding |
-> TextEncoding | windows text encoding |
-> OsString | |
-> Either EncodingException String |
Like fromOsStringUtf
, except allows to provide encodings.
The String is forced into memory to catch all exceptions.
fromOsStringFS :: OsString -> IO String Source #
Like fromOsStringUtf
, except on unix this uses the current
filesystem locale for decoding instead of always UTF8. On windows, uses UTF-16LE.
Looking up the locale requires IO. If you're not worried about calls
to setFileSystemEncoding
, then unsafePerformIO
may be feasible (make sure
to deeply evaluate the result to catch exceptions).
Throws EncodingException
if decoding fails.
bytesToOsString :: MonadThrow m => ByteString -> m OsString Source #
Constructs an OsString
from a ByteString.
On windows, this ensures valid UCS-2LE, on unix it is passed unchanged/unchecked.
Throws EncodingException
on invalid UCS-2LE on windows (although unlikely).
qq :: (ByteString -> Q Exp) -> QuasiQuoter Source #
mkOsString :: ByteString -> Q Exp Source #
QuasiQuote an OsString
. This accepts Unicode characters
and encodes as UTF-8 on unix and UTF-16 on windows.
packOsString :: [OsChar] -> OsString Source #
Pack a list of OsChar
to an OsString
Note that using this in conjunction with unsafeFromChar
to
convert from [Char]
to OsString
is probably not what
you want, because it will truncate unicode code points.
unsafeFromChar :: Char -> OsChar Source #
Truncates on unix to 1 and on Windows to 2 octets.