filepath-1.4.99.2: Library for manipulating FilePaths in a cross platform way.
Safe HaskellNone
LanguageHaskell2010

System.OsPath.Encoding

Synopsis

Types

data EncodingException Source #

Constructors

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

Instances details
Eq EncodingException Source # 
Instance details

Defined in System.OsPath.Encoding.Internal

Show EncodingException Source # 
Instance details

Defined in System.OsPath.Encoding.Internal

Methods

showsPrec :: Int -> EncodingException -> ShowS

show :: EncodingException -> String

showList :: [EncodingException] -> ShowS

Exception EncodingException Source # 
Instance details

Defined in System.OsPath.Encoding.Internal

Methods

toException :: EncodingException -> SomeException

fromException :: SomeException -> Maybe EncodingException

displayException :: EncodingException -> String

NFData EncodingException Source # 
Instance details

Defined in System.OsPath.Encoding.Internal

Methods

rnf :: EncodingException -> ()

UCS-2

ucs2le :: TextEncoding Source #

mkUcs2le :: CodingFailureMode -> TextEncoding Source #

ucs2le_DF :: CodingFailureMode -> IO (TextDecoder ()) Source #

ucs2le_EF :: CodingFailureMode -> IO (TextEncoder ()) Source #

ucs2le_decode :: DecodeBuffer Source #

ucs2le_encode :: EncodeBuffer Source #

UTF-16LE_b

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.

mkUTF16le_b :: CodingFailureMode -> TextEncoding Source #

utf16le_b_DF :: CodingFailureMode -> IO (TextDecoder ()) Source #

utf16le_b_EF :: CodingFailureMode -> IO (TextEncoder ()) Source #

utf16le_b_decode :: DecodeBuffer Source #

utf16le_b_encode :: EncodeBuffer Source #

base encoding

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).

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).

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).

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).