Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- encodeUtf :: MonadThrow m => String -> m OsString
- encodeWith :: TextEncoding -> TextEncoding -> String -> Either EncodingException OsString
- encodeFS :: String -> IO OsString
- decodeUtf :: MonadThrow m => OsString -> m String
- decodeWith :: TextEncoding -> TextEncoding -> OsString -> Either EncodingException String
- decodeFS :: OsString -> IO String
- fromBytes :: MonadThrow m => ByteString -> m OsString
- osstr :: QuasiQuoter
- unpack :: OsString -> [OsChar]
- pack :: [OsChar] -> OsString
- unsafeFromChar :: Char -> OsChar
- toChar :: OsChar -> Char
Documentation
encodeUtf :: MonadThrow m => String -> m OsString Source #
Partial unicode friendly encoding.
On windows this encodes as UTF16-LE (strictly), which is a pretty good guess. On unix this encodes as UTF8 (strictly), which is a good guess.
Throws a EncodingException
if encoding fails.
:: TextEncoding | unix text encoding |
-> TextEncoding | windows text encoding |
-> String | |
-> Either EncodingException OsString |
Encode an OsString
given the platform specific encodings.
encodeFS :: String -> IO OsString Source #
Like encodeUtf
, except this mimics the behavior of the base library when doing filesystem
operations, which is:
- on unix, uses shady PEP 383 style encoding (based on the current locale, but PEP 383 only works properly on UTF-8 encodings, so good luck)
- on windows does permissive UTF-16 encoding, where coding errors generate Chars in the surrogate range
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).
decodeUtf :: MonadThrow m => OsString -> m String Source #
Partial unicode friendly decoding.
On windows this decodes as UTF16-LE (strictly), which is a pretty good guess. On unix this decodes as UTF8 (strictly), 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 |
Decode an OsString
with the specified encoding.
The String is forced into memory to catch all exceptions.
decodeFS :: OsString -> IO String Source #
Like decodeUtf
, except this mimics the behavior of the base library when doing filesystem
operations, which is:
- on unix, uses shady PEP 383 style encoding (based on the current locale, but PEP 383 only works properly on UTF-8 encodings, so good luck)
- on windows does permissive UTF-16 encoding, where coding errors generate Chars in the surrogate range
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).
fromBytes :: 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).
osstr :: QuasiQuoter Source #
QuasiQuote an OsString
. This accepts Unicode characters
and encodes as UTF-8 on unix and UTF-16 on windows.
pack :: [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.