Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- ucs2le :: TextEncoding
- mkUcs2le :: CodingFailureMode -> TextEncoding
- ucs2le_DF :: CodingFailureMode -> IO (TextDecoder ())
- ucs2le_EF :: CodingFailureMode -> IO (TextEncoder ())
- ucs2le_decode :: DecodeBuffer
- ucs2le_encode :: EncodeBuffer
- utf16le_b :: TextEncoding
- mkUTF16le_b :: CodingFailureMode -> TextEncoding
- utf16le_b_DF :: CodingFailureMode -> IO (TextDecoder ())
- utf16le_b_EF :: CodingFailureMode -> IO (TextEncoder ())
- utf16le_b_decode :: DecodeBuffer
- utf16le_b_encode :: EncodeBuffer
- cWcharsToChars_UCS2 :: [Word16] -> [Char]
- cWcharsToChars :: [Word16] -> [Char]
- charsToCWchars :: [Char] -> [Word16]
- withFilePathWin :: FilePath -> (Int -> Ptr Word16 -> IO a) -> IO a
- peekFilePathWin :: (Ptr Word16, Int) -> IO FilePath
- withFilePathPosix :: FilePath -> (CStringLen -> IO a) -> IO a
- peekFilePathPosix :: CStringLen -> IO FilePath
- decodeWithTE :: TextEncoding -> ShortByteString -> Either EncodingException String
- encodeWithTE :: TextEncoding -> String -> Either EncodingException ShortByteString
- decodeWithBasePosix :: ShortByteString -> IO String
- encodeWithBasePosix :: String -> IO ShortByteString
- decodeWithBaseWindows :: ShortByteString -> IO String
- encodeWithBaseWindows :: String -> IO ShortByteString
- data EncodingException = EncodingError String (Maybe Word8)
- showEncodingException :: EncodingException -> String
- wNUL :: Word16
Documentation
ucs2le_DF :: CodingFailureMode -> IO (TextDecoder ()) Source #
ucs2le_EF :: CodingFailureMode -> IO (TextEncoder ()) Source #
utf16le_b :: TextEncoding Source #
Mimics the base encoding for filesystem operations. This should be total on all inputs (word16 byte arrays).
Note that this has a subtle difference to encodeWithBaseWindows
/decodeWithBaseWindows
: it doesn't care for
the 0x0000
end marker and will as such produce different results. Use takeWhile (/= 'NUL')
on the input
to recover this behavior.
utf16le_b_DF :: CodingFailureMode -> IO (TextDecoder ()) Source #
utf16le_b_EF :: CodingFailureMode -> IO (TextEncoder ()) Source #
cWcharsToChars_UCS2 :: [Word16] -> [Char] Source #
cWcharsToChars :: [Word16] -> [Char] Source #
charsToCWchars :: [Char] -> [Word16] Source #
withFilePathPosix :: FilePath -> (CStringLen -> IO a) -> IO a Source #
peekFilePathPosix :: CStringLen -> IO FilePath Source #
decodeWithTE :: TextEncoding -> ShortByteString -> Either EncodingException String Source #
Decode with the given TextEncoding
.
encodeWithTE :: TextEncoding -> String -> Either EncodingException ShortByteString Source #
Encode with the given TextEncoding
.
decodeWithBasePosix :: ShortByteString -> IO String Source #
This mimics the filepath decoder base uses on unix, with the small distinction that we're not truncating at NUL bytes (because we're not at the outer FFI layer).
encodeWithBasePosix :: String -> IO ShortByteString Source #
This mimics the filepath dencoder base uses on unix, with the small distinction that we're not truncating at NUL bytes (because we're not at the outer FFI layer).
decodeWithBaseWindows :: ShortByteString -> IO String Source #
This mimics the filepath decoder base uses on windows, with the small distinction that we're not truncating at NUL bytes (because we're not at the outer FFI layer).
encodeWithBaseWindows :: String -> IO ShortByteString Source #
This mimics the filepath dencoder base uses on windows, with the small distinction that we're not truncating at NUL bytes (because we're not at the outer FFI layer).
data EncodingException Source #
EncodingError String (Maybe Word8) | Could not decode a byte sequence because it was invalid under the given encoding, or ran out of input in mid-decode. |
Instances
Exception EncodingException Source # | |
Show EncodingException Source # | |
Defined in System.OsPath.Encoding.Internal showsPrec :: Int -> EncodingException -> ShowS # show :: EncodingException -> String # showList :: [EncodingException] -> ShowS # | |
NFData EncodingException Source # | |
Defined in System.OsPath.Encoding.Internal rnf :: EncodingException -> () # | |
Eq EncodingException Source # | |
Defined in System.OsPath.Encoding.Internal (==) :: EncodingException -> EncodingException -> Bool # (/=) :: EncodingException -> EncodingException -> Bool # |