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

System.OsString.Posix

Synopsis

Types

data PosixString Source #

Commonly used Posix string as uninterpreted char[] array.

Instances

Instances details
Eq PosixString Source # 
Instance details

Defined in System.OsString.Internal.Types

Methods

(==) :: PosixString -> PosixString -> Bool

(/=) :: PosixString -> PosixString -> Bool

Ord PosixString Source # 
Instance details

Defined in System.OsString.Internal.Types

Read PosixString Source #

Encodes as UTF-8.

Instance details

Defined in System.OsString.Internal.Types

Methods

readsPrec :: Int -> ReadS PosixString

readList :: ReadS [PosixString]

readPrec :: ReadPrec PosixString

readListPrec :: ReadPrec [PosixString]

Show PosixString Source #

Decodes as UTF-8 and replaces invalid chars with unicode replacement char U+FFFD.

Instance details

Defined in System.OsString.Internal.Types

Methods

showsPrec :: Int -> PosixString -> ShowS

show :: PosixString -> String

showList :: [PosixString] -> ShowS

IsString PosixString Source # 
Instance details

Defined in System.OsString.Internal.Types

Methods

fromString :: String -> PosixString

Generic PosixString Source # 
Instance details

Defined in System.OsString.Internal.Types

Associated Types

type Rep PosixString :: Type -> Type

Methods

from :: PosixString -> Rep PosixString x

to :: Rep PosixString x -> PosixString

Semigroup PosixString Source # 
Instance details

Defined in System.OsString.Internal.Types

Methods

(<>) :: PosixString -> PosixString -> PosixString

sconcat :: NonEmpty PosixString -> PosixString

stimes :: Integral b => b -> PosixString -> PosixString

Monoid PosixString Source # 
Instance details

Defined in System.OsString.Internal.Types

NFData PosixString Source # 
Instance details

Defined in System.OsString.Internal.Types

Methods

rnf :: PosixString -> ()

Lift PosixString Source # 
Instance details

Defined in System.OsString.Internal.Types

Methods

lift :: PosixString -> Q Exp

liftTyped :: PosixString -> Q (TExp PosixString)

type Rep PosixString Source # 
Instance details

Defined in System.OsString.Internal.Types

type Rep PosixString = D1 ('MetaData "PosixString" "System.OsString.Internal.Types" "filepath-2.0.0.2-inplace" 'True) (C1 ('MetaCons "PS" 'PrefixI 'True) (S1 ('MetaSel ('Just "unPFP") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ShortByteString)))

data PosixChar Source #

Instances

Instances details
Eq PosixChar Source # 
Instance details

Defined in System.OsString.Internal.Types

Methods

(==) :: PosixChar -> PosixChar -> Bool

(/=) :: PosixChar -> PosixChar -> Bool

Ord PosixChar Source # 
Instance details

Defined in System.OsString.Internal.Types

Methods

compare :: PosixChar -> PosixChar -> Ordering

(<) :: PosixChar -> PosixChar -> Bool

(<=) :: PosixChar -> PosixChar -> Bool

(>) :: PosixChar -> PosixChar -> Bool

(>=) :: PosixChar -> PosixChar -> Bool

max :: PosixChar -> PosixChar -> PosixChar

min :: PosixChar -> PosixChar -> PosixChar

Show PosixChar Source # 
Instance details

Defined in System.OsString.Internal.Types

Methods

showsPrec :: Int -> PosixChar -> ShowS

show :: PosixChar -> String

showList :: [PosixChar] -> ShowS

Generic PosixChar Source # 
Instance details

Defined in System.OsString.Internal.Types

Associated Types

type Rep PosixChar :: Type -> Type

Methods

from :: PosixChar -> Rep PosixChar x

to :: Rep PosixChar x -> PosixChar

NFData PosixChar Source # 
Instance details

Defined in System.OsString.Internal.Types

Methods

rnf :: PosixChar -> ()

type Rep PosixChar Source # 
Instance details

Defined in System.OsString.Internal.Types

type Rep PosixChar = D1 ('MetaData "PosixChar" "System.OsString.Internal.Types" "filepath-2.0.0.2-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 :: TextEncoding -> String -> 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).

pstr :: QuasiQuoter Source #

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 :: TextEncoding -> PosixString -> 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.

Word deconstruction

toChar :: PosixChar -> Char Source #

Converts back to a unicode codepoint (total).