Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data WindowsString
- data WindowsChar
- toPlatformStringUtf :: MonadThrow m => String -> m WindowsString
- toPlatformStringEnc :: TextEncoding -> String -> Either EncodingException WindowsString
- toPlatformStringFS :: String -> IO WindowsString
- bytesToPlatformString :: MonadThrow m => ByteString -> m WindowsString
- pstr :: QuasiQuoter
- packPlatformString :: [WindowsChar] -> WindowsString
- fromPlatformStringUtf :: MonadThrow m => WindowsString -> m String
- fromPlatformStringEnc :: TextEncoding -> WindowsString -> Either EncodingException String
- fromPlatformStringFS :: WindowsString -> IO String
- unpackPlatformString :: WindowsString -> [WindowsChar]
- unsafeFromChar :: Char -> WindowsChar
- toChar :: WindowsChar -> Char
Types
data WindowsString Source #
Commonly used windows string as UTF16 bytes.
Instances
data WindowsChar Source #
Instances
String construction
toPlatformStringUtf :: MonadThrow m => String -> m WindowsString Source #
Convert a String.
On windows this encodes as UTF16, which is a pretty good guess. On unix this encodes as UTF8, which is a good guess.
Throws a EncodingException
if encoding fails.
toPlatformStringEnc :: TextEncoding -> String -> Either EncodingException WindowsString Source #
Like toPlatformStringUtf
, except allows to provide an encoding.
toPlatformStringFS :: String -> IO WindowsString Source #
Like toPlatformStringUtf
, 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 encoding fails.
bytesToPlatformString :: MonadThrow m => ByteString -> m WindowsString Source #
Constructs a platform string from a ByteString.
On windows, this ensures valid UCS-2LE, on unix it is passed unchecked. Note that this doesn't expand Word8 to Word16 on windows, so you may get invalid UTF-16.
Throws EncodingException
on invalid UCS-2LE on windows (although unlikely).
QuasiQuote a WindowsString
. This accepts Unicode characters
and encodes as UTF-16 on windows.
packPlatformString :: [WindowsChar] -> WindowsString Source #
Pack a list of platform words to a platform string.
Note that using this in conjunction with unsafeFromChar
to
convert from [Char]
to platform string is probably not what
you want, because it will truncate unicode code points.
String deconstruction
fromPlatformStringUtf :: MonadThrow m => WindowsString -> 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.
fromPlatformStringEnc :: TextEncoding -> WindowsString -> Either EncodingException String Source #
Like fromPlatformStringUtf
, except allows to provide a text encoding.
The String is forced into memory to catch all exceptions.
fromPlatformStringFS :: WindowsString -> IO String Source #
Like fromPlatformStringUt
, 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.
unpackPlatformString :: WindowsString -> [WindowsChar] Source #
Unpack a platform string to a list of platform words.
Word construction
unsafeFromChar :: Char -> WindowsChar Source #
Truncates to 2 octets.
Word deconstruction
toChar :: WindowsChar -> Char Source #
Converts back to a unicode codepoint (total).