Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data PosixString
- data PosixChar
- toPlatformStringUtf :: MonadThrow m => String -> m PosixString
- toPlatformStringEnc :: String -> TextEncoding -> Either EncodingException PosixString
- toPlatformStringFS :: String -> IO PosixString
- bytesToPlatformString :: MonadThrow m => ByteString -> m PosixString
- pstr :: QuasiQuoter
- packPlatformString :: [PosixChar] -> PosixString
- fromPlatformStringUtf :: MonadThrow m => PosixString -> m String
- fromPlatformStringEnc :: PosixString -> TextEncoding -> Either EncodingException String
- fromPlatformStringFS :: PosixString -> IO String
- unpackPlatformString :: PosixString -> [PosixChar]
- unsafeFromChar :: Char -> PosixChar
- toChar :: PosixChar -> Char
Types
data PosixString Source #
Commonly used Posix string as uninterpreted char[]
array.
Instances
Instances
Eq PosixChar Source # | |
Ord PosixChar Source # | |
Defined in System.OsString.Internal.Types | |
Show PosixChar Source # | |
Generic PosixChar Source # | |
NFData PosixChar Source # | |
Defined in System.OsString.Internal.Types | |
type Rep PosixChar Source # | |
Defined in System.OsString.Internal.Types type Rep PosixChar = D1 ('MetaData "PosixChar" "System.OsString.Internal.Types" "filepath-2.0.0.1-inplace" 'True) (C1 ('MetaCons "PW" 'PrefixI 'True) (S1 ('MetaSel ('Just "unPW") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word8))) |
String construction
toPlatformStringUtf :: MonadThrow m => String -> m PosixString 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 :: String -> TextEncoding -> Either EncodingException PosixString Source #
Like toPlatformStringUtf
, except allows to provide an encoding.
toPlatformStringFS :: String -> IO PosixString 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 PosixString 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 PosixString
. This accepts Unicode characters
and encodes as UTF-8 on unix.
packPlatformString :: [PosixChar] -> PosixString 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 => PosixString -> 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 :: PosixString -> TextEncoding -> Either EncodingException String Source #
Like fromPlatformStringUtf
, except allows to provide a text encoding.
The String is forced into memory to catch all exceptions.
fromPlatformStringFS :: PosixString -> 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 :: PosixString -> [PosixChar] Source #
Unpack a platform string to a list of platform words.
Word construction
unsafeFromChar :: Char -> PosixChar Source #
Truncates to 1 octet.